futhark-0.15.7: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageHaskell2010

Futhark.Test

Description

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

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.

getValues :: (MonadFail m, MonadIO m) => FilePath -> Values -> m [Value] Source #

Get the actual core Futhark values corresponding to a Values specification. The FilePath is the directory which file paths are read relative to.

getValuesBS :: MonadIO m => 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.

compareValues :: [Value] -> [Value] -> [Mismatch] Source #

Compare two sets of Futhark values for equality. Shapes and types must also match.

compareValues1 :: [Value] -> [Value] -> Maybe Mismatch Source #

As compareValues, but only reports one mismatch.

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) => FilePath -> Text -> TestRun -> m (ExpectedResult [Value]) Source #

Get the values corresponding to an expected result, if any.

ensureReferenceOutput :: (MonadIO m, MonadError [Text] m) => Maybe Int -> FilePath -> 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.

data Mismatch Source #

Two values differ in some way. The Show instance produces a human-readable explanation.

Instances

Instances details
Show Mismatch Source # 
Instance details

Defined in Futhark.Test.Values

data ProgramTest Source #

Description of a test to be carried out on a Futhark program. The Futhark program is stored separately.

Instances

Instances details
Show ProgramTest Source # 
Instance details

Defined in Futhark.Test

data StructureTest Source #

A structure test specifies a compilation pipeline, as well as metrics for the program coming out the other end.

Instances

Instances details
Show StructureTest Source # 
Instance details

Defined in Futhark.Test

data StructurePipeline Source #

How a program can be transformed.

Instances

Instances details
Show StructurePipeline Source # 
Instance details

Defined in Futhark.Test

data WarningTest Source #

A warning test requires that a warning matching the regular expression is produced. The program must also compile succesfully.

Constructors

ExpectedWarning Text Regex 

Instances

Instances details
Show WarningTest Source # 
Instance details

Defined in Futhark.Test

data TestAction Source #

How to test a program.

Instances

Instances details
Show TestAction Source # 
Instance details

Defined in Futhark.Test

data ExpectedError Source #

The error expected for a negative test.

Constructors

AnyError 
ThisError Text Regex 

Instances

Instances details
Show ExpectedError Source # 
Instance details

Defined in Futhark.Test

data InputOutputs Source #

Input and output pairs for some entry point(s).

Constructors

InputOutputs 

Instances

Instances details
Show InputOutputs Source # 
Instance details

Defined in Futhark.Test

data TestRun Source #

A condition for execution, input, and expected result.

Instances

Instances details
Show TestRun Source # 
Instance details

Defined in Futhark.Test

data ExpectedResult values Source #

How a test case is expected to terminate.

Constructors

Succeeds (Maybe values)

Execution suceeds, with or without expected result values.

RunTimeFailure ExpectedError

Execution fails with this error.

Instances

Instances details
Show values => Show (ExpectedResult values) Source # 
Instance details

Defined in Futhark.Test

Methods

showsPrec :: Int -> ExpectedResult values -> ShowS #

show :: ExpectedResult values -> String #

showList :: [ExpectedResult values] -> ShowS #

data Success Source #

The result expected from a succesful execution.

Constructors

SuccessValues Values

These values are expected.

SuccessGenerateValues

Compute expected values from executing a known-good reference implementation.

Instances

Instances details
Show Success Source # 
Instance details

Defined in Futhark.Test

data Values Source #

Several Values - either literally, or by reference to a file, or to be generated on demand.

Instances

Instances details
Show Values Source # 
Instance details

Defined in Futhark.Test

data GenValue Source #

Constructors

GenValue [Int] PrimType

Generate a value of the given rank and primitive type. Scalars are considered 0-ary arrays.

GenPrim PrimValue

A fixed non-randomised primitive value.

Instances

Instances details
Show GenValue Source # 
Instance details

Defined in Futhark.Test

data Value Source #

An efficiently represented Futhark value. Use pretty to get a human-readable representation, and the instances of Get and Put to obtain binary representations

Instances

Instances details
Show Value Source # 
Instance details

Defined in Futhark.Test.Values

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Binary Value Source # 
Instance details

Defined in Futhark.Test.Values

Methods

put :: Value -> Put #

get :: Get Value #

putList :: [Value] -> Put #

Pretty Value Source # 
Instance details

Defined in Futhark.Test.Values

Methods

ppr :: Value -> Doc #

pprPrec :: Int -> Value -> Doc #

pprList :: [Value] -> Doc #