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

Futhark.Test.Values

Description

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

Documentation

data Value Source #

An efficiently represented Futhark value. Use pretty to get a human-readable representation, and put to obtain binary a representation.

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 #

PutValue [Value] Source # 
Instance details

Defined in Futhark.Test.Values

Methods

putValue :: [Value] -> Maybe Value Source #

data Compound v Source #

The structure of a compound value, parameterised over the actual values. For most cases you probably want CompoundValue.

Constructors

ValueRecord (Map Text (Compound v)) 
ValueTuple [Compound v]

Must not be single value.

ValueAtom v 

Instances

Instances details
Functor Compound Source # 
Instance details

Defined in Futhark.Test.Values

Methods

fmap :: (a -> b) -> Compound a -> Compound b #

(<$) :: a -> Compound b -> Compound a #

Foldable Compound Source # 
Instance details

Defined in Futhark.Test.Values

Methods

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 #

toList :: Compound a -> [a] #

null :: Compound a -> Bool #

length :: Compound a -> Int #

elem :: Eq a => a -> Compound a -> Bool #

maximum :: Ord a => Compound a -> a #

minimum :: Ord a => Compound a -> a #

sum :: Num a => Compound a -> a #

product :: Num a => Compound a -> a #

Traversable Compound Source # 
Instance details

Defined in Futhark.Test.Values

Methods

traverse :: Applicative f => (a -> f b) -> Compound a -> f (Compound b) #

sequenceA :: Applicative f => Compound (f a) -> f (Compound a) #

mapM :: Monad m => (a -> m b) -> Compound a -> m (Compound b) #

sequence :: Monad m => Compound (m a) -> m (Compound a) #

Eq v => Eq (Compound v) Source # 
Instance details

Defined in Futhark.Test.Values

Methods

(==) :: Compound v -> Compound v -> Bool #

(/=) :: Compound v -> Compound v -> Bool #

Ord v => Ord (Compound v) Source # 
Instance details

Defined in Futhark.Test.Values

Methods

compare :: Compound v -> Compound v -> Ordering #

(<) :: Compound v -> Compound v -> Bool #

(<=) :: Compound v -> Compound v -> Bool #

(>) :: Compound v -> Compound v -> Bool #

(>=) :: Compound v -> Compound v -> Bool #

max :: Compound v -> Compound v -> Compound v #

min :: Compound v -> Compound v -> Compound v #

Show v => Show (Compound v) Source # 
Instance details

Defined in Futhark.Test.Values

Methods

showsPrec :: Int -> Compound v -> ShowS #

show :: Compound v -> String #

showList :: [Compound v] -> ShowS #

Pretty v => Pretty (Compound v) Source # 
Instance details

Defined in Futhark.Test.Values

Methods

ppr :: Compound v -> Doc #

pprPrec :: Int -> Compound v -> Doc #

pprList :: [Compound v] -> Doc #

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.

type Vector = Vector Source #

The value vector type.

Reading Values

readValues :: ByteString -> Maybe [Value] Source #

Parse Futhark values from the given bytestring.

Types of values

data ValueType Source #

A representation of the simple values we represent in this module.

Constructors

ValueType [Int] PrimType 

Instances

Instances details
Eq ValueType Source # 
Instance details

Defined in Futhark.Test.Values

Ord ValueType Source # 
Instance details

Defined in Futhark.Test.Values

Show ValueType Source # 
Instance details

Defined in Futhark.Test.Values

Pretty ValueType Source # 
Instance details

Defined in Futhark.Test.Values

Methods

ppr :: ValueType -> Doc #

pprPrec :: Int -> ValueType -> Doc #

pprList :: [ValueType] -> Doc #

valueType :: Value -> ValueType Source #

Get the type of a value.

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.

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

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.

Methods

getValue :: Value -> Maybe t Source #

Instances

Instances details
GetValue Bool Source # 
Instance details

Defined in Futhark.Test.Values

GetValue Int8 Source # 
Instance details

Defined in Futhark.Test.Values

GetValue Int16 Source # 
Instance details

Defined in Futhark.Test.Values

GetValue Int32 Source # 
Instance details

Defined in Futhark.Test.Values

GetValue Int64 Source # 
Instance details

Defined in Futhark.Test.Values

GetValue Word8 Source # 
Instance details

Defined in Futhark.Test.Values

GetValue Word16 Source # 
Instance details

Defined in Futhark.Test.Values

GetValue Word32 Source # 
Instance details

Defined in Futhark.Test.Values

GetValue Word64 Source # 
Instance details

Defined in Futhark.Test.Values

GetValue t => GetValue [t] Source # 
Instance details

Defined in Futhark.Test.Values

Methods

getValue :: Value -> Maybe [t] Source #

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.

Methods

putValue :: t -> Maybe Value Source #

This may fail for cases such as irregular arrays.

Instances

Instances details
PutValue Word8 Source # 
Instance details

Defined in Futhark.Test.Values

PutValue ByteString Source # 
Instance details

Defined in Futhark.Test.Values

PutValue Text Source # 
Instance details

Defined in Futhark.Test.Values

PutValue PrimValue Source # 
Instance details

Defined in Futhark.Test.Values

PutValue [Value] Source # 
Instance details

Defined in Futhark.Test.Values

Methods

putValue :: [Value] -> Maybe Value Source #