futhark-0.21.11: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageHaskell2010

Futhark.Script

Description

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

Server

data ScriptServer Source #

Like a Server, but keeps a bit more state to make FutharkScript more convenient.

withScriptServer :: ServerCfg -> (ScriptServer -> IO a) -> IO a Source #

Start a server, execute an action, then shut down the server. Similar to withServer.

withScriptServer' :: MonadIO m => Server -> (ScriptServer -> m a) -> m a Source #

Run an action with a ScriptServer produced by an existing Server, without shutting it down at the end.

Expressions, values, and types

data Func Source #

A function called in a Call expression can be either a Futhark function or a builtin function.

Instances

Instances details
Show Func Source # 
Instance details

Defined in Futhark.Script

Methods

showsPrec :: Int -> Func -> ShowS #

show :: Func -> String #

showList :: [Func] -> ShowS #

Pretty Func Source # 
Instance details

Defined in Futhark.Script

Methods

ppr :: Func -> Doc #

pprPrec :: Int -> Func -> Doc #

pprList :: [Func] -> Doc #

data Exp Source #

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.

Constructors

Call Func [Exp] 
Const Value 
Tuple [Exp] 
Record [(Text, Exp)] 
StringLit Text 
Let [VarName] Exp Exp 
ServerVar TypeName VarName

Server-side variable, *not* Futhark variable (these are handled in Call).

Instances

Instances details
Show Exp Source # 
Instance details

Defined in Futhark.Script

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

Pretty Exp Source # 
Instance details

Defined in Futhark.Script

Methods

ppr :: Exp -> Doc #

pprPrec :: Int -> Exp -> Doc #

pprList :: [Exp] -> Doc #

parseExp :: Parsec Void Text () -> Parsec Void Text Exp Source #

Parse a FutharkScript expression, given a whitespace parser.

parseExpFromText :: FilePath -> Text -> Either Text Exp Source #

Parse a FutharkScript expression with normal whitespace handling.

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.

Constructors

STValue TypeName 
STFun [TypeName] [TypeName]

Ins, then outs.

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.

Constructors

SValue TypeName v 
SFun EntryName [TypeName] [TypeName] [ScriptValue v]

Ins, then outs. Yes, this is the opposite of more or less everywhere else.

Instances

Instances details
Functor ScriptValue Source # 
Instance details

Defined in Futhark.Script

Methods

fmap :: (a -> b) -> ScriptValue a -> ScriptValue b #

(<$) :: a -> ScriptValue b -> ScriptValue a #

Foldable ScriptValue Source # 
Instance details

Defined in Futhark.Script

Methods

fold :: Monoid m => ScriptValue m -> m #

foldMap :: Monoid m => (a -> m) -> ScriptValue a -> m #

foldMap' :: Monoid m => (a -> m) -> ScriptValue a -> m #

foldr :: (a -> b -> b) -> b -> ScriptValue a -> b #

foldr' :: (a -> b -> b) -> b -> ScriptValue a -> b #

foldl :: (b -> a -> b) -> b -> ScriptValue a -> b #

foldl' :: (b -> a -> b) -> b -> ScriptValue a -> b #

foldr1 :: (a -> a -> a) -> ScriptValue a -> a #

foldl1 :: (a -> a -> a) -> ScriptValue a -> a #

toList :: ScriptValue a -> [a] #

null :: ScriptValue a -> Bool #

length :: ScriptValue a -> Int #

elem :: Eq a => a -> ScriptValue a -> Bool #

maximum :: Ord a => ScriptValue a -> a #

minimum :: Ord a => ScriptValue a -> a #

sum :: Num a => ScriptValue a -> a #

product :: Num a => ScriptValue a -> a #

Traversable ScriptValue Source # 
Instance details

Defined in Futhark.Script

Methods

traverse :: Applicative f => (a -> f b) -> ScriptValue a -> f (ScriptValue b) #

sequenceA :: Applicative f => ScriptValue (f a) -> f (ScriptValue a) #

mapM :: Monad m => (a -> m b) -> ScriptValue a -> m (ScriptValue b) #

sequence :: Monad m => ScriptValue (m a) -> m (ScriptValue a) #

Show v => Show (ScriptValue v) Source # 
Instance details

Defined in Futhark.Script

serverVarsInValue :: ExpValue -> Set VarName Source #

The set of server-side variables in the value.

data ValOrVar Source #

A Haskell-level value or a variable on the server.

Constructors

VVal Value 
VVar VarName 

Instances

Instances details
Show ValOrVar Source # 
Instance details

Defined in Futhark.Script

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