Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
This module defines an efficient value representation as well as parsing and comparison functions. This is because the standard Futhark parser is not able to cope with large values (like arrays that are tens of megabytes in size). The representation defined here does not support tuples, so don't use those as input/output for your test programs.
Synopsis
- data Value
- = Int8Value (Vector Int) (Vector Int8)
- | Int16Value (Vector Int) (Vector Int16)
- | Int32Value (Vector Int) (Vector Int32)
- | Int64Value (Vector Int) (Vector Int64)
- | Word8Value (Vector Int) (Vector Word8)
- | Word16Value (Vector Int) (Vector Word16)
- | Word32Value (Vector Int) (Vector Word32)
- | Word64Value (Vector Int) (Vector Word64)
- | Float32Value (Vector Int) (Vector Float)
- | Float64Value (Vector Int) (Vector Double)
- | BoolValue (Vector Int) (Vector Bool)
- data Compound v
- = ValueRecord (Map Text (Compound v))
- | ValueTuple [Compound v]
- | ValueAtom v
- type CompoundValue = Compound Value
- type Vector = Vector
- readValues :: ByteString -> Maybe [Value]
- data ValueType = ValueType [Int] PrimType
- prettyValueTypeNoDims :: ValueType -> Text
- valueType :: Value -> ValueType
- valueShape :: Value -> [Int]
- valueElems :: Value -> [Value]
- mkCompound :: [v] -> Compound v
- compareValues :: [Value] -> [Value] -> [Mismatch]
- data Mismatch
- class GetValue t where
- class PutValue t where
Documentation
An efficiently represented Futhark value. Use pretty
to get a
human-readable representation, and put
to obtain binary a
representation.
Int8Value (Vector Int) (Vector Int8) | |
Int16Value (Vector Int) (Vector Int16) | |
Int32Value (Vector Int) (Vector Int32) | |
Int64Value (Vector Int) (Vector Int64) | |
Word8Value (Vector Int) (Vector Word8) | |
Word16Value (Vector Int) (Vector Word16) | |
Word32Value (Vector Int) (Vector Word32) | |
Word64Value (Vector Int) (Vector Word64) | |
Float32Value (Vector Int) (Vector Float) | |
Float64Value (Vector Int) (Vector Double) | |
BoolValue (Vector Int) (Vector Bool) |
The structure of a compound value, parameterised over the actual
values. For most cases you probably want CompoundValue
.
ValueRecord (Map Text (Compound v)) | |
ValueTuple [Compound v] | Must not be single value. |
ValueAtom v |
Instances
Functor Compound Source # | |
Foldable Compound Source # | |
Defined in Futhark.Test.Values fold :: Monoid m => Compound m -> m # foldMap :: Monoid m => (a -> m) -> Compound a -> m # foldMap' :: Monoid m => (a -> m) -> Compound a -> m # foldr :: (a -> b -> b) -> b -> Compound a -> b # foldr' :: (a -> b -> b) -> b -> Compound a -> b # foldl :: (b -> a -> b) -> b -> Compound a -> b # foldl' :: (b -> a -> b) -> b -> Compound a -> b # foldr1 :: (a -> a -> a) -> Compound a -> a # foldl1 :: (a -> a -> a) -> Compound a -> a # elem :: Eq a => a -> Compound a -> Bool # maximum :: Ord a => Compound a -> a # minimum :: Ord a => Compound a -> a # | |
Traversable Compound Source # | |
Eq v => Eq (Compound v) Source # | |
Ord v => Ord (Compound v) Source # | |
Show v => Show (Compound v) Source # | |
Pretty v => Pretty (Compound v) Source # | |
type CompoundValue = Compound Value Source #
Like a Value
, but also grouped in compound ways that are not
supported by raw values. You cannot parse or read these in
standard ways, and they cannot be elements of arrays.
Reading Values
readValues :: ByteString -> Maybe [Value] Source #
Parse Futhark values from the given bytestring.
Types of values
A representation of the simple values we represent in this module.
prettyValueTypeNoDims :: ValueType -> Text Source #
Prettyprint a value type with empty dimensions. This is needed for Futhark server programs, whose types are un-sized.
valueShape :: Value -> [Int] Source #
The shape of a value. Empty list in case of a scalar.
Manipulating values
valueElems :: Value -> [Value] Source #
Produce a list of the immediate elements of the value. That is, a 2D array will produce a list of 1D values. While lists are of course inefficient, the actual values are just slices of the original value, which makes them fairly efficient.
mkCompound :: [v] -> Compound v Source #
Create a tuple for a non-unit list, and otherwise a ValueAtom
Comparing Values
compareValues :: [Value] -> [Value] -> [Mismatch] Source #
Compare two sets of Futhark values for equality. Shapes and types must also match.
Two values differ in some way. The Show
instance produces a
human-readable explanation.
Converting values
class GetValue t where Source #
A class for Haskell values that can be retrieved from Value
.
This is a convenience facility - don't expect it to be fast.
class PutValue t where Source #
A class for Haskell values that can be converted to Value
.
This is a convenience facility - don't expect it to be fast.