Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype Parser a = Parser {}
- readParser :: forall a. (Read a, Typeable a) => Parser a
- parse :: Parser a -> String -> a
- class MarshalHaskell a where
- class MarshalHaskell (HaskellRep a) => MarshalFeld a where
- type HaskellRep a
- writeStd :: MarshalFeld a => a -> Run ()
- readStd :: MarshalFeld a => Run a
- connectStdIO :: (MarshalFeld a, MarshalFeld b) => (a -> Run b) -> Run ()
- streamStdIO :: (MarshalFeld a, MarshalFeld b) => (a -> Run b) -> Run ()
- marshalled' :: (MarshalFeld a, MarshalFeld b) => CompilerOpts -> ExternalCompilerOpts -> (a -> Run b) -> ((HaskellRep a -> IO (HaskellRep b)) -> IO c) -> IO c
- marshalled :: (MarshalFeld a, MarshalFeld b) => (a -> Run b) -> ((HaskellRep a -> IO (HaskellRep b)) -> IO c) -> IO c
- marshalledStream' :: (MarshalFeld a, MarshalFeld b) => CompilerOpts -> ExternalCompilerOpts -> (a -> Run b) -> (([HaskellRep a] -> IO [HaskellRep b]) -> IO c) -> IO c
- marshalledStream :: (MarshalFeld a, MarshalFeld b) => (a -> Run b) -> (([HaskellRep a] -> IO [HaskellRep b]) -> IO c) -> IO c
Documentation
class MarshalHaskell a where Source #
Serialization/deserialization of Haskell values
The following property must hold for all a
:
a = parse toHaskell (fromHaskell a) Prelude.== a
fromHaskell :: a -> String Source #
Serialize a Haskell value
fromHaskell :: Show a => a -> String Source #
Serialize a Haskell value
toHaskell :: Parser a Source #
Deserialize a Haskell value
toHaskell :: (Read a, Typeable a) => Parser a Source #
Deserialize a Haskell value
MarshalHaskell Double Source # | |
MarshalHaskell Float Source # | |
MarshalHaskell Int Source # | |
MarshalHaskell Int8 Source # | |
MarshalHaskell Int16 Source # | |
MarshalHaskell Int32 Source # | |
MarshalHaskell Int64 Source # | |
MarshalHaskell Word8 Source # | |
MarshalHaskell Word16 Source # | |
MarshalHaskell Word32 Source # | |
MarshalHaskell Word64 Source # | |
MarshalHaskell a => MarshalHaskell [a] Source # | |
MarshalHaskell (Complex Double) Source # | |
MarshalHaskell (Complex Float) Source # | |
(MarshalHaskell a, MarshalHaskell b) => MarshalHaskell (a, b) Source # | |
(MarshalHaskell a, MarshalHaskell b, MarshalHaskell c) => MarshalHaskell (a, b, c) Source # | |
(MarshalHaskell a, MarshalHaskell b, MarshalHaskell c, MarshalHaskell d) => MarshalHaskell (a, b, c, d) Source # | |
class MarshalHaskell (HaskellRep a) => MarshalFeld a where Source #
Serialization/deserialization of Feldspar values
type HaskellRep a Source #
The Haskell representation of a Feldspar value
fwrite :: Handle -> a -> Run () Source #
Serialize a Feldspar value to a handle
fwrite :: (PrimType b, Formattable b, a ~ Data b) => Handle -> a -> Run () Source #
Serialize a Feldspar value to a handle
fread :: Handle -> Run a Source #
Deserialize a Feldspar value from a handle
fread :: (PrimType b, Formattable b, a ~ Data b) => Handle -> Run a Source #
Deserialize a Feldspar value from a handle
writeStd :: MarshalFeld a => a -> Run () Source #
Write a value to stdout
readStd :: MarshalFeld a => Run a Source #
Read a value from stdin
connectStdIO :: (MarshalFeld a, MarshalFeld b) => (a -> Run b) -> Run () Source #
Connect a Feldspar function between serializable types to stdin
/stdout
streamStdIO :: (MarshalFeld a, MarshalFeld b) => (a -> Run b) -> Run () Source #
Connect a Feldspar function between serializable types to stdin
/stdout
.
The inputoutput will be in the form of a list as recognized by toHaskell
fromHaskell
(i.e. the length followed by the elements in sequence).
The function will be mapped over the input list in a lazy manner.
:: (MarshalFeld a, MarshalFeld b) | |
=> CompilerOpts | |
-> ExternalCompilerOpts | |
-> (a -> Run b) | Function to compile |
-> ((HaskellRep a -> IO (HaskellRep b)) -> IO c) | Function that has access to the compiled executable as a function |
-> IO c |
A version of marshalled
that takes ExternalCompilerOpts
as additional
argument
:: (MarshalFeld a, MarshalFeld b) | |
=> (a -> Run b) | Function to compile |
-> ((HaskellRep a -> IO (HaskellRep b)) -> IO c) | Function that has access to the compiled executable as a function |
-> IO c |
Compile a function and make it available as an IO
function. Note that
compilation only happens once, even if the function is used many times in the
body.
For example, given the following Feldspar function:
sumArr :: DIArr Int32 -> Run (Data Int32) sumArr arr = do r <- initRef 0 for (0,1,Excl $ length arr) $ \i -> modifyRef r (+ arrIx arr i) unsafeFreezeRef r
marshalled
can be used as follows:
*Main> marshalled sumArr $ \f -> (f [3,4,5] >>= print) >> (f [6,7,8,9] >>= print)
:: (MarshalFeld a, MarshalFeld b) | |
=> CompilerOpts | |
-> ExternalCompilerOpts | |
-> (a -> Run b) | Function to compile |
-> (([HaskellRep a] -> IO [HaskellRep b]) -> IO c) | Function that has access to the compiled executable as a function |
-> IO c |
A version of marshalledStream
that takes ExternalCompilerOpts
as
additional argument
:: (MarshalFeld a, MarshalFeld b) | |
=> (a -> Run b) | Function to compile |
-> (([HaskellRep a] -> IO [HaskellRep b]) -> IO c) | Function that has access to the compiled executable as a function |
-> IO c |
Compile a function and make it available as an IO
function. The compiled
function will be applied repeatedly over the list of inputs producing a list
of outputs. Note that compilation only happens once, even if the function is
used many times in the body.