Safe Haskell | None |
---|---|
Language | Haskell2010 |
Facilities for reading Futhark test programs. A Futhark test program is an ordinary Futhark program where an initial comment block specifies input- and output-sets.
Synopsis
- testSpecFromFile :: FilePath -> IO (Either String ProgramTest)
- testSpecFromFileOrDie :: FilePath -> IO ProgramTest
- testSpecsFromPaths :: [FilePath] -> IO (Either String [(FilePath, ProgramTest)])
- testSpecsFromPathsOrDie :: [FilePath] -> IO [(FilePath, ProgramTest)]
- valuesFromByteString :: String -> ByteString -> Either String [Value]
- newtype FutharkExe = FutharkExe FilePath
- getValues :: (MonadFail m, MonadIO m) => FutharkExe -> FilePath -> Values -> m [Value]
- getValuesBS :: MonadIO m => FutharkExe -> FilePath -> Values -> m ByteString
- withValuesFile :: MonadIO m => FutharkExe -> FilePath -> Values -> (FilePath -> IO a) -> m a
- checkValueTypes :: (MonadError Text m, MonadIO m) => FilePath -> [TypeName] -> m ()
- compareValues :: [Value] -> [Value] -> [Mismatch]
- checkResult :: (MonadError Text m, MonadIO m) => FilePath -> [Value] -> [Value] -> m ()
- testRunReferenceOutput :: FilePath -> Text -> TestRun -> FilePath
- getExpectedResult :: (MonadFail m, MonadIO m) => FutharkExe -> FilePath -> Text -> TestRun -> m (ExpectedResult [Value])
- compileProgram :: (MonadIO m, MonadError [Text] m) => [String] -> FutharkExe -> String -> FilePath -> m (ByteString, ByteString)
- runProgram :: FutharkExe -> FilePath -> [String] -> String -> Text -> Values -> IO (ExitCode, ByteString, ByteString)
- readResults :: (MonadIO m, MonadError Text m) => Server -> [VarName] -> FilePath -> m [Value]
- ensureReferenceOutput :: (MonadIO m, MonadError [Text] m) => Maybe Int -> FutharkExe -> String -> FilePath -> [InputOutputs] -> m ()
- determineTuning :: MonadIO m => Maybe FilePath -> FilePath -> m ([String], String)
- binaryName :: FilePath -> FilePath
- data Mismatch
- data ProgramTest = ProgramTest {
- testDescription :: Text
- testTags :: [Text]
- testAction :: TestAction
- data StructureTest = StructureTest StructurePipeline AstMetrics
- data StructurePipeline
- data WarningTest = ExpectedWarning Text Regex
- data TestAction
- data ExpectedError
- data InputOutputs = InputOutputs {
- iosEntryPoint :: Text
- iosTestRuns :: [TestRun]
- data TestRun = TestRun {}
- data ExpectedResult values
- = Succeeds (Maybe values)
- | RunTimeFailure ExpectedError
- data Success
- data Values
- data Value
Documentation
testSpecFromFile :: FilePath -> IO (Either String ProgramTest) Source #
Read the test specification from the given Futhark program.
testSpecFromFileOrDie :: FilePath -> IO ProgramTest Source #
Like testSpecFromFile
, but kills the process on error.
testSpecsFromPaths :: [FilePath] -> IO (Either String [(FilePath, ProgramTest)]) Source #
Read test specifications from the given paths, which can be a
files or directories containing .fut
files and further
directories.
testSpecsFromPathsOrDie :: [FilePath] -> IO [(FilePath, ProgramTest)] Source #
Like testSpecsFromPaths
, but kills the process on errors.
valuesFromByteString :: String -> ByteString -> Either String [Value] Source #
Try to parse a several values from a byte string. The String
parameter is used for error messages.
newtype FutharkExe Source #
The futhark
executable we are using. This is merely a wrapper
around the underlying file path, because we will be using a lot of
different file paths here, and it is easy to mix them up.
Instances
Eq FutharkExe Source # | |
Defined in Futhark.Test (==) :: FutharkExe -> FutharkExe -> Bool # (/=) :: FutharkExe -> FutharkExe -> Bool # | |
Ord FutharkExe Source # | |
Defined in Futhark.Test compare :: FutharkExe -> FutharkExe -> Ordering # (<) :: FutharkExe -> FutharkExe -> Bool # (<=) :: FutharkExe -> FutharkExe -> Bool # (>) :: FutharkExe -> FutharkExe -> Bool # (>=) :: FutharkExe -> FutharkExe -> Bool # max :: FutharkExe -> FutharkExe -> FutharkExe # min :: FutharkExe -> FutharkExe -> FutharkExe # | |
Show FutharkExe Source # | |
Defined in Futhark.Test showsPrec :: Int -> FutharkExe -> ShowS # show :: FutharkExe -> String # showList :: [FutharkExe] -> ShowS # |
getValuesBS :: MonadIO m => FutharkExe -> FilePath -> Values -> m ByteString Source #
Extract a pretty representation of some Values
. In the IO
monad because this might involve reading from a file. There is no
guarantee that the resulting byte string yields a readable value.
withValuesFile :: MonadIO m => FutharkExe -> FilePath -> Values -> (FilePath -> IO a) -> m a Source #
Evaluate an IO action while the values are available in the binary format in a file by some name. The file will be removed after the action is done.
checkValueTypes :: (MonadError Text m, MonadIO m) => FilePath -> [TypeName] -> m () Source #
Check that the file contains values of the expected types.
compareValues :: [Value] -> [Value] -> [Mismatch] Source #
Compare two sets of Futhark values for equality. Shapes and types must also match.
checkResult :: (MonadError Text m, MonadIO m) => FilePath -> [Value] -> [Value] -> m () Source #
Check that the result is as expected, and write files and throw an error if not.
testRunReferenceOutput :: FilePath -> Text -> TestRun -> FilePath Source #
When/if generating a reference output file for this run, what should it be called? Includes the "data/" folder.
getExpectedResult :: (MonadFail m, MonadIO m) => FutharkExe -> FilePath -> Text -> TestRun -> m (ExpectedResult [Value]) Source #
Get the values corresponding to an expected result, if any.
compileProgram :: (MonadIO m, MonadError [Text] m) => [String] -> FutharkExe -> String -> FilePath -> m (ByteString, ByteString) Source #
compileProgram extra_options futhark backend program
compiles
program
with the command futhark backend extra-options...
, and
returns stdout and stderr of the compiler. Throws an IO exception
containing stderr if compilation fails.
runProgram :: FutharkExe -> FilePath -> [String] -> String -> Text -> Values -> IO (ExitCode, ByteString, ByteString) Source #
runProgram futhark runner extra_options prog entry input
runs the
Futhark program prog
(which must have the .fut
suffix),
executing the entry
entry point and providing input
on stdin.
The program must have been compiled in advance with
compileProgram
. If runner
is non-null, then it is used as
"interpreter" for the compiled program (e.g. python
when using
the Python backends). The extra_options
are passed to the
program.
readResults :: (MonadIO m, MonadError Text m) => Server -> [VarName] -> FilePath -> m [Value] Source #
Read the given variables from a running server.
ensureReferenceOutput :: (MonadIO m, MonadError [Text] m) => Maybe Int -> FutharkExe -> String -> FilePath -> [InputOutputs] -> m () Source #
Ensure that any reference output files exist, or create them (by compiling the program with the reference compiler and running it on the input) if necessary.
determineTuning :: MonadIO m => Maybe FilePath -> FilePath -> m ([String], String) Source #
Determine the --tuning options to pass to the program. The first
argument is the extension of the tuning file, or Nothing
if none
should be used.
binaryName :: FilePath -> FilePath Source #
The name we use for compiled programs.
Two values differ in some way. The Show
instance produces a
human-readable explanation.
data ProgramTest Source #
Description of a test to be carried out on a Futhark program. The Futhark program is stored separately.
ProgramTest | |
|
Instances
Show ProgramTest Source # | |
Defined in Futhark.Test showsPrec :: Int -> ProgramTest -> ShowS # show :: ProgramTest -> String # showList :: [ProgramTest] -> ShowS # |
data StructureTest Source #
A structure test specifies a compilation pipeline, as well as metrics for the program coming out the other end.
Instances
Show StructureTest Source # | |
Defined in Futhark.Test showsPrec :: Int -> StructureTest -> ShowS # show :: StructureTest -> String # showList :: [StructureTest] -> ShowS # |
data StructurePipeline Source #
How a program can be transformed.
Instances
Show StructurePipeline Source # | |
Defined in Futhark.Test showsPrec :: Int -> StructurePipeline -> ShowS # show :: StructurePipeline -> String # showList :: [StructurePipeline] -> ShowS # |
data WarningTest Source #
A warning test requires that a warning matching the regular expression is produced. The program must also compile succesfully.
Instances
Show WarningTest Source # | |
Defined in Futhark.Test showsPrec :: Int -> WarningTest -> ShowS # show :: WarningTest -> String # showList :: [WarningTest] -> ShowS # |
data TestAction Source #
How to test a program.
Instances
Show TestAction Source # | |
Defined in Futhark.Test showsPrec :: Int -> TestAction -> ShowS # show :: TestAction -> String # showList :: [TestAction] -> ShowS # |
data ExpectedError Source #
The error expected for a negative test.
Instances
Show ExpectedError Source # | |
Defined in Futhark.Test showsPrec :: Int -> ExpectedError -> ShowS # show :: ExpectedError -> String # showList :: [ExpectedError] -> ShowS # |
data InputOutputs Source #
Input and output pairs for some entry point(s).
InputOutputs | |
|
Instances
Show InputOutputs Source # | |
Defined in Futhark.Test showsPrec :: Int -> InputOutputs -> ShowS # show :: InputOutputs -> String # showList :: [InputOutputs] -> ShowS # |
A condition for execution, input, and expected result.
TestRun | |
|
data ExpectedResult values Source #
How a test case is expected to terminate.
Succeeds (Maybe values) | Execution suceeds, with or without expected result values. |
RunTimeFailure ExpectedError | Execution fails with this error. |
Instances
Show values => Show (ExpectedResult values) Source # | |
Defined in Futhark.Test showsPrec :: Int -> ExpectedResult values -> ShowS # show :: ExpectedResult values -> String # showList :: [ExpectedResult values] -> ShowS # |
The result expected from a succesful execution.
SuccessValues Values | These values are expected. |
SuccessGenerateValues | Compute expected values from executing a known-good reference implementation. |
Several Values - either literally, or by reference to a file, or to be generated on demand.