| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Feldspar.Run.Compile
Synopsis
- type VExp = Struct PrimType' Prim
 - data VExp' where
 - newRefV :: Monad m => TypeRep a -> String -> TargetT m (Struct PrimType' Ref a)
 - initRefV :: Monad m => String -> VExp a -> TargetT m (Struct PrimType' Ref a)
 - getRefV :: Monad m => Struct PrimType' Ref a -> TargetT m (VExp a)
 - setRefV :: Monad m => Struct PrimType' Ref a -> VExp a -> TargetT m ()
 - unsafeFreezeRefV :: Monad m => Struct PrimType' Ref a -> TargetT m (VExp a)
 - data CompilerOpts = CompilerOpts {}
 - data Env = Env {}
 - env0 :: Env
 - localAlias :: MonadReader Env m => Name -> VExp a -> m b -> m b
 - lookAlias :: MonadReader Env m => TypeRep a -> Name -> m (VExp a)
 - type TargetCMD = RefCMD :+: (ArrCMD :+: (ControlCMD :+: (ThreadCMD :+: (ChanCMD :+: (PtrCMD :+: (FileCMD :+: C_CMD))))))
 - type TargetT m = ReaderT Env (ProgramT TargetCMD (Param2 Prim PrimType') m)
 - type ProgC = Program TargetCMD (Param2 Prim PrimType')
 - translateExp :: forall m a. Monad m => Data a -> TargetT m (VExp a)
 - unsafeTransSmallExp :: Monad m => Data a -> TargetT m (Prim a)
 - translate :: Env -> Run a -> ProgC a
 - runIO :: MonadRun m => m a -> IO a
 - runIO' :: MonadRun m => m a -> IO a
 - captureIO :: MonadRun m => m a -> String -> IO String
 - compile' :: MonadRun m => CompilerOpts -> m a -> String
 - compile :: MonadRun m => m a -> String
 - compileAll' :: MonadRun m => CompilerOpts -> m a -> [(String, String)]
 - compileAll :: MonadRun m => m a -> [(String, String)]
 - icompile' :: MonadRun m => CompilerOpts -> m a -> IO ()
 - icompile :: MonadRun m => m a -> IO ()
 - compileAndCheck' :: MonadRun m => CompilerOpts -> ExternalCompilerOpts -> m a -> IO ()
 - compileAndCheck :: MonadRun m => m a -> IO ()
 - runCompiled' :: MonadRun m => CompilerOpts -> ExternalCompilerOpts -> m a -> IO ()
 - runCompiled :: MonadRun m => m a -> IO ()
 - withCompiled' :: MonadRun m => CompilerOpts -> ExternalCompilerOpts -> m a -> ((String -> IO String) -> IO b) -> IO b
 - withCompiled :: MonadRun m => m a -> ((String -> IO String) -> IO b) -> IO b
 - captureCompiled' :: MonadRun m => CompilerOpts -> ExternalCompilerOpts -> m a -> String -> IO String
 - captureCompiled :: MonadRun m => m a -> String -> IO String
 - compareCompiled' :: MonadRun m => CompilerOpts -> ExternalCompilerOpts -> m a -> IO a -> String -> IO ()
 - compareCompiled :: MonadRun m => m a -> IO a -> String -> IO ()
 
Struct expressions and variables
Struct expression with hidden result type
Compilation options
data CompilerOpts Source #
Options affecting code generation
A default set of options is given by def.
The assertion labels to include in the generated code can be stated using the
 functions select, allExcept and selectBy. For example
def{compilerAssertions =allExcept[InternalAssertion]}
states that we want to include all except internal assertions.
Constructors
| CompilerOpts | |
Fields 
  | |
Instances
| Default CompilerOpts Source # | |
Defined in Feldspar.Run.Compile Methods def :: CompilerOpts #  | |
Translation environment
Translation environment
Constructors
| Env | |
Fields 
  | |
Arguments
| :: MonadReader Env m | |
| => Name | Old name  | 
| -> VExp a | New expression  | 
| -> m b | |
| -> m b | 
Add a local alias to the environment
lookAlias :: MonadReader Env m => TypeRep a -> Name -> m (VExp a) Source #
Lookup an alias in the environment
Translation of expressions
type TargetCMD = RefCMD :+: (ArrCMD :+: (ControlCMD :+: (ThreadCMD :+: (ChanCMD :+: (PtrCMD :+: (FileCMD :+: C_CMD)))))) Source #
type TargetT m = ReaderT Env (ProgramT TargetCMD (Param2 Prim PrimType') m) Source #
Target monad during translation
unsafeTransSmallExp :: Monad m => Data a -> TargetT m (Prim a) Source #
Translate an expression that is assumed to fulfill PrimType a
Back ends
Arguments
| :: MonadRun m | |
| => m a | Program to run  | 
| -> String | Input to send to   | 
| -> IO String | Result from   | 
Like runIO but with explicit inputoutput connected to stdinstdout
compile' :: MonadRun m => CompilerOpts -> m 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.
compile :: MonadRun m => m 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.
By default, only assertions labeled with UserAssertion will be included in
 the generated code.
compileAll' :: MonadRun m => CompilerOpts -> m 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
compileAll :: MonadRun m => m 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
By default, only assertions labeled with UserAssertion will be included in
 the generated code.
icompile' :: MonadRun m => CompilerOpts -> m 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
icompile :: MonadRun m => m 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
By default, only assertions labeled with UserAssertion will be included in
 the generated code.
compileAndCheck' :: MonadRun m => CompilerOpts -> ExternalCompilerOpts -> m a -> IO () Source #
Generate C code and use CC to check that it compiles (no linking)
compileAndCheck :: MonadRun m => m a -> IO () Source #
Generate C code and use CC to check that it compiles (no linking)
By default, all assertions will be included in the generated code.
runCompiled' :: MonadRun m => CompilerOpts -> ExternalCompilerOpts -> m a -> IO () Source #
Generate C code, use CC to compile it, and run the resulting executable
runCompiled :: MonadRun m => m a -> IO () Source #
Generate C code, use CC to compile it, and run the resulting executable
By default, all assertions will be included in the generated code.
Arguments
| :: MonadRun m | |
| => CompilerOpts | |
| -> ExternalCompilerOpts | |
| -> m a | Program to compile  | 
| -> ((String -> IO String) -> IO b) | Function that has access to the compiled executable as a function  | 
| -> IO b | 
Arguments
| :: MonadRun m | |
| => CompilerOpts | |
| -> ExternalCompilerOpts | |
| -> m 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'.
Arguments
| :: MonadRun m | |
| => m 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.
By default, all assertions will be included in the generated code.
Arguments
| :: MonadRun m | |
| => CompilerOpts | |
| -> ExternalCompilerOpts | |
| -> m 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