Safe Haskell | None |
---|---|
Language | Haskell2010 |
C code generation for Program
Synopsis
- module Language.Embedded.Backend.C.Expression
- data ExternalCompilerOpts = ExternalCompilerOpts {}
- namedType :: String -> Type
- viewNotExp :: Exp -> Maybe Exp
- arrayInit :: [Exp] -> Initializer
- compile :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> String
- compileAll :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> [(String, String)]
- icompile :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> IO ()
- removeFileIfPossible :: FilePath -> IO ()
- maybePutStrLn :: Bool -> String -> IO ()
- compileC :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => ExternalCompilerOpts -> Program instr (Param2 exp pred) a -> IO FilePath
- compileAndCheck' :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => ExternalCompilerOpts -> Program instr (Param2 exp pred) a -> IO ()
- compileAndCheck :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> IO ()
- runCompiled' :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => ExternalCompilerOpts -> Program instr (Param2 exp pred) a -> IO ()
- runCompiled :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> IO ()
- withCompiled' :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => ExternalCompilerOpts -> Program instr (Param2 exp pred) a -> ((String -> IO String) -> IO b) -> IO b
- withCompiled :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> ((String -> IO String) -> IO b) -> IO b
- captureCompiled' :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => ExternalCompilerOpts -> Program instr (Param2 exp pred) a -> String -> IO String
- captureCompiled :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> String -> IO String
- compareCompiled' :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => ExternalCompilerOpts -> Program instr (Param2 exp pred) a -> IO a -> String -> IO ()
- compareCompiled :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> IO a -> String -> IO ()
- class Default a where
- def :: a
Documentation
data ExternalCompilerOpts Source #
ExternalCompilerOpts | |
|
Instances
arrayInit :: [Exp] -> Initializer Source #
compile :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> String Source #
Compile a program to C code represented as a string. To compile the resulting C code, use something like
cc -std=c99 YOURPROGRAM.c
This function returns only the first (main) module. To get all C translation
unit, use compileAll
.
compileAll :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> [(String, String)] Source #
Compile a program to C modules, each one represented as a pair of a name and the code represented as a string. To compile the resulting C code, use something like
cc -std=c99 YOURPROGRAM.c
icompile :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> IO () Source #
Compile a program to C code and print it on the screen. To compile the resulting C code, use something like
cc -std=c99 YOURPROGRAM.c
removeFileIfPossible :: FilePath -> IO () Source #
:: (Interp instr CGen (Param2 exp pred), HFunctor instr) | |
=> ExternalCompilerOpts | |
-> Program instr (Param2 exp pred) a | Program to compile |
-> IO FilePath | Path to the generated executable |
Generate C code and use CC to compile it
compileAndCheck' :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => ExternalCompilerOpts -> Program instr (Param2 exp pred) a -> IO () Source #
Generate C code and use CC to check that it compiles (no linking)
compileAndCheck :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> IO () Source #
Generate C code and use CC to check that it compiles (no linking)
runCompiled' :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => ExternalCompilerOpts -> Program instr (Param2 exp pred) a -> IO () Source #
Generate C code, use CC to compile it, and run the resulting executable
runCompiled :: (Interp instr CGen (Param2 exp pred), HFunctor instr) => Program instr (Param2 exp pred) a -> IO () Source #
Generate C code, use CC to compile it, and run the resulting executable
:: (Interp instr CGen (Param2 exp pred), HFunctor instr) | |
=> ExternalCompilerOpts | |
-> Program instr (Param2 exp pred) a | Program to run |
-> String | Input to send to |
-> IO String | Result from |
Like runCompiled'
but with explicit input/output connected to
stdin
/stdout
. Note that the program will be compiled every time the
function is applied to a string. In order to compile once and run many times,
use the function withCompiled'
.
:: (Interp instr CGen (Param2 exp pred), HFunctor instr) | |
=> Program instr (Param2 exp pred) a | Program to run |
-> String | Input to send to |
-> IO String | Result from |
Like runCompiled
but with explicit input/output connected to
stdin
/stdout
. Note that the program will be compiled every time the
function is applied to a string. In order to compile once and run many times,
use the function withCompiled
.
:: (Interp instr CGen (Param2 exp pred), HFunctor instr) | |
=> ExternalCompilerOpts | |
-> Program instr (Param2 exp pred) a | Program to run |
-> IO a | Reference program |
-> String | Input to send to |
-> IO () |
Compare the content written to stdout
from the reference program and from
running the compiled C code
:: (Interp instr CGen (Param2 exp pred), HFunctor instr) | |
=> Program instr (Param2 exp pred) a | Program to run |
-> IO a | Reference program |
-> String | Input to send to |
-> IO () |
Compare the content written to stdout
from the reference program and from
running the compiled C code
A class for types with a default value.
Nothing