futhark-server-1.2.1.0: Client implementation of the Futhark server protocol.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.Server

Description

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

Server creation

data Server Source #

A handle to a running server.

data ServerCfg Source #

Configuration of the server. Use newServerCfg to conveniently create a sensible default configuration.

Constructors

ServerCfg 

Fields

  • cfgProg :: FilePath

    Path to the server executable.

  • cfgProgOpts :: [String]

    Command line options to pass to the server executable.

  • cfgDebug :: Bool

    If true, print a running log of server communication to stderr.

  • cfgOnLine :: Cmd -> Text -> IO ()

    A function that is invoked on every line of input sent by the server, except the %%% OK and %%% FAILURE prompts. This can be used to e.g. print or gather logging messages as they arrive, instead of waiting for the command to finish. The name of the command leading to the message is also provided. The default function does nothing.

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

type Cmd = Text Source #

The name of a command.

data CmdFailure Source #

The command failed, and this is why. The first Text is any output before the failure indicator, and the second Text is the output after the indicator.

Constructors

CmdFailure 

Fields

type VarName = Text Source #

The name of a server-side variable.

type TypeName = Text Source #

The name of a server-side type.

type EntryName = Text Source #

The name of an entry point.

data InputType Source #

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).

Constructors

InputType 

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).

Constructors

OutputType 

Main commands

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....

cmdFree :: Server -> [VarName] -> IO (Maybe CmdFailure) Source #

free vars....

cmdRename :: Server -> VarName -> VarName -> IO (Maybe CmdFailure) Source #

rename oldname newname.

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.

Interrogation

Records

cmdNew :: Server -> Text -> Text -> [Text] -> IO (Maybe CmdFailure) Source #

new var0 type var1...

cmdProject :: Server -> Text -> Text -> Text -> IO (Maybe CmdFailure) Source #

project to from field

cmdFields :: Server -> Text -> IO (Either CmdFailure [Text]) Source #

fields type

Auxiliary

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 -> Cmd -> [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.