Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Haskell code for interacting with a Futhark server program. This module presents a low-level interface. See <https://futhark.readthedocs.io/en/latest/server-protocol.html the documentation of the server protocol> for the meaning of the commands. See also Futhark.Server.Values for higher-level functions for loading data into a server.
Error messages produced by the server will be returned as a
CmdFailure
. However, certain errors (such as if the server
process terminates unexpectedly, or temporary files cannot be
created) will result in an IO exception.
Many of the functions here are documented only as the server protocol command they correspond to. See the protocol documentation for details.
Synopsis
- data Server
- data ServerCfg = ServerCfg {}
- newServerCfg :: FilePath -> [String] -> ServerCfg
- withServer :: ServerCfg -> (Server -> IO a) -> IO a
- data CmdFailure = CmdFailure {
- failureLog :: [Text]
- failureMsg :: [Text]
- type VarName = Text
- type TypeName = Text
- type EntryName = Text
- data InputType = InputType {}
- data OutputType = OutputType {}
- cmdRestore :: Server -> FilePath -> [(VarName, TypeName)] -> IO (Maybe CmdFailure)
- cmdStore :: Server -> FilePath -> [VarName] -> IO (Maybe CmdFailure)
- cmdCall :: Server -> EntryName -> [VarName] -> [VarName] -> IO (Either CmdFailure [Text])
- cmdFree :: Server -> [VarName] -> IO (Maybe CmdFailure)
- cmdRename :: Server -> VarName -> VarName -> IO (Maybe CmdFailure)
- cmdInputs :: Server -> EntryName -> IO (Either CmdFailure [InputType])
- cmdOutputs :: Server -> EntryName -> IO (Either CmdFailure [OutputType])
- cmdClear :: Server -> IO (Maybe CmdFailure)
- cmdReport :: Server -> IO (Either CmdFailure [Text])
- cmdPauseProfiling :: Server -> IO (Maybe CmdFailure)
- cmdUnpauseProfiling :: Server -> IO (Maybe CmdFailure)
- cmdSetTuningParam :: Server -> Text -> Text -> IO (Either CmdFailure [Text])
- cmdMaybe :: (MonadError Text m, MonadIO m) => IO (Maybe CmdFailure) -> m ()
- cmdEither :: (MonadError Text m, MonadIO m) => IO (Either CmdFailure a) -> m a
- startServer :: ServerCfg -> IO Server
- stopServer :: Server -> IO ()
- sendCommand :: Server -> [Text] -> IO (Either CmdFailure [Text])
Server creation
Configuration of the server. Use newServerCfg
to conveniently
create a sensible default configuration.
newServerCfg :: FilePath -> [String] -> ServerCfg Source #
Create a server config with the given cfgProg
and cfgProgOpts
.
withServer :: ServerCfg -> (Server -> IO a) -> IO a Source #
Start a server, execute an action, then shut down the server.
The Server
may not be returned from the action.
Commands
data CmdFailure Source #
The command failed, and this is why. The first Text
is any
output before the failure indincator, and the second Text is the
output after the indicator.
CmdFailure | |
|
Instances
Eq CmdFailure Source # | |
Defined in Futhark.Server (==) :: CmdFailure -> CmdFailure -> Bool # (/=) :: CmdFailure -> CmdFailure -> Bool # | |
Ord CmdFailure Source # | |
Defined in Futhark.Server compare :: CmdFailure -> CmdFailure -> Ordering # (<) :: CmdFailure -> CmdFailure -> Bool # (<=) :: CmdFailure -> CmdFailure -> Bool # (>) :: CmdFailure -> CmdFailure -> Bool # (>=) :: CmdFailure -> CmdFailure -> Bool # max :: CmdFailure -> CmdFailure -> CmdFailure # min :: CmdFailure -> CmdFailure -> CmdFailure # | |
Show CmdFailure Source # | |
Defined in Futhark.Server showsPrec :: Int -> CmdFailure -> ShowS # show :: CmdFailure -> String # showList :: [CmdFailure] -> ShowS # |
The type of an input of an entry point. If inputConsumed
, then
the value passed in a cmdCall
must not be used again (nor any of
its aliases).
data OutputType Source #
The type of an output of an entry point. If outputUnique
, then
the value returned does not alias any of the inputs. See the
Futhark language manual itself for more details - the implications
are quite subtle (but you can ignore them unless you manually use
type annotations to make some entry point parameters unique).
cmdRestore :: Server -> FilePath -> [(VarName, TypeName)] -> IO (Maybe CmdFailure) Source #
restore filename var0 type0 var1 type1...
.
cmdStore :: Server -> FilePath -> [VarName] -> IO (Maybe CmdFailure) Source #
store filename vars...
.
cmdCall :: Server -> EntryName -> [VarName] -> [VarName] -> IO (Either CmdFailure [Text]) Source #
call entrypoint outs... ins...
.
cmdInputs :: Server -> EntryName -> IO (Either CmdFailure [InputType]) Source #
inputs entryname
, with uniqueness represented as True.
cmdOutputs :: Server -> EntryName -> IO (Either CmdFailure [OutputType]) Source #
outputs entryname
, with uniqueness represented as True.
cmdPauseProfiling :: Server -> IO (Maybe CmdFailure) Source #
pause_profiling
cmdUnpauseProfiling :: Server -> IO (Maybe CmdFailure) Source #
unpause_profiling
cmdSetTuningParam :: Server -> Text -> Text -> IO (Either CmdFailure [Text]) Source #
set_tuning_param param value
Utility
cmdMaybe :: (MonadError Text m, MonadIO m) => IO (Maybe CmdFailure) -> m () Source #
Turn a Maybe
-producing command into a monadic action.
cmdEither :: (MonadError Text m, MonadIO m) => IO (Either CmdFailure a) -> m a Source #
Turn an Either
-producing command into a monadic action.
Raw
startServer :: ServerCfg -> IO Server Source #
Start up a server. Make sure that stopServer
is eventually
called on the server. If this does not happen, then temporary
files may be left on the file system. You almost certainly wish to
use bracket
or similar to avoid this. Calls error
if startup
fails.
stopServer :: Server -> IO () Source #
Shut down a server. It may not be used again. Calls error
if
the server process terminates with a failing exit code
(i.e. anything but ExitSuccess
).
sendCommand :: Server -> [Text] -> IO (Either CmdFailure [Text]) Source #
Send an arbitrary command to the server. This is only useful when the server protocol has been extended without this module having been similarly extended. Be careful not to send invalid commands.