Parsec
ライブラリを使用してファイル パーサーを作成しました。Tasty
パーサーが特定のファイルを正しく解析することを確認するために、テスト フレームワークを使用して高レベルの単体テストを作成したいと考えています。
次のディレクトリ構造に、適切にフォーマットされた 3 つのファイルがあります。
path/to/files -+
|-> fileA
|-> fileB
|-> fileC
私はしたいと思います:
- すべてのファイルを取得する
path/to/files
- 各ファイルの内容を読み取る
testCase
ファイルのコンテンツが正常に解析されることを保証する for each ファイルを作成します- これを動的に実行して、後でファイルを追加し、コードを変更しないようにします
私は次のように構築することができました:
{-# LANGUAGE BangPatterns, FlexibleContexts #-}
module Test.MyParser
( testSuite
) where
import Control.Arrow ((&&&))
import Data.Map (Map,fromList,toList)
import System.Directory
import System.IO.Unsafe (unsafePerformIO) -- This is used for a hack
import Test.Tasty (TestTree,testGroup,withResource)
import Test.Tasty.HUnit
import Text.Parsec
-- | Determine if an Either is a Right or Left value
-- Useful for determining if a parse attempt was successful
isLeft, isRight :: Either a b -> Bool
isLeft (Left _) = True
isLeft _ = False
isRight = not . isLeft
-- | My file parser, a Parsec monad definition
myFileParser :: Parsec s u a
myFileParser = undefined -- The parser's definition is irrelivant
-- | Gets all the given files and thier contents in the specified directory
getFileContentsInDirectory :: FilePath -> IO (Map FilePath String)
getFileContentsInDirectory path = do
files <- filter isFile <$> getDirectoryContents path
sequence . fromList $ (id &&& readFile) . withPath <$> files
where
isFile = not . all (=='.')
withPath file = if last path /= '/'
then concat [path,"/",file]
else concat [path, file]
-- | Reads in all files in a directory and ensures that they correctly parse
-- NOTE: Library hack :(
-- On success, no file names will be displayed.
-- On the first failure, no subsequent files will have parsing attempt tried
-- and the file path for the failed file will be displayed.
testSuite :: TestTree
testSuite = testGroup "Files that should successfully be parsed" [withResource validContents release validateFiles]
where
validContents = getFileContentsInDirectory "path/to/files"
release = const $ pure ()
parse' :: (FilePath,String) -> Either ParseError a
parse' (path,content) = parse myFileParser path content
success :: (FilePath,String) -> Assertion
success (path,content) = assertBool path . isRight $ parse' (path,content)
validateFiles :: IO (Map FilePath String) -> TestTree
validateFiles !filesIO = testGroup "Valid files" [testCase "Unexpected parse errors" fileTree]
where
fileTree :: IO () --also an Assertion
fileTree = do
files <- toList <$> filesIO
sequence_ $ success <$> files
この構造は機能しますが、理想的ではありません。これは、 のtestSuite
実行時に生成される出力があまり説明的でないためです。
成功時:
Files that should successfully be parsed
Valid files
Unexpected parse errors: OK (6.54s)
失敗時:
Files that should successfully be parsed
Valid files
Unexpected parse errors: FAIL (3.40s)
path/to/files/fileB
この出力は、解析に失敗したすべてのファイルではなく、解析に失敗した最初のファイルのみを出力するため、理想的ではありません。また、エラーがあるかどうかに関係なく、どのファイルが正常に解析されているかもわかりません。
テストツリーを次のようにしたいと思います。
成功時:
Files that should successfully be parsed
Valid files
"path/to/files/fileA": OK (2.34s)
"path/to/files/fileB": OK (3.45s)
"path/to/files/fileC": OK (4.56s)
失敗時:
Files that should successfully be parsed
Valid files
"path/to/files/fileA": OK (2.34s)
"path/to/files/fileB": FAIL (3.45s)
"path/to/files/fileC": FAIL (4.56s)
TestTree
ファイルシステムから動的に整形式を作成しようとする私の試みは次のとおりです。
-- | How I would like the code to work, except for the `unsafePerformIO` call
testSuite' :: TestTree
testSuite' = testGroup "Files that should successfully be parsed" [withResource validContents release validateFiles]
where
validContents = getFileContentsInDirectory "path/to/files"
release = const $ pure ()
parse' :: (FilePath,String) -> Either ParseError a
parse' (path,content) = parse myFileParser path content
success :: (FilePath,String) -> TestTree
success (path,content) = testCase (show path) . assert . isRight $ parse' (path,content)
validateFiles :: IO (Map FilePath String) -> TestTree
validateFiles !filesIO = testGroup "Valid files" $ unsafePerformIO fileTree
where
fileTree :: IO [TestTree]
fileTree = fmap success . toList <$> filesIO
ご覧のとおり、このコードにはviaunsafePerformIO
を抽出する見苦しい呼び出しがあります。ファイル システムから派生した情報 (ファイル名) を構成内で使用する方法を理解できなかったため、この安全でない関数呼び出しを使用せざるを得ないと感じました。結果はモナドに閉じ込められました。TestTree
unsafePerformIO :: IO [TestTree] -> [TestTree]
testCase
[TestTree]
IO
この安全でない関数を使用するのは理想的ではないだけでなく、IO
アクションが実際には安全でないため、機能しません。次の例外が発生するため、テスト スイートは実行されません。
*** Exception: Unhandled resource. Probably a bug in the runner you're using.
の型シグネチャが与えられた場合withResource
:
withResource :: IO a -- initialize the resource
-> (a -> IO ()) -- free the resource
-> (IO a -> TestTree) -- IO a is an action which returns the acquired resource. Despite it being an IO action, the resource it returns will be acquired only once and shared across all the tests in the tree.
-> TestTree
または呼び出しのパラメーターで入力を使用しないIO a -> TestTree
最後のパラメーターの型の関数を構築することは不可能であることがわかりました。フレームワーク作成者の詳細な説明を確認したにもかかわらず、おそらく to の使用方法を理解していない可能性があります。Tasty フレームワーク内に、目的を達成するためのより良い機能があるのではないでしょうか?withResource
IO a
TestName
testCase
testGroup
Tasty
withResources
TestTree
質問:
TestTree
必要な記述出力を持つファイル システムから動的に作成するにはどうすればよいですか?