expresso-0.1.2.0: A simple expressions language based on row types

Copyright(c) Tim Williams 2017-2019
LicenseBSD3
Maintainerinfo@timphilipwilliams.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Expresso

Description

A simple expressions language with polymorphic extensible row types.

This module is the public API for Expresso.

Synopsis

Documentation

data Bind v Source #

Binders

Constructors

Arg v 
RecArg [(v, v)] 
RecWildcard 
Instances
Show v => Show (Bind v) Source # 
Instance details

Defined in Expresso.Syntax

Methods

showsPrec :: Int -> Bind v -> ShowS #

show :: Bind v -> String #

showList :: [Bind v] -> ShowS #

data Env Source #

A call-by-need environment. Using a HashMap makes it easy to support record wildcards.

Instances
Semigroup Env Source # 
Instance details

Defined in Expresso.Eval

Methods

(<>) :: Env -> Env -> Env #

sconcat :: NonEmpty Env -> Env #

stimes :: Integral b => b -> Env -> Env #

Monoid Env Source # 
Instance details

Defined in Expresso.Eval

Methods

mempty :: Env #

mappend :: Env -> Env -> Env #

mconcat :: [Env] -> Env #

data Environments Source #

Type and term environments.

type Exp = Fix (ExpF Name Bind Type :*: K Pos) Source #

Expressions with imports resolved.

data ExpF v b t r Source #

Pattern functor representing expressions and parameterised with the type of variable v, type of binder b and the type of type-annotation t.

Constructors

EVar v 
EPrim Prim 
EApp r r 
ELam (b v) r 
EAnnLam (b v) t r 
ELet (b v) r r 
EAnnLet (b v) t r r 
EAnn r t 
Instances
Functor (ExpF v b t) Source # 
Instance details

Defined in Expresso.Syntax

Methods

fmap :: (a -> b0) -> ExpF v b t a -> ExpF v b t b0 #

(<$) :: a -> ExpF v b t b0 -> ExpF v b t a #

Foldable (ExpF v b t) Source # 
Instance details

Defined in Expresso.Syntax

Methods

fold :: Monoid m => ExpF v b t m -> m #

foldMap :: Monoid m => (a -> m) -> ExpF v b t a -> m #

foldr :: (a -> b0 -> b0) -> b0 -> ExpF v b t a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> ExpF v b t a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> ExpF v b t a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> ExpF v b t a -> b0 #

foldr1 :: (a -> a -> a) -> ExpF v b t a -> a #

foldl1 :: (a -> a -> a) -> ExpF v b t a -> a #

toList :: ExpF v b t a -> [a] #

null :: ExpF v b t a -> Bool #

length :: ExpF v b t a -> Int #

elem :: Eq a => a -> ExpF v b t a -> Bool #

maximum :: Ord a => ExpF v b t a -> a #

minimum :: Ord a => ExpF v b t a -> a #

sum :: Num a => ExpF v b t a -> a #

product :: Num a => ExpF v b t a -> a #

Traversable (ExpF v b t) Source # 
Instance details

Defined in Expresso.Syntax

Methods

traverse :: Applicative f => (a -> f b0) -> ExpF v b t a -> f (ExpF v b t b0) #

sequenceA :: Applicative f => ExpF v b t (f a) -> f (ExpF v b t a) #

mapM :: Monad m => (a -> m b0) -> ExpF v b t a -> m (ExpF v b t b0) #

sequence :: Monad m => ExpF v b t (m a) -> m (ExpF v b t a) #

(Show v, Show r, Show t, Show (b v)) => Show (ExpF v b t r) Source # 
Instance details

Defined in Expresso.Syntax

Methods

showsPrec :: Int -> ExpF v b t r -> ShowS #

show :: ExpF v b t r -> String #

showList :: [ExpF v b t r] -> ShowS #

type ExpI = Fix ((ExpF Name Bind Type :+: K Import) :*: K Pos) Source #

Expressions with imports.

class HasValue a where Source #

A class of Haskell types that can be projected from or injected into Expresso values.

Methods

proj :: Value -> EvalM a Source #

inj :: a -> Value Source #

Instances
HasValue Bool Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM Bool Source #

inj :: Bool -> Value Source #

HasValue Char Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM Char Source #

inj :: Char -> Value Source #

HasValue Double Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM Double Source #

inj :: Double -> Value Source #

HasValue Integer Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM Integer Source #

inj :: Integer -> Value Source #

HasValue String Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM String Source #

inj :: String -> Value Source #

HasValue Text Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM Text Source #

inj :: Text -> Value Source #

HasValue Value Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM Value Source #

inj :: Value -> Value Source #

HasValue a => HasValue [(Name, a)] Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM [(Name, a)] Source #

inj :: [(Name, a)] -> Value Source #

HasValue [(Name, Thunk)] Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM [(Name, Thunk)] Source #

inj :: [(Name, Thunk)] -> Value Source #

HasValue a => HasValue [a] Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM [a] Source #

inj :: [a] -> Value Source #

HasValue [Value] Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM [Value] Source #

inj :: [Value] -> Value Source #

HasValue a => HasValue (Maybe a) Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM (Maybe a) Source #

inj :: Maybe a -> Value Source #

(HasValue a, HasValue b, HasValue c, HasValue d) => HasValue (a -> b -> c -> IO d) Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM (a -> b -> c -> IO d) Source #

inj :: (a -> b -> c -> IO d) -> Value Source #

(HasValue a, HasValue b, HasValue c) => HasValue (a -> b -> IO c) Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM (a -> b -> IO c) Source #

inj :: (a -> b -> IO c) -> Value Source #

(HasValue a, HasValue b) => HasValue (a -> IO b) Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM (a -> IO b) Source #

inj :: (a -> IO b) -> Value Source #

(HasValue a, HasValue b, HasValue c, HasValue d) => HasValue (a -> b -> c -> d) Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM (a -> b -> c -> d) Source #

inj :: (a -> b -> c -> d) -> Value Source #

(HasValue a, HasValue b, HasValue c) => HasValue (a -> b -> c) Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM (a -> b -> c) Source #

inj :: (a -> b -> c) -> Value Source #

(HasValue a, HasValue b) => HasValue (a -> b) Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM (a -> b) Source #

inj :: (a -> b) -> Value Source #

HasValue a => HasValue (HashMap Name a) Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM (HashMap Name a) Source #

inj :: HashMap Name a -> Value Source #

HasValue (HashMap Name Thunk) Source # 
Instance details

Defined in Expresso.Eval

newtype Import Source #

An import file path.

Constructors

Import 

Fields

type Name = String Source #

A string representing a unique name.

data SynonymDecl Source #

A type synonym definition.

Constructors

SynonymDecl 

Fields

Instances
Data SynonymDecl Source # 
Instance details

Defined in Expresso.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SynonymDecl -> c SynonymDecl #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SynonymDecl #

toConstr :: SynonymDecl -> Constr #

dataTypeOf :: SynonymDecl -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SynonymDecl) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SynonymDecl) #

gmapT :: (forall b. Data b => b -> b) -> SynonymDecl -> SynonymDecl #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SynonymDecl -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SynonymDecl -> r #

gmapQ :: (forall d. Data d => d -> u) -> SynonymDecl -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SynonymDecl -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SynonymDecl -> m SynonymDecl #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SynonymDecl -> m SynonymDecl #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SynonymDecl -> m SynonymDecl #

Show SynonymDecl Source # 
Instance details

Defined in Expresso.Type

newtype Thunk Source #

A potentially unevaluated value.

Constructors

Thunk 

Fields

Instances
Show Thunk Source # 
Instance details

Defined in Expresso.Eval

Methods

showsPrec :: Int -> Thunk -> ShowS #

show :: Thunk -> String #

showList :: [Thunk] -> ShowS #

HasValue [(Name, Thunk)] Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM [(Name, Thunk)] Source #

inj :: [(Name, Thunk)] -> Value Source #

HasValue (HashMap Name Thunk) Source # 
Instance details

Defined in Expresso.Eval

data TIState Source #

Internal state of the inference engine.

type Type = Fix (TypeF :*: K Pos) Source #

Type syntax annotated with source position.

pattern TForAll :: forall a. View TypeF a => [TyVar] -> a -> a Source #

pattern TVar :: forall a. View TypeF a => TyVar -> a Source #

pattern TMetaVar :: forall a. View TypeF a => MetaTv -> a Source #

pattern TInt :: forall a. View TypeF a => a Source #

pattern TDbl :: forall a. View TypeF a => a Source #

pattern TBool :: forall a. View TypeF a => a Source #

pattern TChar :: forall a. View TypeF a => a Source #

pattern TText :: forall a. View TypeF a => a Source #

pattern TFun :: forall a. View TypeF a => a -> a -> a Source #

pattern TList :: forall a. View TypeF a => a -> a Source #

pattern TRecord :: forall a. View TypeF a => a -> a Source #

pattern TVariant :: forall a. View TypeF a => a -> a Source #

pattern TRowEmpty :: forall a. View TypeF a => a Source #

pattern TRowExtend :: forall a. View TypeF a => Label -> a -> a -> a Source #

data TypeF r Source #

Pattern functor for the syntax of types.

Constructors

TForAllF [TyVar] r 
TVarF TyVar 
TMetaVarF MetaTv 
TSynonymF Name [r] 
TIntF 
TDblF 
TBoolF 
TCharF 
TTextF 
TFunF r r 
TListF r 
TRecordF r 
TVariantF r 
TRowEmptyF 
TRowExtendF Label r r 
Instances
Functor TypeF Source # 
Instance details

Defined in Expresso.Type

Methods

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

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

Foldable TypeF Source # 
Instance details

Defined in Expresso.Type

Methods

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

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

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

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

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

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

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

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

toList :: TypeF a -> [a] #

null :: TypeF a -> Bool #

length :: TypeF a -> Int #

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

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

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

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

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

Traversable TypeF Source # 
Instance details

Defined in Expresso.Type

Methods

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

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

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

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

Eq r => Eq (TypeF r) Source # 
Instance details

Defined in Expresso.Type

Methods

(==) :: TypeF r -> TypeF r -> Bool #

(/=) :: TypeF r -> TypeF r -> Bool #

Data r => Data (TypeF r) Source # 
Instance details

Defined in Expresso.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeF r -> c (TypeF r) #

gunfold :: (forall b r0. Data b => c (b -> r0) -> c r0) -> (forall r1. r1 -> c r1) -> Constr -> c (TypeF r) #

toConstr :: TypeF r -> Constr #

dataTypeOf :: TypeF r -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TypeF r)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TypeF r)) #

gmapT :: (forall b. Data b => b -> b) -> TypeF r -> TypeF r #

gmapQl :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> TypeF r -> r0 #

gmapQr :: (r' -> r0 -> r0) -> r0 -> (forall d. Data d => d -> r') -> TypeF r -> r0 #

gmapQ :: (forall d. Data d => d -> u) -> TypeF r -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeF r -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeF r -> m (TypeF r) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeF r -> m (TypeF r) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeF r -> m (TypeF r) #

Ord r => Ord (TypeF r) Source # 
Instance details

Defined in Expresso.Type

Methods

compare :: TypeF r -> TypeF r -> Ordering #

(<) :: TypeF r -> TypeF r -> Bool #

(<=) :: TypeF r -> TypeF r -> Bool #

(>) :: TypeF r -> TypeF r -> Bool #

(>=) :: TypeF r -> TypeF r -> Bool #

max :: TypeF r -> TypeF r -> TypeF r #

min :: TypeF r -> TypeF r -> TypeF r #

Show r => Show (TypeF r) Source # 
Instance details

Defined in Expresso.Type

Methods

showsPrec :: Int -> TypeF r -> ShowS #

show :: TypeF r -> String #

showList :: [TypeF r] -> ShowS #

data TypeEnv Source #

The type environment.

Instances
Semigroup TypeEnv Source # 
Instance details

Defined in Expresso.Type

Monoid TypeEnv Source # 
Instance details

Defined in Expresso.Type

data Value Source #

Type for an evaluated term.

Constructors

VLam !(Thunk -> EvalM Value) 
VInt !Integer 
VDbl !Double 
VBool !Bool 
VChar !Char 
VText !Text 
VList ![Value] 
VRecord !(HashMap Label Thunk) 
VVariant !Label !Thunk 
Instances
HasValue Value Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM Value Source #

inj :: Value -> Value Source #

HasValue [Value] Source # 
Instance details

Defined in Expresso.Eval

Methods

proj :: Value -> EvalM [Value] Source #

inj :: [Value] -> Value Source #

bind :: Environments -> Bind Name -> Maybe Type -> ExpI -> EvalM Environments Source #

Used by the REPL to bind variables.

dummyPos :: Pos Source #

A useless source position.

evalFile :: HasValue a => Maybe Type -> FilePath -> IO (Either String a) Source #

Evaluate the contents of the supplied file path; and optionally validate using a supplied type (schema).

evalFile' :: HasValue a => Environments -> Maybe Type -> FilePath -> IO (Either String a) Source #

Evaluate the contents of the supplied file path; and optionally validate using a supplied type (schema). NOTE: This version also takes a term environment and a type environment so that foreign functions and their types can be installed respectively.

evalString :: HasValue a => Maybe Type -> String -> IO (Either String a) Source #

Parse an expression and evaluate it; optionally validate using a supplied type (schema).

evalString' :: HasValue a => Environments -> Maybe Type -> String -> IO (Either String a) Source #

Parse an expression and evaluate it; optionally validate using a supplied type (schema). NOTE: This version also takes a term environment and a type environment so that foreign functions and their types can be installed respectively.

evalWithEnv :: HasValue a => Environments -> ExpI -> IO (Either String a) Source #

Evaluate an expression using the supplied type and term environments.

initEnvironments :: Environments Source #

Empty initial environments.

installBinding :: Name -> Type -> Value -> Environments -> Environments Source #

Install a binding using the supplied name, type and term. Useful for extending the set of built-in functions.

installSynonyms :: MonadError String m => [SynonymDecl] -> Environments -> m Environments Source #

Install the supplied type synonym declarations.

uninstallSynonym :: SynonymDecl -> Environments -> Environments Source #

Used by the REPL, deletes any previous definition.

runEvalM :: EvalM a -> IO (Either String a) Source #

Run the EvalM evaluation computation.

setLibDirs :: [FilePath] -> Environments -> Environments Source #

Set the library paths used when resolving relative imports.

showType :: Type -> String Source #

Pretty print the supplied type.

showValue :: Value -> String Source #

Pretty print the supplied value. This does *not* evaluate deeply.

showValue' :: Value -> IO String Source #

Pretty print the supplied value. This evaluates deeply.

dumpTypeEnv :: Environments -> [(Name, Sigma)] Source #

Extract type environment bindings.

typeOf :: ExpI -> IO (Either String Type) Source #

Query the type of an expression.

typeOfString :: String -> IO (Either String Type) Source #

Parse an expression and query its type.

typeOfWithEnv :: Environments -> ExpI -> IO (Either String Type) Source #

Query the type of an expression using the supplied type environment.

validate :: Type -> ExpI -> ExpI Source #

Add a validating type signature section to the supplied expression.

choice :: HasValue a => [(Name, Value -> EvalM a)] -> Value -> EvalM a Source #

Convenience for implementing proj for a sum type.

mkRecord :: [(Name, Thunk)] -> Value Source #

Convenience constructor for a record value.

mkStrictLam :: (Value -> EvalM Value) -> Value Source #

Make a strict Expresso lambda value (forced arguments) from a Haskell function (on Expresso values).

mkStrictLam2 :: (Value -> Value -> EvalM Value) -> Value Source #

As mkStrictLam, but accepts Haskell functions with two curried arguments.

mkStrictLam3 :: (Value -> Value -> Value -> EvalM Value) -> Value Source #

As mkStrictLam, but accepts Haskell functions with three curried arguments.

mkVariant :: Name -> Value -> Value Source #

Convenience constructor for a variant value.

typeMismatch :: String -> Value -> EvalM a Source #

Throw a type mismatch error.

unit :: Value Source #

Unit value. Equivalent to () in Haskell.

(.:) :: HasValue a => Value -> Name -> EvalM a Source #

Project out a record field, fail with a type mismatch if it is not present.

(.=) :: Name -> Value -> (Name, Thunk) Source #

Pair up a field name and a value. Intended to be used with mkRecord or mkVariant.