imperative-edsl-0.8: 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) 

data Sym sig where Source #

Syntactic symbols for C

Constructors

Lit :: String -> a -> Sym (Full a) 
Const :: String -> a -> Sym (Full a) 
Fun :: Signature sig => 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) 
WithCode :: SupportCode -> Sym (a :-> Full a) 
Instances
Equality Sym Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

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

hash :: Sym a -> Hash #

Render Sym Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

renderSym :: Sym sig -> String #

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

StringTree Sym Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

stringTreeSym :: [Tree String] -> Sym a -> Tree String #

Symbol Sym Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

symSig :: Sym sig -> SigRep sig #

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

data T sig where Source #

Constructors

T 

Fields

Instances
Equality T Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

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

hash :: T a -> Hash #

Render T Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

renderSym :: T sig -> String #

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

StringTree T Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

stringTreeSym :: [Tree String] -> T a -> Tree String #

Symbol T Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

symSig :: T sig -> SigRep sig #

newtype CExp a Source #

C expression

Constructors

CExp 

Fields

Instances
EvalExp CExp Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

evalExp :: CExp a -> a Source #

FreeExp CExp Source # 
Instance details

Defined in Language.Embedded.CExp

Associated Types

type FreePred CExp :: Type -> Constraint Source #

Methods

constExp :: FreePred CExp a => a -> CExp a Source #

varExp :: FreePred CExp a => VarId -> CExp a Source #

CompExp CExp Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

compExp :: MonadC m => CExp a -> m Exp Source #

Eq (CExp a) Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

(==) :: CExp a -> CExp a -> Bool #

(/=) :: CExp a -> CExp a -> Bool #

(Fractional a, Ord a, CType a) => Fractional (CExp a) Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

(/) :: CExp a -> CExp a -> CExp a #

recip :: CExp a -> CExp a #

fromRational :: Rational -> CExp a #

(Num a, Ord a, CType a) => Num (CExp a) Source # 
Instance details

Defined in Language.Embedded.CExp

Methods

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

(-) :: CExp a -> CExp a -> CExp a #

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

negate :: CExp a -> CExp a #

abs :: CExp a -> CExp a #

signum :: CExp a -> CExp a #

fromInteger :: Integer -> CExp a #

Syntactic (CExp a) Source # 
Instance details

Defined in Language.Embedded.CExp

Associated Types

type Domain (CExp a) :: Type -> Type #

type Internal (CExp a) :: Type #

Methods

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

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

type FreePred CExp Source # 
Instance details

Defined in Language.Embedded.CExp

type Internal (CExp a) Source # 
Instance details

Defined in Language.Embedded.CExp

type Internal (CExp a) = a
type Domain (CExp a) Source # 
Instance details

Defined in Language.Embedded.CExp

type Domain (CExp a) = T

evalSym :: Sym sig -> Denotation sig Source #

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 :: forall a. () => forall a1. (CType (DenResult (Full a)), Full a ~# Full a1) => a1 -> CExp a Source #

pattern LitP' :: forall sig. () => forall a. (CType (DenResult sig), sig ~# Full a) => a -> AST T sig Source #

pattern NonLitP :: forall a. CExp a Source #

pattern NonLitP' :: forall a. ASTF T a Source #

pattern OpP :: forall a. () => forall a1 a2 a3 b c. (CType (DenResult (a2 :-> (a1 :-> Full a))), (a2 :-> (a1 :-> Full a)) ~# (a3 :-> (b :-> Full c))) => Binary (a3 -> b -> c) -> AST T (Full a2) -> AST T (Full a1) -> CExp a Source #

pattern OpP' :: forall sig. () => forall a a1 a2 b c. (CType (DenResult (a1 :-> (a :-> sig))), (a1 :-> (a :-> sig)) ~# (a2 :-> (b :-> Full c))) => Binary (a2 -> b -> c) -> AST T (Full a1) -> AST T (Full a) -> AST T sig Source #

pattern UOpP :: forall a. () => forall a1 a2 b. (CType (DenResult (a1 :-> Full a)), (a1 :-> Full a) ~# (a2 :-> Full b)) => Unary (a2 -> b) -> AST T (Full a1) -> CExp a Source #

pattern UOpP' :: forall sig. () => forall a a1 b. (CType (DenResult (a :-> sig)), (a :-> sig) ~# (a1 :-> Full b)) => Unary (a1 -> b) -> AST T (Full a) -> AST T sig 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 
=> String

Name of constant

-> a

Value of constant

-> CExp a 

Predefined constant

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

Create a named variable

withCode :: CType a => (forall m. MonadC m => m ()) -> CExp a -> CExp a Source #

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

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