Safe Haskell | None |
---|---|
Language | Haskell2010 |
- decl :: CDeclSpec -> CDeclr -> Maybe CExpr -> CDecl
- voidSpec :: CTypeSpec
- charSpec :: CTypeSpec
- shortSpec :: CTypeSpec
- intSpec :: CTypeSpec
- longSpec :: CTypeSpec
- floatSpec :: CTypeSpec
- doubleSpec :: CTypeSpec
- voidTy :: CDeclSpec
- charTy :: CDeclSpec
- shortTy :: CDeclSpec
- intTy :: CDeclSpec
- longTy :: CDeclSpec
- floatTy :: CDeclSpec
- doubleTy :: CDeclSpec
- ty :: Ident -> CTypeSpec
- ptr :: CDeclr -> CDeclr
- char :: CDeclr -> Maybe CExpr -> CDecl
- short :: CDeclr -> Maybe CExpr -> CDecl
- int :: CDeclr -> Maybe CExpr -> CDecl
- long :: CDeclr -> Maybe CExpr -> CDecl
- float :: CDeclr -> Maybe CExpr -> CDecl
- double :: CDeclr -> Maybe CExpr -> CDecl
- charPtr :: CDeclr -> Maybe CExpr -> CDecl
- shortPtr :: CDeclr -> Maybe CExpr -> CDecl
- intPtr :: CDeclr -> Maybe CExpr -> CDecl
- longPtr :: CDeclr -> Maybe CExpr -> CDecl
- floatPtr :: CDeclr -> Maybe CExpr -> CDecl
- doublePtr :: CDeclr -> Maybe CExpr -> CDecl
- (.=) :: (Maybe CExpr -> CDecl) -> CExpr -> CDecl
- uninit :: (Maybe CExpr -> CDecl) -> CDecl
- csu :: CStructTag -> String -> [(String, CTypeSpec)] -> CDecl
- struct :: String -> [(String, CTypeSpec)] -> CDecl
- union :: String -> [(String, CTypeSpec)] -> CDecl
- fun :: [CDeclSpec] -> String -> [Maybe CExpr -> CDecl] -> CStat -> CFunDef
- annotatedFun :: [CDeclSpec] -> String -> [Maybe CExpr -> CDecl] -> [String] -> CStat -> CFunDef
- class External a where
- transUnit :: [CExtDecl] -> CTranslUnit
Documentation
:: CDeclSpec | The declaration specifier, usually this is a type |
-> CDeclr | Equivalent to the name of the object being declared. Often this will
make use of the overloaded string instance for |
-> Maybe CExpr | The optional init expression |
-> CDecl |
A low level way to declare something.
doubleSpec :: CTypeSpec Source
The CTypeSpec
for double
ty :: Ident -> CTypeSpec Source
Turns a string into the corresponding typedefed type.
For example
struct "foo" [("bar, ty "quux")]
will generate the corresponding
typedef foo {quux bar;} foo
ptr :: CDeclr -> CDeclr Source
Modifies a declarator to be a pointer. For example
ptr someName
would be *x
in C.
char :: CDeclr -> Maybe CExpr -> CDecl Source
A short cut for declaring a char
.
char "x" .= 1 uninit $ char "y"
Would generate
char x = 1; char y;
(.=) :: (Maybe CExpr -> CDecl) -> CExpr -> CDecl infixl 7 Source
Supplies an initializer for an for a declaration. This
is meant to be used with the char
and friends short cuts
uninit :: (Maybe CExpr -> CDecl) -> CDecl Source
Leave a declaration uninitialized. This is meant to be used
with the char
and friends declaration
struct :: String -> [(String, CTypeSpec)] -> CDecl Source
Create a structure, for example struct "foo" [("bar", intTy)]
is
typedef struct foo {int bar;} foo;
union :: String -> [(String, CTypeSpec)] -> CDecl Source
Equivalent to struct
but generates a C union instead.
fun :: [CDeclSpec] -> String -> [Maybe CExpr -> CDecl] -> CStat -> CFunDef Source
Defines a C function. For example
test = fun [intTy] "test"[int "a", int "b"] $ hblock [ creturn ("a" + "b") ]
Would be the equivalent of
int test(int a, int b) { return a + b; }
annotatedFun :: [CDeclSpec] -> String -> [Maybe CExpr -> CDecl] -> [String] -> CStat -> CFunDef Source
Identical to fun except this annotates the list of attributes given as a list of strings.
transUnit :: [CExtDecl] -> CTranslUnit Source
Exports a series of declarations to a translation unit.