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

Safe HaskellNone
LanguageHaskell2010

Language.Embedded.Imperative.Frontend.General

Description

Exports the general parts of imperative front ends. The motivation for this module is to support making specialized front ends (e.g. like Language.Embedded.Imperative.Frontend but for a specific instruction set). These exports are the parts of the front end that are independent of the instruction set and/or expression language.

Synopsis

Documentation

data Ref a Source #

Mutable reference

Instances

Eq (Ref a) Source # 

Methods

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

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

ToIdent (Ref a) Source # 

Methods

toIdent :: Ref a -> SrcLoc -> Id #

Assignable (Ref a) Source # 

data Arr i a Source #

Mutable array

Instances

Eq (Arr i a) Source # 

Methods

(==) :: Arr i a -> Arr i a -> Bool #

(/=) :: Arr i a -> Arr i a -> Bool #

ToIdent (Arr i a) Source # 

Methods

toIdent :: Arr i a -> SrcLoc -> Id #

Assignable (Arr i a) Source # 
IsPointer (Arr i a) Source # 

Methods

runSwapPtr :: Arr i a -> Arr i a -> IO () Source #

data IArr i a Source #

Immutable array

Instances

(Show a, Show i, Ix i) => Show (IArr i a) Source # 

Methods

showsPrec :: Int -> IArr i a -> ShowS #

show :: IArr i a -> String #

showList :: [IArr i a] -> ShowS #

ToIdent (IArr i a) Source # 

Methods

toIdent :: IArr i a -> SrcLoc -> Id #

Assignable (IArr i a) Source # 

data Border i Source #

Constructors

Incl i 
Excl i 

Instances

Functor Border Source # 

Methods

fmap :: (a -> b) -> Border a -> Border b #

(<$) :: a -> Border b -> Border a #

Foldable Border Source # 

Methods

fold :: Monoid m => Border m -> m #

foldMap :: Monoid m => (a -> m) -> Border a -> m #

foldr :: (a -> b -> b) -> b -> Border a -> b #

foldr' :: (a -> b -> b) -> b -> Border a -> b #

foldl :: (b -> a -> b) -> b -> Border a -> b #

foldl' :: (b -> a -> b) -> b -> Border a -> b #

foldr1 :: (a -> a -> a) -> Border a -> a #

foldl1 :: (a -> a -> a) -> Border a -> a #

toList :: Border a -> [a] #

null :: Border a -> Bool #

length :: Border a -> Int #

elem :: Eq a => a -> Border a -> Bool #

maximum :: Ord a => Border a -> a #

minimum :: Ord a => Border a -> a #

sum :: Num a => Border a -> a #

product :: Num a => Border a -> a #

Traversable Border Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Border a -> f (Border b) #

sequenceA :: Applicative f => Border (f a) -> f (Border a) #

mapM :: Monad m => (a -> m b) -> Border a -> m (Border b) #

sequence :: Monad m => Border (m a) -> m (Border a) #

Eq i => Eq (Border i) Source # 

Methods

(==) :: Border i -> Border i -> Bool #

(/=) :: Border i -> Border i -> Bool #

Num i => Num (Border i) Source #

fromInteger gives an inclusive border. No other methods defined.

Methods

(+) :: Border i -> Border i -> Border i #

(-) :: Border i -> Border i -> Border i #

(*) :: Border i -> Border i -> Border i #

negate :: Border i -> Border i #

abs :: Border i -> Border i #

signum :: Border i -> Border i #

fromInteger :: Integer -> Border i #

Show i => Show (Border i) Source # 

Methods

showsPrec :: Int -> Border i -> ShowS #

show :: Border i -> String #

showList :: [Border i] -> ShowS #

type IxRange i = (i, Int, Border i) Source #

Index range

(lo,step,hi)

lo gives the start index; step gives the step length; hi gives the stop index which may be inclusive or exclusive.

class ToIdent a => IsPointer a Source #

Types that are represented as a pointers in C

Minimal complete definition

runSwapPtr

Instances

IsPointer (Ptr a) Source # 

Methods

runSwapPtr :: Ptr a -> Ptr a -> IO () Source #

IsPointer (Arr i a) Source # 

Methods

runSwapPtr :: Arr i a -> Arr i a -> IO () Source #

data Handle Source #

File handle

Instances

stdin :: Handle Source #

Handle to stdin

stdout :: Handle Source #

Handle to stdout

data PrintfArg exp Source #

class (Typeable a, Read a, PrintfArg a) => Formattable a Source #

Values that can be printed/scanned using printf/scanf

Minimal complete definition

formatSpecPrint

Instances

Formattable Double Source # 
Formattable Float Source # 
Formattable Int Source # 
Formattable Int8 Source # 
Formattable Int16 Source # 
Formattable Int32 Source # 
Formattable Int64 Source # 
Formattable Word Source # 
Formattable Word8 Source # 
Formattable Word16 Source # 
Formattable Word32 Source # 
Formattable Word64 Source # 

data Ptr a Source #

Pointer

Instances

Eq (Ptr a) Source # 

Methods

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

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

Show (Ptr a) Source # 

Methods

showsPrec :: Int -> Ptr a -> ShowS #

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

ToIdent (Ptr a) Source # 

Methods

toIdent :: Ptr a -> SrcLoc -> Id #

Assignable (Ptr a) Source # 
IsPointer (Ptr a) Source # 

Methods

runSwapPtr :: Ptr a -> Ptr a -> IO () Source #

data Object Source #

Abstract object

data FunArg exp pred where Source #

Constructors

ValArg :: pred a => exp a -> FunArg exp pred 
AddrArg :: FunArg exp pred -> FunArg exp pred 
DerefArg :: FunArg exp pred -> FunArg exp pred 
OffsetArg :: FunArg exp pred -> exp i -> FunArg exp pred 
FunArg :: Arg arg pred => arg pred -> FunArg exp pred 

Instances

(CompExp exp, CompTypeClass ct) => Arg (* -> Constraint) (FunArg * exp) ct Source # 

Methods

mkArg :: ct pred -> CGen Exp Source #

mkParam :: ct pred -> CGen Param Source #

data Definition :: * #

Instances

Eq Definition 
Data Definition 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Definition -> c Definition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Definition #

toConstr :: Definition -> Constr #

dataTypeOf :: Definition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Definition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Definition) #

gmapT :: (forall b. Data b => b -> b) -> Definition -> Definition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Definition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Definition -> r #

gmapQ :: (forall d. Data d => d -> u) -> Definition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Definition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Definition -> m Definition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Definition -> m Definition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Definition -> m Definition #

Ord Definition 
Show Definition 
Located Definition 
Relocatable Definition 

Methods

reloc :: Loc -> Definition -> Definition #