raw-feldspar-0.1: Resource-Aware Feldspar

Safe HaskellNone
LanguageHaskell2010

Feldspar.Primitive.Representation

Contents

Description

Primitive Feldspar expressions

Synopsis

Types

data PrimTypeView a where Source #

A different view of PrimTypeRep that allows matching on similar types

class (Eq a, Show a, Typeable a) => PrimType' a where Source #

Primitive supported types

Minimal complete definition

primTypeRep

Methods

primTypeRep :: PrimTypeRep a Source #

Reify a primitive type

Instances

PrimType' Bool Source # 
PrimType' Double Source # 
PrimType' Float Source # 
PrimType' Int8 Source # 
PrimType' Int16 Source # 
PrimType' Int32 Source # 
PrimType' Int64 Source # 
PrimType' Word8 Source # 
PrimType' Word16 Source # 
PrimType' Word32 Source # 
PrimType' Word64 Source # 
PrimType' (Complex Double) Source # 
PrimType' (Complex Float) Source # 
InterpBi (* -> Constraint, *) * (AssertCMD (* -> *) (* -> Constraint)) IO (Param1 (* -> Constraint) PrimType') # 

Methods

interpBi :: Param1 (* -> Constraint) PrimType' ((IO -> *, (IO -> *, AssertCMD (* -> *) (* -> Constraint))) m ((IO -> *, AssertCMD (* -> *) (* -> Constraint)) m fs)) a -> m a #

Syntactic (Struct PrimType' Data a) # 
type Internal (Struct PrimType' Data a) # 
type Domain (Struct PrimType' Data a) # 

primTypeOf :: PrimType' a => a -> PrimTypeRep a Source #

Convenience function; like primTypeRep but with an extra argument to constrain the type parameter. The extra argument is ignored.

primTypeEq :: PrimTypeRep a -> PrimTypeRep b -> Maybe (Dict (a ~ b)) Source #

Check whether two type representations are equal

witPrimType :: PrimTypeRep a -> Dict (PrimType' a) Source #

Reflect a PrimTypeRep to a PrimType' constraint

Expressions

data Primitive sig where Source #

Primitive operations

Constructors

FreeVar :: PrimType' a => String -> Primitive (Full a) 
Lit :: (Eq a, Show a) => a -> Primitive (Full a) 
Add :: (Num a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
Sub :: (Num a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
Mul :: (Num a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
Neg :: (Num a, PrimType' a) => Primitive (a :-> Full a) 
Abs :: (Num a, PrimType' a) => Primitive (a :-> Full a) 
Sign :: (Num a, PrimType' a) => Primitive (a :-> Full a) 
Quot :: (Integral a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
Rem :: (Integral a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
Div :: (Integral a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
Mod :: (Integral a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
FDiv :: (Fractional a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
Pi :: (Floating a, PrimType' a) => Primitive (Full a) 
Exp :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Log :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Sqrt :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Pow :: (Floating a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
Sin :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Cos :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Tan :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Asin :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Acos :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Atan :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Sinh :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Cosh :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Tanh :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Asinh :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Acosh :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Atanh :: (Floating a, PrimType' a) => Primitive (a :-> Full a) 
Complex :: (Num a, PrimType' a, PrimType' (Complex a)) => Primitive (a :-> (a :-> Full (Complex a))) 
Polar :: (Floating a, PrimType' a, PrimType' (Complex a)) => Primitive (a :-> (a :-> Full (Complex a))) 
Real :: (PrimType' a, PrimType' (Complex a)) => Primitive (Complex a :-> Full a) 
Imag :: (PrimType' a, PrimType' (Complex a)) => Primitive (Complex a :-> Full a) 
Magnitude :: (RealFloat a, PrimType' a, PrimType' (Complex a)) => Primitive (Complex a :-> Full a) 
Phase :: (RealFloat a, PrimType' a, PrimType' (Complex a)) => Primitive (Complex a :-> Full a) 
Conjugate :: (Num a, PrimType' (Complex a)) => Primitive (Complex a :-> Full (Complex a)) 
I2N :: (Integral a, Num b, PrimType' a, PrimType' b) => Primitive (a :-> Full b) 
I2B :: (Integral a, PrimType' a) => Primitive (a :-> Full Bool) 
B2I :: (Integral a, PrimType' a) => Primitive (Bool :-> Full a) 
Round :: (RealFrac a, Num b, PrimType' a, PrimType' b) => Primitive (a :-> Full b) 
Not :: Primitive (Bool :-> Full Bool) 
And :: Primitive (Bool :-> (Bool :-> Full Bool)) 
Or :: Primitive (Bool :-> (Bool :-> Full Bool)) 
Eq :: (Eq a, PrimType' a) => Primitive (a :-> (a :-> Full Bool)) 
NEq :: (Eq a, PrimType' a) => Primitive (a :-> (a :-> Full Bool)) 
Lt :: (Ord a, PrimType' a) => Primitive (a :-> (a :-> Full Bool)) 
Gt :: (Ord a, PrimType' a) => Primitive (a :-> (a :-> Full Bool)) 
Le :: (Ord a, PrimType' a) => Primitive (a :-> (a :-> Full Bool)) 
Ge :: (Ord a, PrimType' a) => Primitive (a :-> (a :-> Full Bool)) 
BitAnd :: (Bits a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
BitOr :: (Bits a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
BitXor :: (Bits a, PrimType' a) => Primitive (a :-> (a :-> Full a)) 
BitCompl :: (Bits a, PrimType' a) => Primitive (a :-> Full a) 
ShiftL :: (Bits a, PrimType' a, Integral b, PrimType' b) => Primitive (a :-> (b :-> Full a)) 
ShiftR :: (Bits a, PrimType' a, Integral b, PrimType' b) => Primitive (a :-> (b :-> Full a)) 
ArrIx :: PrimType' a => IArr Index a -> Primitive (Index :-> Full a) 
Cond :: Primitive (Bool :-> (a :-> (a :-> Full a))) 

Instances

Eval Primitive Source # 

Methods

evalSym :: Primitive sig -> Denotation sig #

Equality Primitive Source # 

Methods

equal :: Primitive a -> Primitive b -> Bool #

hash :: Primitive a -> Hash #

Render Primitive Source # 

Methods

renderSym :: Primitive sig -> String #

renderArgs :: [String] -> Primitive sig -> String #

StringTree Primitive Source # 
Symbol Primitive Source # 

Methods

symSig :: Primitive sig -> SigRep sig #

EvalEnv Primitive env Source #

Assumes no occurrences of FreeVar and concrete representation of arrays

Methods

compileSym :: proxy env -> Primitive sig -> DenotationM (Reader env) sig #

Show (Primitive a) Source # 

newtype Prim a Source #

Primitive expressions

Constructors

Prim 

Fields

Instances

FreeExp Prim Source # 

Associated Types

type FreePred (Prim :: * -> *) :: * -> Constraint #

Methods

constExp :: FreePred Prim a => a -> Prim a #

varExp :: FreePred Prim a => VarId -> Prim a #

EvalExp Prim Source # 

Methods

evalExp :: Prim a -> a #

(Num a, PrimType' a) => Num (Prim a) Source # 

Methods

(+) :: Prim a -> Prim a -> Prim a #

(-) :: Prim a -> Prim a -> Prim a #

(*) :: Prim a -> Prim a -> Prim a #

negate :: Prim a -> Prim a #

abs :: Prim a -> Prim a #

signum :: Prim a -> Prim a #

fromInteger :: Integer -> Prim a #

Syntactic (Prim a) Source # 

Associated Types

type Domain (Prim a) :: * -> * #

type Internal (Prim a) :: * #

Methods

desugar :: Prim a -> ASTF (Domain (Prim a)) (Internal (Prim a)) #

sugar :: ASTF (Domain (Prim a)) (Internal (Prim a)) -> Prim a #

type FreePred Prim Source # 
type Internal (Prim a) Source # 
type Internal (Prim a) = a
type Domain (Prim a) Source # 

evalPrim :: Prim a -> a Source #

Evaluate a closed expression

sugarSymPrim :: (Signature sig, fi ~ SmartFun dom sig, sig ~ SmartSig fi, dom ~ SmartSym fi, dom ~ PrimDomain, SyntacticN f fi, sub :<: Primitive, PrimType' (DenResult sig)) => sub sig -> f Source #

Interface