| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Ivory.Language.Syntax.Concrete.ParseAST
- type FnSym = String
- type Var = String
- type RefVar = String
- type IxVar = String
- type TypeVar = String
- type FieldNm = String
- type MacroVar = String
- data GlobalSym
- data IncludeDef = IncludeDef {
- inclModule :: String
- inclDefLoc :: SrcLoc
- data Extern = Extern {
- externSym :: String
- externFile :: String
- externType :: Type
- externLoc :: SrcLoc
- data ConstDef = ConstDef {}
- data TypeDef = TypeDef {}
- data ProcDef = ProcDef {}
- data IncludeProc = IncludeProc {
- procInclTy :: Type
- procInclSym :: FnSym
- procInclArgs :: [(Type, Var)]
- procIncl :: (String, FnSym)
- procInclLoc :: SrcLoc
- data PrePost
- data Type
- data Scope
- data IntSize
- data WordSize
- data Literal
- data Exp
- data ExpOp
- = EqOp
- | NeqOp
- | CondOp
- | GtOp Bool
- | LtOp Bool
- | NotOp
- | AndOp
- | OrOp
- | MulOp
- | AddOp
- | SubOp
- | NegateOp
- | AbsOp
- | SignumOp
- | DivOp
- | EucDivOp
- | ModOp
- | FExpOp
- | FSqrtOp
- | FLogOp
- | FPowOp
- | FSinOp
- | FTanOp
- | FCosOp
- | FAsinOp
- | FAtanOp
- | FAtan2Op
- | FAcosOp
- | FSinhOp
- | FTanhOp
- | FCoshOp
- | FAsinhOp
- | FAtanhOp
- | FAcoshOp
- | IsNanOp
- | IsInfOp
- | RoundFOp
- | CeilFOp
- | FloorFOp
- | BitAndOp
- | BitOrOp
- | BitXorOp
- | BitComplementOp
- | BitShiftLOp
- | BitShiftROp
- | ConstRefOp
- | SafeCast
- | BitCast
- | CastWith
- | TwosCompCast
- | TwosCompRep
- | ToIx
- | FromIx
- | IxSize
- | ArrayLen
- | SizeOf
- | NullPtr
- | RefToPtr
- | ToCArray
- data StructInit
- data AllocRef
- = AllocBase RefVar (Maybe Exp)
- | AllocArr RefVar [Exp]
- | AllocStruct RefVar StructInit
- data Stmt
- = IfTE Exp [Stmt] [Stmt]
- | Assert Exp
- | Assume Exp
- | Return Exp
- | ReturnVoid
- | Store Exp Exp
- | Assign Var Exp (Maybe Type)
- | NoBindCall Var [Exp]
- | RefCopy Exp Exp
- | AllocRef AllocRef
- | MapArr IxVar [Stmt]
- | UpTo Exp IxVar [Stmt]
- | UpFromTo Exp Exp IxVar [Stmt]
- | DownFrom Exp IxVar [Stmt]
- | DownFromTo Exp Exp IxVar [Stmt]
- | Forever [Stmt]
- | IvoryMacroStmt (Maybe Var) (String, [Exp])
- | Break
- | LocStmt (Located Stmt)
- data StructDef
- structSym :: StructDef -> String
- ivoryStringStructName :: String -> String
- data Field = Field {}
- data BitDataDef = BitDataDef {}
- data BitTy
- data Constr = Constr {
- constrName :: String
- constrFields :: [BitField]
- constrLayout :: [LayoutItem]
- constrLoc :: SrcLoc
- data LayoutItem
- data BitLiteral
- = BitLitKnown { }
- | BitLitUnknown { }
- data BitField = BitField {}
Documentation
data IncludeDef Source
Constructors
| IncludeDef | |
Fields
| |
Constructors
| Extern | |
Fields
| |
Constructors
| ConstDef | |
Constructors
| ProcDef | |
data IncludeProc Source
We distinguish the name used from the name imported so the same symbol can
be used twice at different types. (E.g., printf).
Constructors
| IncludeProc | |
Fields
| |
Constructors
| TyVoid | Unit type |
| TyInt IntSize | Signed ints |
| TyWord WordSize | Unsigned ints |
| TyBool | Booleans |
| TyChar | Characters |
| TyFloat | Floats |
| TyDouble | Doubles XXX | TyPtr Type -- ^ Pointers |
| TyIx Integer | Index type |
| TyString | Static strings |
| TyStored Type | References |
| TyStruct String | Structures |
| TyArray Type (Either String Integer) | Arrays of fixed length (can be a macro or integer) |
| TyRef Scope Type | References |
| TyConstRef Scope Type | Constant References |
| TySynonym String | Type synonym |
| LocTy (Located Type) |
Constructors
data StructInit Source
Constructors
| AllocBase RefVar (Maybe Exp) | |
| AllocArr RefVar [Exp] | |
| AllocStruct RefVar StructInit |
AST for parsing C-like statements.
Constructors
| IfTE Exp [Stmt] [Stmt] | |
| Assert Exp | |
| Assume Exp | |
| Return Exp | |
| ReturnVoid | |
| Store Exp Exp | |
| Assign Var Exp (Maybe Type) | |
| NoBindCall Var [Exp] | |
| RefCopy Exp Exp | |
| AllocRef AllocRef | |
| MapArr IxVar [Stmt] | |
| UpTo Exp IxVar [Stmt] | |
| UpFromTo Exp Exp IxVar [Stmt] | |
| DownFrom Exp IxVar [Stmt] | |
| DownFromTo Exp Exp IxVar [Stmt] | |
| Forever [Stmt] | |
| IvoryMacroStmt (Maybe Var) (String, [Exp]) | |
| Break | |
| LocStmt (Located Stmt) |
Basic type representation allowed in bit definitions.
A constructor definition within a "bitdata".
Constructors
| Constr | |
Fields
| |
data LayoutItem Source
One element of a bit data constructor layout.
Constructors
| LayoutConst BitLiteral | |
| LayoutField String |
Instances
data BitLiteral Source
A bit integer literal with a known or unknown size.
Constructors
| BitLitKnown | |
| BitLitUnknown | |
Instances
A record-like field defined within a "bitdata" constructor. If the name is
an underscore, we name it with Nothing.
Constructors
| BitField | |
Fields
| |