Safe Haskell | Safe-Inferred |
---|---|
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
- module Futhark.Test.Spec
- valuesFromByteString :: String -> ByteString -> Either String [Value]
- newtype FutharkExe = FutharkExe FilePath
- getValues :: (MonadFail m, MonadIO m) => FutharkExe -> FilePath -> Values -> m [Value]
- getValuesBS :: (MonadFail m, MonadIO m) => FutharkExe -> FilePath -> Values -> m ByteString
- valuesAsVars :: (MonadError Text m, MonadIO m) => Server -> [(VarName, TypeName)] -> FutharkExe -> FilePath -> Values -> m ()
- compareValues :: Tolerance -> 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] -> m [Value]
- ensureReferenceOutput :: (MonadIO m, MonadError [Text] m) => Maybe Int -> FutharkExe -> String -> FilePath -> [InputOutputs] -> m ()
- determineTuning :: MonadIO m => Maybe FilePath -> FilePath -> m ([String], String)
- determineCache :: Maybe FilePath -> FilePath -> [String]
- binaryName :: FilePath -> FilePath
- futharkServerCfg :: FilePath -> [String] -> ServerCfg
- data Mismatch
- data Value
- valueText :: Value -> Text
Documentation
module Futhark.Test.Spec
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
Show FutharkExe Source # | |
Defined in Futhark.Test showsPrec :: Int -> FutharkExe -> ShowS # show :: FutharkExe -> String # showList :: [FutharkExe] -> ShowS # | |
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 # |
getValuesBS :: (MonadFail m, MonadIO m) => FutharkExe -> FilePath -> Values -> m ByteString Source #
Extract a text 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.
valuesAsVars :: (MonadError Text m, MonadIO m) => Server -> [(VarName, TypeName)] -> FutharkExe -> FilePath -> Values -> m () Source #
Make the provided Values
available as server-side variables.
This may involve arbitrary server-side computation. Error
detection... dubious.
compareValues :: Tolerance -> Value -> Value -> [Mismatch] #
Compare two Futhark values for equality.
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] -> 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.
determineCache :: Maybe FilePath -> FilePath -> [String] Source #
Determine the --cache-file
options to pass to the program. The
first argument is the extension of the cache file, or Nothing
if
none should be used.
binaryName :: FilePath -> FilePath Source #
The name we use for compiled programs.
futharkServerCfg :: FilePath -> [String] -> ServerCfg Source #
Create a Futhark server configuration suitable for use when testing/benchmarking Futhark programs.
Two values differ in some way. The Show
instance produces a
human-readable explanation.
An efficiently represented Futhark value, represented as a shape vector and a value vector, which contains elements in row-major order. The size of the value vector must be equal to the product of the shape vector. This is not enforced by the representation, but consuming functions may give unexpected results if this invariant is broken. Scalars are represented with an empty shape vector.
Use valueText
to get a human-readable representation, and put
to obtain binary a representation.
The Eq
instance is the naive one, meaning that no values
containing NaNs will be considered equal. Use the functions from
Futhark.Data.Compare if this is not what you want.