Safe Haskell | None |
---|---|
Language | Haskell2010 |
FutharkScript is a (tiny) subset of Futhark used to write small
expressions that are evaluated by server executables. The futhark
literate
command is the main user.
Synopsis
- data ScriptServer
- withScriptServer :: FilePath -> [FilePath] -> (ScriptServer -> IO a) -> IO a
- data Func
- data Exp
- parseExp :: Parser () -> Parser Exp
- varsInExp :: Exp -> Set EntryName
- data ScriptValueType
- data ScriptValue v
- scriptValueType :: ScriptValue v -> ScriptValueType
- type ExpValue = Compound (ScriptValue ValOrVar)
- type EvalBuiltin m = Text -> [CompoundValue] -> m CompoundValue
- evalExp :: forall m. (MonadError Text m, MonadIO m) => EvalBuiltin m -> ScriptServer -> Exp -> m ExpValue
- getExpValue :: (MonadError Text m, MonadIO m) => ScriptServer -> ExpValue -> m CompoundValue
- evalExpToGround :: (MonadError Text m, MonadIO m) => EvalBuiltin m -> ScriptServer -> Exp -> m (Either (Compound ScriptValueType) CompoundValue)
- valueToExp :: ExpValue -> Exp
- freeValue :: (MonadError Text m, MonadIO m) => ScriptServer -> ExpValue -> m ()
Server
data ScriptServer Source #
Like a Server
, but keeps a bit more state to make FutharkScript
more convenient.
withScriptServer :: FilePath -> [FilePath] -> (ScriptServer -> IO a) -> IO a Source #
Start a server, execute an action, then shut down the server.
Similar to withServer
.
Expressions, values, and types
A function called in a Call
expression can be either a Futhark
function or a builtin function.
A FutharkScript expression. This is a simple AST that might not correspond exactly to what the user wrote (e.g. no parentheses or source locations). This is fine for small expressions, which is all this is meant for.
varsInExp :: Exp -> Set EntryName Source #
The set of Futhark variables that are referenced by the expression - these will have to be entry points in the Futhark program.
data ScriptValueType Source #
The type of a ScriptValue
- either a value type or a function type.
Instances
Eq ScriptValueType Source # | |
Defined in Futhark.Script (==) :: ScriptValueType -> ScriptValueType -> Bool # (/=) :: ScriptValueType -> ScriptValueType -> Bool # | |
Show ScriptValueType Source # | |
Defined in Futhark.Script showsPrec :: Int -> ScriptValueType -> ShowS # show :: ScriptValueType -> String # showList :: [ScriptValueType] -> ShowS # | |
Pretty ScriptValueType Source # | |
Defined in Futhark.Script ppr :: ScriptValueType -> Doc # pprPrec :: Int -> ScriptValueType -> Doc # pprList :: [ScriptValueType] -> Doc # |
data ScriptValue v Source #
A ScriptValue is either a base value or a partially applied function. We don't have real first-class functions in FutharkScript, but we sort of have closures.
SValue TypeName v | |
SFun EntryName [TypeName] [TypeName] [ScriptValue v] | Ins, then outs. Yes, this is the opposite of more or less everywhere else. |
Instances
scriptValueType :: ScriptValue v -> ScriptValueType Source #
The type of a ScriptValue
.
type ExpValue = Compound (ScriptValue ValOrVar) Source #
The intermediate values produced by an expression - in particular, these may not be on the server.
Evaluation
type EvalBuiltin m = Text -> [CompoundValue] -> m CompoundValue Source #
How to evaluate a builtin function.
evalExp :: forall m. (MonadError Text m, MonadIO m) => EvalBuiltin m -> ScriptServer -> Exp -> m ExpValue Source #
Evaluate a FutharkScript expression relative to some running server.
getExpValue :: (MonadError Text m, MonadIO m) => ScriptServer -> ExpValue -> m CompoundValue Source #
Read actual values from the server. Fails for values that have no well-defined external representation.
evalExpToGround :: (MonadError Text m, MonadIO m) => EvalBuiltin m -> ScriptServer -> Exp -> m (Either (Compound ScriptValueType) CompoundValue) Source #
Like evalExp
, but requires all values to be non-functional. If
the value has a bad type, return that type instead. Other
evaluation problems (e.g. type failures) raise errors.
valueToExp :: ExpValue -> Exp Source #
Convert a value into a corresponding expression.
freeValue :: (MonadError Text m, MonadIO m) => ScriptServer -> ExpValue -> m () Source #
Release all the server-side variables in the value. Yes, FutharkScript has manual memory management...