Copyright | (c) Tim Williams 2017-2019 |
---|---|
License | BSD3 |
Maintainer | info@timphilipwilliams.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
A simple expressions language with polymorphic extensible row types.
This module is the public API for Expresso.
Synopsis
- data Bind v
- = Arg v
- | RecArg [(v, v)]
- | RecWildcard
- data Env
- data Environments
- type Exp = Fix (ExpF Name Bind Type :*: K Pos)
- data ExpF v b t r
- type ExpI = Fix ((ExpF Name Bind Type :+: K Import) :*: K Pos)
- class HasValue a where
- newtype Import = Import {}
- type Name = String
- data SynonymDecl = SynonymDecl {
- synonymPos :: Pos
- synonymName :: Name
- synonymParams :: [TyVar]
- synonymBody :: Type
- newtype Thunk = Thunk {}
- data TIState
- type Type = Fix (TypeF :*: K Pos)
- pattern TForAll :: forall a. View TypeF a => [TyVar] -> a -> a
- pattern TVar :: forall a. View TypeF a => TyVar -> a
- pattern TMetaVar :: forall a. View TypeF a => MetaTv -> a
- pattern TInt :: forall a. View TypeF a => a
- pattern TDbl :: forall a. View TypeF a => a
- pattern TBool :: forall a. View TypeF a => a
- pattern TChar :: forall a. View TypeF a => a
- pattern TText :: forall a. View TypeF a => a
- pattern TFun :: forall a. View TypeF a => a -> a -> a
- pattern TList :: forall a. View TypeF a => a -> a
- pattern TRecord :: forall a. View TypeF a => a -> a
- pattern TVariant :: forall a. View TypeF a => a -> a
- pattern TRowEmpty :: forall a. View TypeF a => a
- pattern TRowExtend :: forall a. View TypeF a => Label -> a -> a -> a
- data TypeF r
- data TypeEnv
- data Value
- bind :: Environments -> Bind Name -> Maybe Type -> ExpI -> EvalM Environments
- dummyPos :: Pos
- evalFile :: HasValue a => Maybe Type -> FilePath -> IO (Either String a)
- evalFile' :: HasValue a => Environments -> Maybe Type -> FilePath -> IO (Either String a)
- evalString :: HasValue a => Maybe Type -> String -> IO (Either String a)
- evalString' :: HasValue a => Environments -> Maybe Type -> String -> IO (Either String a)
- evalWithEnv :: HasValue a => Environments -> ExpI -> IO (Either String a)
- initEnvironments :: Environments
- installBinding :: Name -> Type -> Value -> Environments -> Environments
- installSynonyms :: MonadError String m => [SynonymDecl] -> Environments -> m Environments
- uninstallSynonym :: SynonymDecl -> Environments -> Environments
- runEvalM :: EvalM a -> IO (Either String a)
- setLibDirs :: [FilePath] -> Environments -> Environments
- showType :: Type -> String
- showValue :: Value -> String
- showValue' :: Value -> IO String
- dumpTypeEnv :: Environments -> [(Name, Sigma)]
- typeOf :: ExpI -> IO (Either String Type)
- typeOfString :: String -> IO (Either String Type)
- typeOfWithEnv :: Environments -> ExpI -> IO (Either String Type)
- validate :: Type -> ExpI -> ExpI
- choice :: HasValue a => [(Name, Value -> EvalM a)] -> Value -> EvalM a
- mkRecord :: [(Name, Thunk)] -> Value
- mkStrictLam :: (Value -> EvalM Value) -> Value
- mkStrictLam2 :: (Value -> Value -> EvalM Value) -> Value
- mkStrictLam3 :: (Value -> Value -> Value -> EvalM Value) -> Value
- mkVariant :: Name -> Value -> Value
- typeMismatch :: String -> Value -> EvalM a
- unit :: Value
- (.:) :: HasValue a => Value -> Name -> EvalM a
- (.=) :: Name -> Value -> (Name, Thunk)
Documentation
Binders
Arg v | |
RecArg [(v, v)] | |
RecWildcard |
A call-by-need environment. Using a HashMap makes it easy to support record wildcards.
data Environments Source #
Type and term environments.
Pattern functor representing expressions and parameterised with
the type of variable v
, type of binder b
and the type of
type-annotation t
.
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 # | |
Foldable (ExpF v b t) Source # | |
Defined in Expresso.Syntax 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 # | |
Traversable (ExpF v b t) Source # | |
Defined in Expresso.Syntax | |
(Show v, Show r, Show t, Show (b v)) => Show (ExpF v b t r) Source # | |
class HasValue a where Source #
A class of Haskell types that can be projected from or injected into Expresso values.
Instances
HasValue Bool Source # | |
HasValue Char Source # | |
HasValue Double Source # | |
HasValue Integer Source # | |
HasValue String Source # | |
HasValue Text Source # | |
HasValue Value Source # | |
HasValue a => HasValue [(Name, a)] Source # | |
HasValue [(Name, Thunk)] Source # | |
HasValue a => HasValue [a] Source # | |
HasValue [Value] Source # | |
HasValue a => HasValue (Maybe a) Source # | |
(HasValue a, HasValue b, HasValue c, HasValue d) => HasValue (a -> b -> c -> IO d) Source # | |
(HasValue a, HasValue b, HasValue c) => HasValue (a -> b -> IO c) Source # | |
(HasValue a, HasValue b) => HasValue (a -> IO b) Source # | |
(HasValue a, HasValue b, HasValue c, HasValue d) => HasValue (a -> b -> c -> d) Source # | |
(HasValue a, HasValue b, HasValue c) => HasValue (a -> b -> c) Source # | |
(HasValue a, HasValue b) => HasValue (a -> b) Source # | |
HasValue a => HasValue (HashMap Name a) Source # | |
HasValue (HashMap Name Thunk) Source # | |
data SynonymDecl Source #
A type synonym definition.
SynonymDecl | |
|
Instances
Data SynonymDecl Source # | |
Defined in Expresso.Type 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 # | |
Defined in Expresso.Type showsPrec :: Int -> SynonymDecl -> ShowS # show :: SynonymDecl -> String # showList :: [SynonymDecl] -> ShowS # |
A potentially unevaluated value.
pattern TRowExtend :: forall a. View TypeF a => Label -> a -> a -> a Source #
Pattern functor for the syntax of types.
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 # | |
Foldable TypeF Source # | |
Defined in Expresso.Type 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 # elem :: Eq a => a -> TypeF a -> Bool # maximum :: Ord a => TypeF a -> a # minimum :: Ord a => TypeF a -> a # | |
Traversable TypeF Source # | |
Eq r => Eq (TypeF r) Source # | |
Data r => Data (TypeF r) Source # | |
Defined in Expresso.Type 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 # | |
Show r => Show (TypeF r) Source # | |
Type for an evaluated term.
bind :: Environments -> Bind Name -> Maybe Type -> ExpI -> EvalM Environments Source #
Used by the REPL to bind variables.
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.
setLibDirs :: [FilePath] -> Environments -> Environments Source #
Set the library paths used when resolving relative imports.
showValue :: Value -> String Source #
Pretty print the supplied value. This does *not* evaluate deeply.
dumpTypeEnv :: Environments -> [(Name, Sigma)] Source #
Extract type environment bindings.
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.
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.
typeMismatch :: String -> Value -> EvalM a Source #
Throw a type mismatch error.