dovetail-0.1.0.0
Safe HaskellNone
LanguageHaskell2010

Dovetail.Types

Synopsis

Evaluation

Value types

data Value m Source #

The representation of values used by the interpreter - essentially, the semantic domain for a simple untyped lambda calculus with records and ADTs.

Any additional side effects which might occur in FFI calls to Haskell code are tracked by a monad in the type argument.

Constructors

Object (HashMap Text (Value m))

Records are represented as hashmaps from their field names to values

Array (Vector (Value m)) 
String Text 
Char Char 
Number Double 
Int Integer 
Bool Bool 
Closure (Value m -> EvalT m (Value m))

Closures, represented in higher-order abstract syntax style.

Constructor (ProperName 'ConstructorName) [Value m]

Fully-applied data constructors

Foreign Dynamic

Foreign data types

Instances

Instances details
MonadFix m => ToValue m (Value m) Source # 
Instance details

Defined in Dovetail.Evaluate

Methods

toValue :: Value m -> Value m Source #

fromValue :: Value m -> EvalT m (Value m) Source #

Evaluation monad

type Env m = Map (Qualified Ident) (Value m) Source #

An environment, i.e. a mapping from names to evaluated values.

An environment for a single built-in function can be constructed using the builtIn function, and environments can be combined easily using the Monoid instance for Map.

newtype EvalT m a Source #

The monad used by the interpreter, which supports error reporting for errors which can occur during evaluation.

The transformed monad is used to track any benign side effects that might be exposed via the foreign function interface to PureScript code.

Constructors

EvalT 

Instances

Instances details
MonadTrans EvalT Source # 
Instance details

Defined in Dovetail.Types

Methods

lift :: Monad m => m a -> EvalT m a #

(ToValue m a, n ~ m) => ToValueRHS m (EvalT n a) Source # 
Instance details

Defined in Dovetail.Evaluate

Methods

toValueRHS :: EvalT n a -> EvalT m (Value m) Source #

fromValueRHS :: EvalT m (Value m) -> EvalT n a Source #

Monad m => Monad (EvalT m) Source # 
Instance details

Defined in Dovetail.Types

Methods

(>>=) :: EvalT m a -> (a -> EvalT m b) -> EvalT m b #

(>>) :: EvalT m a -> EvalT m b -> EvalT m b #

return :: a -> EvalT m a #

Functor m => Functor (EvalT m) Source # 
Instance details

Defined in Dovetail.Types

Methods

fmap :: (a -> b) -> EvalT m a -> EvalT m b #

(<$) :: a -> EvalT m b -> EvalT m a #

MonadFix m => MonadFix (EvalT m) Source # 
Instance details

Defined in Dovetail.Types

Methods

mfix :: (a -> EvalT m a) -> EvalT m a #

Monad m => Applicative (EvalT m) Source # 
Instance details

Defined in Dovetail.Types

Methods

pure :: a -> EvalT m a #

(<*>) :: EvalT m (a -> b) -> EvalT m a -> EvalT m b #

liftA2 :: (a -> b -> c) -> EvalT m a -> EvalT m b -> EvalT m c #

(*>) :: EvalT m a -> EvalT m b -> EvalT m b #

(<*) :: EvalT m a -> EvalT m b -> EvalT m a #

Monad m => MonadError (EvaluationError m) (EvalT m) Source # 
Instance details

Defined in Dovetail.Types

Methods

throwError :: EvaluationError m -> EvalT m a #

catchError :: EvalT m a -> (EvaluationError m -> EvalT m a) -> EvalT m a #

Monad m => MonadReader (EvaluationContext m) (EvalT m) Source # 
Instance details

Defined in Dovetail.Types

Methods

ask :: EvalT m (EvaluationContext m) #

local :: (EvaluationContext m -> EvaluationContext m) -> EvalT m a -> EvalT m a #

reader :: (EvaluationContext m -> a) -> EvalT m a #

type Eval = EvalT Identity Source #

Non-transformer version of EvalT, useful in any settings where the FFI does not use any side effects during evaluation.

Evaluation errors

data EvaluationError m Source #

An evaluation error containing the evaluation context at the point the error was raised.

Constructors

EvaluationError 

Fields

Instances

Instances details
Monad m => MonadError (EvaluationError m) (EvalT m) Source # 
Instance details

Defined in Dovetail.Types

Methods

throwError :: EvaluationError m -> EvalT m a #

catchError :: EvalT m a -> (EvaluationError m -> EvalT m a) -> EvalT m a #

data EvaluationErrorType m Source #

Errors which can occur during evaluation of PureScript code.

PureScript is a typed language, and tries to prevent runtime errors. However, in the context of this interpreter, we can receive data from outside PureScript code, so it is possible that runtime errors can occur if we are not careful. This is similar to how PureScript code can fail at runtime due to errors in the FFI.

Constructors

UnknownIdent (Qualified Ident)

A name was not found in the environment

TypeMismatch Text (Value m)

The runtime representation of a value did not match the expected representation

FieldNotFound Text (Value m)

A record field did not exist in an Object value.

InexhaustivePatternMatch [Value m]

A pattern match failed to match its argument

InvalidNumberOfArguments Int Int

A pattern match received the wrong number of arguments

UnsaturatedConstructorApplication

A pattern match occurred against a partially-applied data constructor

InvalidFieldName PSString

A PureScript string which contains lone surrogates which could not be decoded. See PSString.

OtherError Text

An error occurred in a foreign function which is not tracked by any of the other error types.

Evaluation contexts

newtype EvaluationContext m Source #

An evaluation context currently consists of an evaluation stack, which is only used for debugging purposes.

The context type is parameterized by a monad m, because stack frames can contain environments, which can in turn contain Values, which may contain monadic closures. This can be useful for inspecting values or resuming execution in the event of an error.

Instances

Instances details
Monad m => MonadReader (EvaluationContext m) (EvalT m) Source # 
Instance details

Defined in Dovetail.Types

Methods

ask :: EvalT m (EvaluationContext m) #

local :: (EvaluationContext m -> EvaluationContext m) -> EvalT m a -> EvalT m a #

reader :: (EvaluationContext m -> a) -> EvalT m a #

Stack frames

data EvaluationStackFrame m Source #

A single evaluation stack frame TODO: support frames for foreign function calls

Constructors

EvaluationStackFrame 

Fields

  • frameEnv :: Env m

    The current environment in this stack frame

  • frameSource :: SourceSpan

    The source span of the expression whose evaluation created this stack frame.

  • frameExpr :: Expr Ann

    The expression whose evaluation created this stack frame.

pushStackFrame :: Monad m => Env m -> Expr Ann -> EvalT m a -> EvalT m a Source #

Create a stack frame for the evaluation of an expression, and push it onto the stack.

throwErrorWithContext :: (MonadError (EvaluationError x) m, MonadReader (EvaluationContext x) m) => EvaluationErrorType x -> m a Source #

Throw an error which captures the current execution context.

Debugging

renderValue :: RenderValueOptions -> Value m -> Text Source #

Render a Value as human-readable text.

As a general rule, apart from any closures, the rendered text should evaluate to the value you started with (when maximumDepth is not set).

data RenderValueOptions Source #

Options when rendering values as strings using renderValue.

Constructors

RenderValueOptions 

Fields

defaultTerminalRenderValueOptions :: RenderValueOptions Source #

Some sensible default rendering options for use on a terminal which supports color.