| Portability | non-portable (GHC extensions) /Scalar types supported in array computations/ Integral types: Int, Int8, Int16, Int32, Int64, Word, Word8, Word16, Word32, Word64, CShort, CUShort, CInt, CUInt, CLong, CULong, CLLong, CULLong Floating types: Float, Double, CFloat, CDouble Non-numeric types: Bool, Char, CChar, CSChar, CUChar 'Int' has the same bitwidth as in plain Haskell computations, and 'Float' and 'Double' represent IEEE single and double precision floating point numbers, respectively. | 
|---|---|
| Stability | experimental | 
| Maintainer | Manuel M T Chakravarty <chak@cse.unsw.edu.au> | 
| Safe Haskell | None | 
Data.Array.Accelerate.Type
Description
- module Data.Int
 - module Data.Word
 - module Foreign.C.Types
 - myMkTyCon :: String -> TyCon
 - class Typeable8 t where
 - typeOf7Default :: (Typeable8 t, Typeable a) => t a b c d e f g h -> TypeRep
 - class Typeable9 t where
 - typeOf8Default :: (Typeable9 t, Typeable a) => t a b c d e f g h i -> TypeRep
 - data IntegralDict a where
 - data  FloatingDict a where
- FloatingDict :: (Enum a, Eq a, Ord a, Show a, Floating a, Fractional a, Num a, Real a, RealFrac a, RealFloat a, Storable a) => FloatingDict a
 
 - data  NonNumDict a where
- NonNumDict :: (Bounded a, Enum a, Eq a, Ord a, Show a, Storable a) => NonNumDict a
 
 - data  IntegralType a where
- TypeInt :: IntegralDict Int -> IntegralType Int
 - TypeInt8 :: IntegralDict Int8 -> IntegralType Int8
 - TypeInt16 :: IntegralDict Int16 -> IntegralType Int16
 - TypeInt32 :: IntegralDict Int32 -> IntegralType Int32
 - TypeInt64 :: IntegralDict Int64 -> IntegralType Int64
 - TypeWord :: IntegralDict Word -> IntegralType Word
 - TypeWord8 :: IntegralDict Word8 -> IntegralType Word8
 - TypeWord16 :: IntegralDict Word16 -> IntegralType Word16
 - TypeWord32 :: IntegralDict Word32 -> IntegralType Word32
 - TypeWord64 :: IntegralDict Word64 -> IntegralType Word64
 - TypeCShort :: IntegralDict CShort -> IntegralType CShort
 - TypeCUShort :: IntegralDict CUShort -> IntegralType CUShort
 - TypeCInt :: IntegralDict CInt -> IntegralType CInt
 - TypeCUInt :: IntegralDict CUInt -> IntegralType CUInt
 - TypeCLong :: IntegralDict CLong -> IntegralType CLong
 - TypeCULong :: IntegralDict CULong -> IntegralType CULong
 - TypeCLLong :: IntegralDict CLLong -> IntegralType CLLong
 - TypeCULLong :: IntegralDict CULLong -> IntegralType CULLong
 
 - data FloatingType a where
 - data  NonNumType a where
- TypeBool :: NonNumDict Bool -> NonNumType Bool
 - TypeChar :: NonNumDict Char -> NonNumType Char
 - TypeCChar :: NonNumDict CChar -> NonNumType CChar
 - TypeCSChar :: NonNumDict CSChar -> NonNumType CSChar
 - TypeCUChar :: NonNumDict CUChar -> NonNumType CUChar
 
 - data  NumType a where
- IntegralNumType :: IntegralType a -> NumType a
 - FloatingNumType :: FloatingType a -> NumType a
 
 - data  BoundedType a where
- IntegralBoundedType :: IntegralType a -> BoundedType a
 - NonNumBoundedType :: NonNumType a -> BoundedType a
 
 - data  ScalarType a where
- NumScalarType :: NumType a -> ScalarType a
 - NonNumScalarType :: NonNumType a -> ScalarType a
 
 - class (IsScalar a, IsNum a, IsBounded a) => IsIntegral a  where
- integralType :: IntegralType a
 
 - class (Floating a, IsScalar a, IsNum a) => IsFloating a  where
- floatingType :: FloatingType a
 
 - class  IsNonNum a  where
- nonNumType :: NonNumType a
 
 - class (Num a, IsScalar a) => IsNum a where
 - class  IsBounded a  where
- boundedType :: BoundedType a
 
 - class Typeable a => IsScalar a  where
- scalarType :: ScalarType a
 
 - integralDict :: IntegralType a -> IntegralDict a
 - floatingDict :: FloatingType a -> FloatingDict a
 - nonNumDict :: NonNumType a -> NonNumDict a
 - data  TupleType a where
- UnitTuple :: TupleType ()
 - SingleTuple :: ScalarType a -> TupleType a
 - PairTuple :: TupleType a -> TupleType b -> TupleType (a, b)
 
 - data Boundary a
 
Documentation
module Data.Int
module Data.Word
module Foreign.C.Types
typeOf7Default :: (Typeable8 t, Typeable a) => t a b c d e f g h -> TypeRepSource
Instances
typeOf8Default :: (Typeable9 t, Typeable a) => t a b c d e f g h i -> TypeRepSource
data IntegralDict a whereSource
data FloatingDict a whereSource
Constructors
| FloatingDict :: (Enum a, Eq a, Ord a, Show a, Floating a, Fractional a, Num a, Real a, RealFrac a, RealFloat a, Storable a) => FloatingDict a | 
data NonNumDict a whereSource
Constructors
| NonNumDict :: (Bounded a, Enum a, Eq a, Ord a, Show a, Storable a) => NonNumDict a | 
data IntegralType a whereSource
Integral types supported in array computations.
Constructors
Instances
| Show (IntegralType a) | 
data FloatingType a whereSource
Floating-point types supported in array computations.
Constructors
Instances
| Show (FloatingType a) | 
data NonNumType a whereSource
Non-numeric types supported in array computations.
Constructors
| TypeBool :: NonNumDict Bool -> NonNumType Bool | |
| TypeChar :: NonNumDict Char -> NonNumType Char | |
| TypeCChar :: NonNumDict CChar -> NonNumType CChar | |
| TypeCSChar :: NonNumDict CSChar -> NonNumType CSChar | |
| TypeCUChar :: NonNumDict CUChar -> NonNumType CUChar | 
Instances
| Show (NonNumType a) | 
Numeric element types implement Num & Real
Constructors
| IntegralNumType :: IntegralType a -> NumType a | |
| FloatingNumType :: FloatingType a -> NumType a | 
data BoundedType a whereSource
Bounded element types implement Bounded
Constructors
| IntegralBoundedType :: IntegralType a -> BoundedType a | |
| NonNumBoundedType :: NonNumType a -> BoundedType a | 
Instances
| Show (BoundedType a) | 
data ScalarType a whereSource
All scalar element types implement Eq, Ord & Enum
Constructors
| NumScalarType :: NumType a -> ScalarType a | |
| NonNumScalarType :: NonNumType a -> ScalarType a | 
Instances
| Show (ScalarType a) | 
class (IsScalar a, IsNum a, IsBounded a) => IsIntegral a whereSource
Integral types
Methods
Instances
Non-numeric types
Methods
Bounded types
Methods
Instances
class Typeable a => IsScalar a whereSource
All scalar type
Methods
Instances
integralDict :: IntegralType a -> IntegralDict aSource
floatingDict :: FloatingType a -> FloatingDict aSource
nonNumDict :: NonNumType a -> NonNumDict aSource
Constructors
| UnitTuple :: TupleType () | |
| SingleTuple :: ScalarType a -> TupleType a | |
| PairTuple :: TupleType a -> TupleType b -> TupleType (a, b) |