{-# LANGUAGE QuasiQuotes #-} module Futhark.CodeGen.Backends.SequentialC.Boilerplate (generateBoilerplate) where import qualified Futhark.CodeGen.Backends.GenericC as GC import qualified Language.C.Quote.OpenCL as C generateBoilerplate :: GC.CompilerM op s () generateBoilerplate :: CompilerM op s () generateBoilerplate = do String cfg <- String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s String forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s String GC.publicDef String "context_config" HeaderSection GC.InitDecl ((String -> (Definition, Definition)) -> CompilerM op s String) -> (String -> (Definition, Definition)) -> CompilerM op s String forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|struct $id:s;|], [C.cedecl|struct $id:s { int debugging; };|] ) String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () GC.publicDef_ String "context_config_new" HeaderSection GC.InitDecl ((String -> (Definition, Definition)) -> CompilerM op s ()) -> (String -> (Definition, Definition)) -> CompilerM op s () forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|struct $id:cfg* $id:s(void);|], [C.cedecl|struct $id:cfg* $id:s(void) { struct $id:cfg *cfg = (struct $id:cfg*) malloc(sizeof(struct $id:cfg)); if (cfg == NULL) { return NULL; } cfg->debugging = 0; return cfg; }|] ) String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () GC.publicDef_ String "context_config_free" HeaderSection GC.InitDecl ((String -> (Definition, Definition)) -> CompilerM op s ()) -> (String -> (Definition, Definition)) -> CompilerM op s () forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|void $id:s(struct $id:cfg* cfg);|], [C.cedecl|void $id:s(struct $id:cfg* cfg) { free(cfg); }|] ) String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () GC.publicDef_ String "context_config_set_debugging" HeaderSection GC.InitDecl ((String -> (Definition, Definition)) -> CompilerM op s ()) -> (String -> (Definition, Definition)) -> CompilerM op s () forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|void $id:s(struct $id:cfg* cfg, int flag);|], [C.cedecl|void $id:s(struct $id:cfg* cfg, int detail) { cfg->debugging = detail; }|] ) String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () GC.publicDef_ String "context_config_set_logging" HeaderSection GC.InitDecl ((String -> (Definition, Definition)) -> CompilerM op s ()) -> (String -> (Definition, Definition)) -> CompilerM op s () forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|void $id:s(struct $id:cfg* cfg, int flag);|], [C.cedecl|void $id:s(struct $id:cfg* cfg, int detail) { /* Does nothing for this backend. */ (void)cfg; (void)detail; }|] ) ([FieldGroup] fields, [Stm] init_fields) <- CompilerM op s ([FieldGroup], [Stm]) forall op s. CompilerM op s ([FieldGroup], [Stm]) GC.contextContents String ctx <- String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s String forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s String GC.publicDef String "context" HeaderSection GC.InitDecl ((String -> (Definition, Definition)) -> CompilerM op s String) -> (String -> (Definition, Definition)) -> CompilerM op s String forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|struct $id:s;|], [C.cedecl|struct $id:s { int detail_memory; int debugging; int profiling; int logging; typename lock_t lock; char *error; typename FILE *log; int profiling_paused; $sdecls:fields };|] ) String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () GC.publicDef_ String "context_new" HeaderSection GC.InitDecl ((String -> (Definition, Definition)) -> CompilerM op s ()) -> (String -> (Definition, Definition)) -> CompilerM op s () forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|struct $id:ctx* $id:s(struct $id:cfg* cfg);|], [C.cedecl|struct $id:ctx* $id:s(struct $id:cfg* cfg) { struct $id:ctx* ctx = (struct $id:ctx*) malloc(sizeof(struct $id:ctx)); if (ctx == NULL) { return NULL; } ctx->detail_memory = cfg->debugging; ctx->debugging = cfg->debugging; ctx->profiling = cfg->debugging; ctx->logging = cfg->debugging; ctx->error = NULL; ctx->log = stderr; create_lock(&ctx->lock); $stms:init_fields init_constants(ctx); return ctx; }|] ) String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () GC.publicDef_ String "context_free" HeaderSection GC.InitDecl ((String -> (Definition, Definition)) -> CompilerM op s ()) -> (String -> (Definition, Definition)) -> CompilerM op s () forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|void $id:s(struct $id:ctx* ctx);|], [C.cedecl|void $id:s(struct $id:ctx* ctx) { free_constants(ctx); free_lock(&ctx->lock); free(ctx); }|] ) String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () GC.publicDef_ String "context_sync" HeaderSection GC.MiscDecl ((String -> (Definition, Definition)) -> CompilerM op s ()) -> (String -> (Definition, Definition)) -> CompilerM op s () forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|int $id:s(struct $id:ctx* ctx);|], [C.cedecl|int $id:s(struct $id:ctx* ctx) { (void)ctx; return 0; }|] ) Definition -> CompilerM op s () forall op s. Definition -> CompilerM op s () GC.earlyDecl [C.cedecl|static const char *size_names[0];|] Definition -> CompilerM op s () forall op s. Definition -> CompilerM op s () GC.earlyDecl [C.cedecl|static const char *size_vars[0];|] Definition -> CompilerM op s () forall op s. Definition -> CompilerM op s () GC.earlyDecl [C.cedecl|static const char *size_classes[0];|] String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () forall op s. String -> HeaderSection -> (String -> (Definition, Definition)) -> CompilerM op s () GC.publicDef_ String "context_config_set_size" HeaderSection GC.InitDecl ((String -> (Definition, Definition)) -> CompilerM op s ()) -> (String -> (Definition, Definition)) -> CompilerM op s () forall a b. (a -> b) -> a -> b $ \String s -> ( [C.cedecl|int $id:s(struct $id:cfg* cfg, const char *size_name, size_t size_value);|], [C.cedecl|int $id:s(struct $id:cfg* cfg, const char *size_name, size_t size_value) { (void)cfg; (void)size_name; (void)size_value; return 1; }|] )