feldspar-language-0.3.1: A functional embedded language for DSP and parallelismSource codeContentsIndex
Feldspar.Core.Types
Contents
Misc.
Tuples
Data
Types
Description
Defines types and classes for the data computed by Feldspar programs.
Synopsis
data T a = T
mkT :: a -> T a
data a :> b = a :> b
class Set a where
universal :: a
type Length = Int
data Tuple a
= One a
| Tup [Tuple a]
showTuple :: Tuple String -> String
tuplePath :: Tuple a -> Tuple [Int]
data PrimitiveData
= UnitData ()
| BoolData Bool
| IntData Integer
| FloatData Float
data StorableData
= PrimitiveData PrimitiveData
| StorableData [StorableData]
type Unsigned32 = Word32
type Signed32 = Int32
type Unsigned16 = Word16
type Signed16 = Int16
type Unsigned8 = Word8
type Signed8 = Int8
data PrimitiveType
= UnitType
| BoolType
| IntType {
signed :: Bool
bitSize :: Int
valueSet :: Range Integer
}
| FloatType (Range Float)
| UserType String
data StorableType = StorableType [Range Length] PrimitiveType
showPrimitiveRange :: PrimitiveType -> String
showStorableSize :: StorableType -> String
class Storable a => Primitive a
class Typeable a => Storable a where
storableData :: a -> StorableData
storableType :: Size a -> T a -> StorableType
storableSize :: a -> Size a
listSize :: T a -> Size a -> [Range Length]
class (Eq a, Monoid (Size a), Set (Size a)) => Typeable a where
type Size a
typeOf :: Size a -> T a -> Tuple StorableType
typeOfStorable :: Storable a => Size a -> T a -> Tuple StorableType
Misc.
data T a Source
Used to pass a type to a function without using undefined.
Constructors
T
mkT :: a -> T aSource
data a :> b Source
Heterogeneous list
Constructors
a :> b
show/hide Instances
(Eq a, Eq b) => Eq (:> a b)
(Ord a, Ord b) => Ord (:> a b)
(Show a, Show b) => Show (:> a b)
(Monoid a, Monoid b) => Monoid (:> a b)
(Set a, Set b) => Set (:> a b)
class Set a whereSource
Methods
universal :: aSource
show/hide Instances
Set ()
Ord a => Set (Range a)
(Set a, Set b) => Set (a, b)
(Set a, Set b) => Set (:> a b)
(Set a, Set b, Set c) => Set (a, b, c)
(Set a, Set b, Set c, Set d) => Set (a, b, c, d)
type Length = IntSource
Tuples
data Tuple a Source
Untyped representation of nested tuples
Constructors
One a
Tup [Tuple a]
show/hide Instances
showTuple :: Tuple String -> StringSource
Shows a nested tuple in Haskell's tuple syntax (e.g "(a,(b,c))").
tuplePath :: Tuple a -> Tuple [Int]Source

Replaces each element by its path in the tuple tree. For example:

 tuplePath (Tup [One 'a',Tup [One 'b', One 'c']])
   ==
 Tup [One [0],Tup [One [1,0],One [1,1]]]
Data
data PrimitiveData Source
Untyped representation of primitive data
Constructors
UnitData ()
BoolData Bool
IntData Integer
FloatData Float
show/hide Instances
data StorableData Source
Untyped representation of storable data (arrays of primitive data)
Constructors
PrimitiveData PrimitiveData
StorableData [StorableData]
show/hide Instances
Types
type Unsigned32 = Word32Source
type Signed32 = Int32Source
type Unsigned16 = Word16Source
type Signed16 = Int16Source
type Unsigned8 = Word8Source
type Signed8 = Int8Source
data PrimitiveType Source
Representation of primitive types
Constructors
UnitType
BoolType
IntType
signed :: Bool
bitSize :: Int
valueSet :: Range Integer
FloatType (Range Float)
UserType String
show/hide Instances
data StorableType Source
Representation of storable types (arrays of primitive types). Array size is given as a list of ranged lengths, starting with outermost array level. Primitive types are treated as zero-dimensional arrays.
Constructors
StorableType [Range Length] PrimitiveType
show/hide Instances
showPrimitiveRange :: PrimitiveType -> StringSource
showStorableSize :: StorableType -> StringSource
Shows the size of a storable type.
class Storable a => Primitive a Source
Primitive types
show/hide Instances
class Typeable a => Storable a whereSource
Storable types (zero- or higher-level arrays of primitive data).
Methods
storableData :: a -> StorableDataSource
Converts a storable value to its untyped representation.
storableType :: Size a -> T a -> StorableTypeSource
Gives the type representation of a storable value.
storableSize :: a -> Size aSource
Gives the size of a storable value.
listSize :: T a -> Size a -> [Range Length]Source
show/hide Instances
class (Eq a, Monoid (Size a), Set (Size a)) => Typeable a whereSource
Associated Types
type Size a Source
This type provides the necessary extra information to compute a type representation Tuple StorableType from a type a. This is needed because the type a is missing information about sizes of arrays and primitive values.
Methods
typeOf :: Size a -> T a -> Tuple StorableTypeSource
Gives the type representation of a storable value.
show/hide Instances
typeOfStorable :: Storable a => Size a -> T a -> Tuple StorableTypeSource
Default implementation of typeOf for Storable types.
Produced by Haddock version 2.6.1