| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Futhark.CodeGen.Backends.GenericPython
Description
A generic Python code generator which is polymorphic in the type of the operations. Concretely, we use this to handle both sequential and PyOpenCL Python code.
Synopsis
- compileProg :: MonadFreshNames m => Maybe String -> Constructor -> [PyStmt] -> [PyStmt] -> Operations op s -> s -> [PyStmt] -> [Option] -> Definitions op -> m String
- data Constructor = Constructor [String] [PyStmt]
- emptyConstructor :: Constructor
- compileName :: VName -> String
- compileVar :: VName -> CompilerM op s PyExp
- compileDim :: DimSize -> PyExp
- compileExp :: Exp -> CompilerM op s PyExp
- compilePrimExp :: Monad m => (v -> m PyExp) -> PrimExp v -> m PyExp
- compileCode :: Code op -> CompilerM op s ()
- compilePrimValue :: PrimValue -> PyExp
- compilePrimType :: PrimType -> String
- compilePrimTypeExt :: PrimType -> Signedness -> String
- compilePrimToNp :: PrimType -> String
- compilePrimToExtNp :: PrimType -> Signedness -> String
- data Operations op s = Operations {- opsWriteScalar :: WriteScalar op s
- opsReadScalar :: ReadScalar op s
- opsAllocate :: Allocate op s
- opsCopy :: Copy op s
- opsStaticArray :: StaticArray op s
- opsCompiler :: OpCompiler op s
- opsEntryOutput :: EntryOutput op s
- opsEntryInput :: EntryInput op s
 
- defaultOperations :: Operations op s
- unpackDim :: PyExp -> DimSize -> Int32 -> CompilerM op s ()
- newtype CompilerM op s a = CompilerM (RWS (CompilerEnv op s) [PyStmt] (CompilerState s) a)
- type OpCompiler op s = op -> CompilerM op s ()
- type WriteScalar op s = PyExp -> PyExp -> PrimType -> SpaceId -> PyExp -> CompilerM op s ()
- type ReadScalar op s = PyExp -> PyExp -> PrimType -> SpaceId -> CompilerM op s PyExp
- type Allocate op s = PyExp -> PyExp -> SpaceId -> CompilerM op s ()
- type Copy op s = PyExp -> PyExp -> Space -> PyExp -> PyExp -> Space -> PyExp -> PrimType -> CompilerM op s ()
- type StaticArray op s = VName -> SpaceId -> PrimType -> ArrayContents -> CompilerM op s ()
- type EntryOutput op s = VName -> SpaceId -> PrimType -> Signedness -> [DimSize] -> CompilerM op s PyExp
- type EntryInput op s = PyExp -> SpaceId -> PrimType -> Signedness -> [DimSize] -> PyExp -> CompilerM op s ()
- data CompilerEnv op s = CompilerEnv {- envOperations :: Operations op s
- envVarExp :: Map VName PyExp
 
- data CompilerState s = CompilerState {- compNameSrc :: VNameSource
- compInit :: [PyStmt]
- compUserState :: s
 
- stm :: PyStmt -> CompilerM op s ()
- atInit :: PyStmt -> CompilerM op s ()
- collect' :: CompilerM op s a -> CompilerM op s (a, [PyStmt])
- collect :: CompilerM op s () -> CompilerM op s [PyStmt]
- simpleCall :: String -> [PyExp] -> PyExp
- copyMemoryDefaultSpace :: PyExp -> PyExp -> PyExp -> PyExp -> PyExp -> CompilerM op s ()
Documentation
compileProg :: MonadFreshNames m => Maybe String -> Constructor -> [PyStmt] -> [PyStmt] -> Operations op s -> s -> [PyStmt] -> [Option] -> Definitions op -> m String Source #
data Constructor Source #
The class generated by the code generator must have a constructor, although it can be vacuous.
Constructors
| Constructor [String] [PyStmt] | 
emptyConstructor :: Constructor Source #
A constructor that takes no arguments and does nothing.
compileName :: VName -> String Source #
compileDim :: DimSize -> PyExp Source #
compilePrimExp :: Monad m => (v -> m PyExp) -> PrimExp v -> m PyExp Source #
Tell me how to compile a v, and I'll Compile any PrimExp v for you.
compileCode :: Code op -> CompilerM op s () Source #
compilePrimValue :: PrimValue -> PyExp Source #
compilePrimTypeExt :: PrimType -> Signedness -> String Source #
The ctypes type corresponding to a PrimType, taking sign into account.
compilePrimToExtNp :: PrimType -> Signedness -> String Source #
The Numpy type corresponding to a PrimType, taking sign into account.
data Operations op s Source #
Constructors
| Operations | |
| Fields 
 | |
defaultOperations :: Operations op s Source #
A set of operations that fail for every operation involving
 non-default memory spaces.  Uses plain pointers and malloc for
 memory management.
newtype CompilerM op s a Source #
Constructors
| CompilerM (RWS (CompilerEnv op s) [PyStmt] (CompilerState s) a) | 
Instances
type OpCompiler op s = op -> CompilerM op s () Source #
A substitute expression compiler, tried before the main compilation function.
type WriteScalar op s = PyExp -> PyExp -> PrimType -> SpaceId -> PyExp -> CompilerM op s () Source #
Write a scalar to the given memory block with the given index and in the given memory space.
type ReadScalar op s = PyExp -> PyExp -> PrimType -> SpaceId -> CompilerM op s PyExp Source #
Read a scalar from the given memory block with the given index and in the given memory space.
type Allocate op s = PyExp -> PyExp -> SpaceId -> CompilerM op s () Source #
Allocate a memory block of the given size in the given memory space, saving a reference in the given variable name.
type Copy op s = PyExp -> PyExp -> Space -> PyExp -> PyExp -> Space -> PyExp -> PrimType -> CompilerM op s () Source #
Copy from one memory block to another.
type StaticArray op s = VName -> SpaceId -> PrimType -> ArrayContents -> CompilerM op s () Source #
Create a static array of values - initialised at load time.
type EntryOutput op s = VName -> SpaceId -> PrimType -> Signedness -> [DimSize] -> CompilerM op s PyExp Source #
Construct the Python array being returned from an entry point.
type EntryInput op s = PyExp -> SpaceId -> PrimType -> Signedness -> [DimSize] -> PyExp -> CompilerM op s () Source #
Unpack the array being passed to an entry point.
data CompilerEnv op s Source #
Constructors
| CompilerEnv | |
| Fields 
 | |
Instances
| MonadReader (CompilerEnv op s) (CompilerM op s) Source # | |
| Defined in Futhark.CodeGen.Backends.GenericPython Methods ask :: CompilerM op s (CompilerEnv op s) # local :: (CompilerEnv op s -> CompilerEnv op s) -> CompilerM op s a -> CompilerM op s a # reader :: (CompilerEnv op s -> a) -> CompilerM op s a # | |
data CompilerState s Source #
Constructors
| CompilerState | |
| Fields 
 | |
Instances
| MonadState (CompilerState s) (CompilerM op s) Source # | |
| Defined in Futhark.CodeGen.Backends.GenericPython Methods get :: CompilerM op s (CompilerState s) # put :: CompilerState s -> CompilerM op s () # state :: (CompilerState s -> (a, CompilerState s)) -> CompilerM op s a # | |