imperative-edsl-0.5: Deep embedding of imperative programs with code generation

Safe HaskellNone
LanguageHaskell2010

Language.Embedded.CExp

Contents

Description

Typed deep embedding of simple C expressions

This is a subset of C expressions that only have simple non-compound and non-pointed types, and that don't contain any control structures.

(Of course, nothing stops one from translating CExp to something other than C, but its constructors and set of supported types is inspired by C.)

Synopsis

Expressions

data Unary a where Source

Constructors

UnNeg :: Num a => Unary (a -> a) 
UnNot :: Unary (Bool -> Bool) 

data Binary a where Source

Constructors

BiAdd :: Num a => Binary (a -> a -> a) 
BiSub :: Num a => Binary (a -> a -> a) 
BiMul :: Num a => Binary (a -> a -> a) 
BiDiv :: Fractional a => Binary (a -> a -> a) 
BiQuot :: Integral a => Binary (a -> a -> a) 
BiRem :: Integral a => Binary (a -> a -> a) 
BiAnd :: Binary (Bool -> Bool -> Bool) 
BiOr :: Binary (Bool -> Bool -> Bool) 
BiEq :: CType a => Binary (a -> a -> Bool) 
BiNEq :: CType a => Binary (a -> a -> Bool) 
BiLt :: (Ord a, CType a) => Binary (a -> a -> Bool) 
BiGt :: (Ord a, CType a) => Binary (a -> a -> Bool) 
BiLe :: (Ord a, CType a) => Binary (a -> a -> Bool) 
BiGe :: (Ord a, CType a) => Binary (a -> a -> Bool) 

type SupportCode = forall m. MonadC m => m () Source

data Sym sig where Source

Syntactic symbols for C

Constructors

Lit :: String -> a -> Sym (Full a) 
Const :: SupportCode -> String -> a -> Sym (Full a) 
Fun :: Signature sig => SupportCode -> String -> Denotation sig -> Sym sig 
UOp :: Unary (a -> b) -> Sym (a :-> Full b) 
Op :: Binary (a -> b -> c) -> Sym (a :-> (b :-> Full c)) 
Cast :: (a -> b) -> Sym (a :-> Full b) 
Cond :: Sym (Bool :-> (a :-> (a :-> Full a))) 
Var :: VarId -> Sym (Full a) 
ArrIx :: (Integral i, Ix i) => IArr i a -> Sym (i :-> Full a) 

data T sig where Source

Constructors

T :: CType (DenResult sig) => Sym sig -> T sig 

Fields

unT :: Sym sig
 

newtype CExp a Source

C expression

Constructors

CExp 

Fields

unCExp :: ASTF T a
 

evalCExp :: CExp a -> a Source

Evaluate an expression

compCExp :: forall m a. MonadC m => CExp a -> m Exp Source

Compile an expression

constFold :: CExp a -> CExp a Source

One-level constant folding: if all immediate sub-expressions are literals, the expression is reduced to a single literal

castAST :: forall a b. Typeable b => ASTF T a -> Maybe (ASTF T b) Source

viewLit :: CExp a -> Maybe a Source

Get the value of a literal expression

pattern LitP :: (CType (DenResult (Full t)), (~) * (Full t) (Full a)) => a -> CExp t Source

pattern LitP' :: (CType (DenResult t), (~) * t (Full a)) => a -> AST T t Source

pattern NonLitP :: CExp a Source

pattern NonLitP' :: ASTF T a Source

pattern OpP :: (CType (DenResult ((:->) a ((:->) a (Full t)))), (~) * ((:->) a ((:->) a (Full t))) ((:->) a ((:->) b (Full c)))) => Binary (a -> b -> c) -> AST T (Full a) -> AST T (Full a) -> CExp t Source

pattern OpP' :: (CType (DenResult ((:->) a ((:->) a t))), (~) * ((:->) a ((:->) a t)) ((:->) a ((:->) b (Full c)))) => Binary (a -> b -> c) -> AST T (Full a) -> AST T (Full a) -> AST T t Source

pattern UOpP :: (CType (DenResult ((:->) a (Full t))), (~) * ((:->) a (Full t)) ((:->) a (Full b))) => Unary (a -> b) -> AST T (Full a) -> CExp t Source

pattern UOpP' :: (CType (DenResult ((:->) a t)), (~) * ((:->) a t) ((:->) a (Full b))) => Unary (a -> b) -> AST T (Full a) -> AST T t Source

isFloat :: forall a. CType a => CExp a -> Bool Source

Return whether the type of the expression is a floating-point numeric type

isExact :: CType a => CExp a -> Bool Source

Return whether the type of the expression is a non-floating-point type

isExact' :: CType a => ASTF T a -> Bool Source

Return whether the type of the expression is a non-floating-point type

User interface

value :: CType a => a -> CExp a Source

Construct a literal expression

constant Source

Arguments

:: CType a 
=> SupportCode

Supporting C code

-> String

Name of constant

-> a

Value of constant

-> CExp a 

Predefined constant

variable :: CType a => VarId -> CExp a Source

Create a named variable

quot_ :: (Integral a, CType a) => CExp a -> CExp a -> CExp a Source

Integer division truncated toward zero

(#%) :: (Integral a, CType a) => CExp a -> CExp a -> CExp a Source

Integer remainder satisfying

(x `quot_` y)*y + (x #% y) == x

round_ :: (RealFrac a, Integral b, CType b) => CExp a -> CExp b Source

i2n :: (Integral a, Num b, CType b) => CExp a -> CExp b Source

Integral type casting

i2b :: Integral a => CExp a -> CExp Bool Source

Cast integer to Bool

b2i :: (Integral a, CType a) => CExp Bool -> CExp a Source

Cast Bool to integer

not_ :: CExp Bool -> CExp Bool Source

Boolean negation

(#&&) :: CExp Bool -> CExp Bool -> CExp Bool Source

Logical and

(#||) :: CExp Bool -> CExp Bool -> CExp Bool Source

Logical or

(#==) :: (Eq a, CType a) => CExp a -> CExp a -> CExp Bool infix 4 Source

Equality

(#!=) :: (Eq a, CType a) => CExp a -> CExp a -> CExp Bool infix 4 Source

In-equality

(#<) :: (Ord a, CType a) => CExp a -> CExp a -> CExp Bool infix 4 Source

(#>) :: (Ord a, CType a) => CExp a -> CExp a -> CExp Bool infix 4 Source

(#<=) :: (Ord a, CType a) => CExp a -> CExp a -> CExp Bool infix 4 Source

(#>=) :: (Ord a, CType a) => CExp a -> CExp a -> CExp Bool infix 4 Source

cond Source

Arguments

:: CType a 
=> CExp Bool

Condition

-> CExp a

True branch

-> CExp a

False branch

-> CExp a 

Conditional expression

(?) infixl 1 Source

Arguments

:: CType a 
=> CExp Bool

Condition

-> CExp a

True branch

-> CExp a

False branch

-> CExp a 

Condition operator; use as follows:

cond1 ? a $
cond2 ? b $
cond3 ? c $
        default

(#!) :: (CType a, Integral i, Ix i) => IArr i a -> CExp i -> CExp a Source

Array indexing