imperative-edsl-0.4.1: 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

Types

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

Expressions

data Sym sig where Source

Syntactic symbols for C

Constructors

Fun :: Signature sig => String -> Denotation sig -> Sym sig 
UOp :: UnOp -> (a -> b) -> Sym (a :-> Full b) 
Op :: BinOp -> (a -> b -> c) -> Sym (a :-> (b :-> Full c)) 
Cast :: (a -> b) -> Sym (a :-> Full b) 
Cond :: Sym (Bool :-> (a :-> (a :-> Full a))) 
Var :: String -> Sym (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

viewLit :: CExp a -> Maybe a Source

Get the value of a literal expression

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

User interface

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

Create a named variable

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

Construct a literal expression

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

not_ :: CExp Bool -> CExp Bool Source

Boolean negation

(#==) :: (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