Safe Haskell | None |
---|---|
Language | Haskell2010 |
- toBlock :: Program () -> Block ()
- toProg :: Block () -> Program ()
- copyProg :: Maybe (Expression ()) -> [Expression ()] -> Program ()
- mkInitialize :: String -> Maybe (Expression ()) -> Expression () -> Program ()
- initArray :: Maybe (Expression ()) -> Expression () -> Program ()
- setLength :: Maybe (Expression ()) -> Expression () -> Program ()
- freeArray :: Variable () -> Program ()
- freeArrays :: [Declaration ()] -> [Program ()]
- arrayLength :: Expression () -> Expression ()
- chaseArray :: Expression t -> Maybe (Range Length)
- iVarInit :: Expression () -> Program ()
- iVarGet :: Expression () -> Expression () -> Program ()
- iVarPut :: Expression () -> Expression () -> Program ()
- iVarDestroy :: Variable () -> Program ()
- freeIVars :: [Declaration ()] -> [Program ()]
- spawn :: String -> [Variable ()] -> Program ()
- run :: String -> [Variable ()] -> Program ()
- intWidth :: Type -> Maybe Integer
- intSigned :: Type -> Maybe Bool
- litF :: Float -> Expression t
- litD :: Double -> Expression t
- litB :: Bool -> Expression ()
- litC :: Constant () -> Constant () -> Expression ()
- litI :: Type -> Integer -> Expression ()
- litI32 :: Integer -> Expression ()
- isArray :: Type -> Bool
- isNativeArray :: Type -> Bool
- isIVar :: Type -> Bool
- isPointer :: Type -> Bool
- isVarExpr :: Expression () -> Bool
- containsNativeArray :: Type -> Bool
- flattenStructs :: Type -> [(Expression () -> Expression (), Type)]
- hasReference :: Type -> Bool
- dVar :: Declaration () -> Variable ()
- vName :: Variable t -> String
- lName :: Expression t -> String
- varToExpr :: Variable t -> Expression t
- binop :: Type -> String -> Expression () -> Expression () -> Expression ()
- fun :: Type -> String -> [Expression ()] -> Expression ()
- fun' :: FunctionMode -> Type -> String -> [Expression ()] -> Expression ()
- call :: String -> [ActualParameter ()] -> Program ()
- for :: Bool -> String -> Expression () -> Expression () -> Block () -> Program ()
- while :: Block () -> Expression () -> Block () -> Program ()
Documentation
copyProg :: Maybe (Expression ()) -> [Expression ()] -> Program () Source
Copies expressions into a destination. If the destination is a non-scalar the arguments are appended to the destination.
mkInitialize :: String -> Maybe (Expression ()) -> Expression () -> Program () Source
initArray :: Maybe (Expression ()) -> Expression () -> Program () Source
setLength :: Maybe (Expression ()) -> Expression () -> Program () Source
freeArrays :: [Declaration ()] -> [Program ()] Source
arrayLength :: Expression () -> Expression () Source
chaseArray :: Expression t -> Maybe (Range Length) Source
iVarInit :: Expression () -> Program () Source
iVarGet :: Expression () -> Expression () -> Program () Source
iVarPut :: Expression () -> Expression () -> Program () Source
iVarDestroy :: Variable () -> Program () Source
freeIVars :: [Declaration ()] -> [Program ()] Source
litF :: Float -> Expression t Source
litD :: Double -> Expression t Source
litB :: Bool -> Expression () Source
litC :: Constant () -> Constant () -> Expression () Source
litI :: Type -> Integer -> Expression () Source
litI32 :: Integer -> Expression () Source
isNativeArray :: Type -> Bool Source
isVarExpr :: Expression () -> Bool Source
containsNativeArray :: Type -> Bool Source
flattenStructs :: Type -> [(Expression () -> Expression (), Type)] Source
Returns a list of access functions and types for the leaves of the struct tree of the type
hasReference :: Type -> Bool Source
dVar :: Declaration () -> Variable () Source
lName :: Expression t -> String Source
varToExpr :: Variable t -> Expression t Source
binop :: Type -> String -> Expression () -> Expression () -> Expression () Source
fun :: Type -> String -> [Expression ()] -> Expression () Source
fun' :: FunctionMode -> Type -> String -> [Expression ()] -> Expression () Source
call :: String -> [ActualParameter ()] -> Program () Source
for :: Bool -> String -> Expression () -> Expression () -> Block () -> Program () Source