Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type CodeWriter = RWS Readers Writers States
- data Readers = Readers {
- alias :: [(VarId, Expression ())]
- sourceInfo :: SourceInfo
- backendOpts :: Options
- initReader :: Options -> Readers
- data Writers = Writers {}
- data States = States {}
- initState :: States
- type Location = Maybe (Expression ())
- class Compile sub dom where
- compileProgSym :: sub a -> Info (DenResult a) -> Location -> Args (AST (Decor Info dom)) a -> CodeWriter ()
- compileExprSym :: sub a -> Info (DenResult a) -> Args (AST (Decor Info dom)) a -> CodeWriter (Expression ())
- compileExprLoc :: Compile sub dom => sub a -> Info (DenResult a) -> Location -> Args (AST (Decor Info dom)) a -> CodeWriter ()
- compileProgFresh :: Compile sub dom => sub a -> Info (DenResult a) -> Args (AST (Decor Info dom)) a -> CodeWriter (Expression ())
- compileDecor :: Info a -> CodeWriter b -> CodeWriter b
- compileProgDecor :: Compile dom dom => Location -> Decor Info dom a -> Args (AST (Decor Info dom)) a -> CodeWriter ()
- compileExprDecor :: Compile dom dom => Decor Info dom a -> Args (AST (Decor Info dom)) a -> CodeWriter (Expression ())
- compileProg :: Compile dom dom => Location -> ASTF (Decor Info dom) a -> CodeWriter ()
- compileExpr :: Compile dom dom => ASTF (Decor Info dom) a -> CodeWriter (Expression ())
- compileExprVar :: Compile dom dom => ASTF (Decor Info dom) a -> CodeWriter (Expression ())
- compileNumType :: Signedness a -> BitWidth n -> Type
- mkStructType :: [(String, Type)] -> Type
- compileTypeRep :: TypeRep a -> Size a -> Type
- mkVar :: Type -> VarId -> Expression ()
- mkNamedVar :: String -> Type -> VarId -> Variable ()
- mkNamedRef :: String -> Type -> VarId -> Variable ()
- mkRef :: Type -> VarId -> Expression ()
- mkVariable :: Type -> VarId -> Variable ()
- mkPointer :: Type -> VarId -> Variable ()
- freshId :: CodeWriter VarId
- freshVar :: String -> TypeRep a -> Size a -> CodeWriter (Expression ())
- freshAlias :: Expression () -> CodeWriter (Expression ())
- declare :: Expression () -> CodeWriter ()
- declareAlias :: Expression () -> CodeWriter ()
- initialize :: Expression () -> Expression () -> CodeWriter ()
- tellDef :: [Entity ()] -> CodeWriter ()
- tellProg :: [Program ()] -> CodeWriter ()
- tellDeclWith :: Bool -> [Declaration ()] -> CodeWriter ()
- encodeType :: Type -> String
- getTypes :: Options -> [Declaration ()] -> [Entity ()]
- assign :: Location -> Expression () -> CodeWriter ()
- shallowAssign :: Location -> Expression () -> CodeWriter ()
- freshAliasInit :: Expression () -> CodeWriter (Expression ())
- shallowCopyWithRefSwap :: Expression () -> Expression () -> CodeWriter ()
- shallowCopyReferences :: Expression () -> Expression () -> CodeWriter ()
- mkDoubleBufferState :: Expression () -> VarId -> CodeWriter (Expression (), Expression ())
- confiscateBlock :: CodeWriter a -> CodeWriter (a, Block ())
- confiscateBigBlock :: CodeWriter a -> CodeWriter ((a, Writers), Block ())
- withAlias :: VarId -> Expression () -> CodeWriter a -> CodeWriter a
- isVariableOrLiteral :: (Project (Variable :|| Type) dom, Project (Literal :|| Type) dom) => AST (Decor info dom) a -> Bool
- mkLength :: (Project (Literal :|| Type) dom, Project (Variable :|| Type) dom, Compile dom dom) => ASTF (Decor Info dom) a -> TypeRep a -> Size a -> CodeWriter (Expression ())
- mkBranch :: Compile dom dom => Location -> ASTF (Decor Info dom) Bool -> ASTF (Decor Info dom) a -> Maybe (ASTF (Decor Info dom) a) -> CodeWriter ()
- isComposite :: Type -> Bool
Documentation
Readers | |
|
initReader :: Options -> Readers Source
type Location = Maybe (Expression ()) Source
Where to place the program result
class Compile sub dom where Source
A minimal complete instance has to define either compileProgSym
or
compileExprSym
.
Nothing
compileProgSym :: sub a -> Info (DenResult a) -> Location -> Args (AST (Decor Info dom)) a -> CodeWriter () Source
compileExprSym :: sub a -> Info (DenResult a) -> Args (AST (Decor Info dom)) a -> CodeWriter (Expression ()) Source
compileExprLoc :: Compile sub dom => sub a -> Info (DenResult a) -> Location -> Args (AST (Decor Info dom)) a -> CodeWriter () Source
Implementation of compileExprSym
that assigns an expression to the given
location.
compileProgFresh :: Compile sub dom => sub a -> Info (DenResult a) -> Args (AST (Decor Info dom)) a -> CodeWriter (Expression ()) Source
Implementation of compileProgSym
that generates code into a fresh
variable.
compileDecor :: Info a -> CodeWriter b -> CodeWriter b Source
compileProgDecor :: Compile dom dom => Location -> Decor Info dom a -> Args (AST (Decor Info dom)) a -> CodeWriter () Source
compileExprDecor :: Compile dom dom => Decor Info dom a -> Args (AST (Decor Info dom)) a -> CodeWriter (Expression ()) Source
compileProg :: Compile dom dom => Location -> ASTF (Decor Info dom) a -> CodeWriter () Source
compileExpr :: Compile dom dom => ASTF (Decor Info dom) a -> CodeWriter (Expression ()) Source
compileExprVar :: Compile dom dom => ASTF (Decor Info dom) a -> CodeWriter (Expression ()) Source
Utility functions
compileNumType :: Signedness a -> BitWidth n -> Type Source
mkStructType :: [(String, Type)] -> Type Source
compileTypeRep :: TypeRep a -> Size a -> Type Source
mkVar :: Type -> VarId -> Expression () Source
Construct a variable.
mkRef :: Type -> VarId -> Expression () Source
Construct a pointer.
mkVariable :: Type -> VarId -> Variable () Source
freshVar :: String -> TypeRep a -> Size a -> CodeWriter (Expression ()) Source
freshAlias :: Expression () -> CodeWriter (Expression ()) Source
declare :: Expression () -> CodeWriter () Source
declareAlias :: Expression () -> CodeWriter () Source
initialize :: Expression () -> Expression () -> CodeWriter () Source
tellDef :: [Entity ()] -> CodeWriter () Source
tellProg :: [Program ()] -> CodeWriter () Source
tellDeclWith :: Bool -> [Declaration ()] -> CodeWriter () Source
encodeType :: Type -> String Source
getTypes :: Options -> [Declaration ()] -> [Entity ()] Source
assign :: Location -> Expression () -> CodeWriter () Source
shallowAssign :: Location -> Expression () -> CodeWriter () Source
freshAliasInit :: Expression () -> CodeWriter (Expression ()) Source
shallowCopyWithRefSwap :: Expression () -> Expression () -> CodeWriter () Source
shallowCopyReferences :: Expression () -> Expression () -> CodeWriter () Source
mkDoubleBufferState :: Expression () -> VarId -> CodeWriter (Expression (), Expression ()) Source
confiscateBlock :: CodeWriter a -> CodeWriter (a, Block ()) Source
Like listen
, but also prevents the program from being written in the
monad.
confiscateBigBlock :: CodeWriter a -> CodeWriter ((a, Writers), Block ()) Source
Like listen
, but also catches writer things and prevents the program
from being written in the monad.
withAlias :: VarId -> Expression () -> CodeWriter a -> CodeWriter a Source
isVariableOrLiteral :: (Project (Variable :|| Type) dom, Project (Literal :|| Type) dom) => AST (Decor info dom) a -> Bool Source
mkLength :: (Project (Literal :|| Type) dom, Project (Variable :|| Type) dom, Compile dom dom) => ASTF (Decor Info dom) a -> TypeRep a -> Size a -> CodeWriter (Expression ()) Source
mkBranch :: Compile dom dom => Location -> ASTF (Decor Info dom) Bool -> ASTF (Decor Info dom) a -> Maybe (ASTF (Decor Info dom) a) -> CodeWriter () Source
isComposite :: Type -> Bool Source