c-dsl-0.3.1: A higher level DSL on top of language-c

Safe HaskellNone
LanguageHaskell2010

Language.C.DSL.Decl

Synopsis

Documentation

decl Source

Arguments

:: 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 CDeclrs

-> Maybe CExpr

The optional init expression

-> CDecl 

A low level way to declare something.

voidTy :: CDeclSpec Source

The CDeclSpec for declarations of type void

charTy :: CDeclSpec Source

The CDeclSpec for declarations of type char

shortTy :: CDeclSpec Source

The CDeclSpec for declarations of type short

intTy :: CDeclSpec Source

The CDeclSpec for declarations of type int

longTy :: CDeclSpec Source

The CDeclSpec for declarations of type long

floatTy :: CDeclSpec Source

The CDeclSpec for declarations of type float

doubleTy :: CDeclSpec Source

The CDeclSpec for declarations of type 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;

short :: CDeclr -> Maybe CExpr -> CDecl Source

A short cut for declaring a short

int :: CDeclr -> Maybe CExpr -> CDecl Source

A short cut for declaring a int

long :: CDeclr -> Maybe CExpr -> CDecl Source

A short cut for declaring a long

float :: CDeclr -> Maybe CExpr -> CDecl Source

A short cut for declaring a float

double :: CDeclr -> Maybe CExpr -> CDecl Source

A short cut for declaring a double

charPtr :: CDeclr -> Maybe CExpr -> CDecl Source

Equivalent to char but wraps the CDeclr in a pointer. This means that uninit $ charPtr someName is equivalent to char *someName;

(.=) :: (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.