module DDC.Core.Flow.Procedure
( Procedure (..)
, Nest (..)
, Context (..)
, StmtStart (..)
, StmtBody (..)
, StmtEnd (..))
where
import DDC.Core.Flow.Exp
import DDC.Core.Flow.Prim
import DDC.Core.Flow.Context
import Data.Monoid
data Procedure
= Procedure
{ procedureName :: Name
, procedureParamTypes :: [BindF]
, procedureParamValues :: [BindF]
, procedureNest :: Nest }
data Nest
= NestEmpty
| NestList
{ nestList :: [Nest]}
| NestLoop
{ nestRate :: Type Name
, nestStart :: [StmtStart]
, nestBody :: [StmtBody]
, nestInner :: Nest
, nestEnd :: [StmtEnd]
, nestResult :: Exp () Name }
| NestGuard
{ nestOuterRate :: Type Name
, nestInnerRate :: Type Name
, nestFlags :: Bound Name
, nestBody :: [StmtBody]
, nestInner :: Nest }
| NestSegment
{ nestOuterRate :: Type Name
, nestInnerRate :: Type Name
, nestLength :: Bound Name
, nestBody :: [StmtBody]
, nestInner :: Nest }
deriving Show
instance Monoid Nest where
mempty = NestEmpty
mappend n1 n2
= case (n1, n2) of
(NestEmpty, _) -> n2
(_, NestEmpty) -> n1
(NestList ns1, NestList ns2) -> NestList (ns1 ++ ns2)
(NestList ns1, _) -> NestList (ns1 ++ [n2])
(_, NestList ns2) -> NestList (n1 : ns2)
(_, _) -> NestList [n1, n2]
data StmtStart
= StartStmt
{ startResultBind :: Bind Name
, startExpression :: Exp () Name }
| StartVecNew
{ startVecNewName :: Name
, startVecNewElemType :: Type Name
, startVecNewRate :: Type Name }
| StartAcc
{ startAccName :: Name
, startAccType :: Type Name
, startAccExp :: Exp () Name }
deriving Show
data StmtBody
= BodyStmt
{
bodyResultBind :: Bind Name
, bodyExpression :: Exp () Name }
| BodyVecWrite
{
bodyVecName :: Name
, bodyVecWriteElemType :: Type Name
, bodyVecWriteIx :: Exp () Name
, bodyVecWriteVal :: Exp () Name
}
| BodyAccRead
{
bodyAccName :: Name
, bodyAccType :: Type Name
, bodyAccNameBind :: Bind Name
}
| BodyAccWrite
{
bodyAccName :: Name
, bodyAccType :: Type Name
, bodyAccExp :: Exp () Name }
deriving Show
data StmtEnd
= EndStmt
{ endBind :: Bind Name
, endExp :: Exp () Name }
| EndAcc
{ endName :: Name
, endType :: Type Name
, endAccName :: Name }
| EndVecTrunc
{ endVecName :: Name
, endVecType :: Type Name
, endVecRate :: Type Name }
deriving Show