Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides the types and the functions necessary for defining funcons. The package provides a large collection of predefined funcons in Funcons.Core. Module Funcons.Tools provides functions for creating executables.
Synopsis
- data Funcons
- = FName Name
- | FApp Name [Funcons]
- | FSet [Funcons]
- | FMap [Funcons]
- | FBinding Funcons [Funcons]
- | FValue Values
- | FSortSeq Funcons SeqSortOp
- | FSortPower Funcons Funcons
- | FSortUnion Funcons Funcons
- | FSortInter Funcons Funcons
- | FSortComplement Funcons
- | FSortComputes Funcons
- | FSortComputesFrom Funcons Funcons
- type Values = Values Funcons
- type Types = Types Funcons
- type ComputationTypes = ComputationTypes Funcons
- data SeqSortOp
- applyFuncon :: Name -> [Funcons] -> Funcons
- app0_ :: ([Funcons] -> Funcons) -> Funcons
- app1_ :: ([Funcons] -> Funcons) -> Funcons -> Funcons
- app2_ :: ([Funcons] -> Funcons) -> Funcons -> Funcons -> Funcons
- app3_ :: ([Funcons] -> Funcons) -> Funcons -> Funcons -> Funcons -> Funcons
- set_ :: [Funcons] -> Funcons
- vec_ :: [Values] -> Funcons
- env_fromlist_ :: [(String, Funcons)] -> Funcons
- null__ :: Values t
- int_ :: Int -> Funcons
- bool_ :: Bool -> Funcons
- bool__ :: Bool -> Values
- list__ :: [Values] -> Values
- vector__ :: [Values] -> Values
- tuple__ :: [Values] -> Values
- char_ :: Char -> Funcons
- char__ :: Char -> Values
- nat_ :: Int -> Funcons
- float_ :: Double -> Funcons
- ieee_float_32_ :: Float -> Funcons
- ieee_float_64_ :: Double -> Funcons
- string_ :: String -> Funcons
- string__ :: String -> Values
- atom_ :: String -> Funcons
- values_ :: Funcons
- integers_ :: Funcons
- vectors_ :: Types -> Funcons
- type_ :: Types -> Funcons
- ty_star :: Funcons -> Funcons
- ty_plus :: Funcons -> Funcons
- ty_opt :: Funcons -> Funcons
- ty_union :: Funcons -> Funcons -> Funcons
- ty_neg :: Funcons -> Funcons
- ty_inter :: Funcons -> Funcons -> Funcons
- ty_power :: Funcons -> Funcons -> Funcons
- showValues :: Values -> String
- showValuesSeq :: [Values] -> String
- showFuncons :: Funcons -> String
- showFunconsSeq :: [Funcons] -> String
- showTypes :: Types -> String
- showTerms :: FTerm -> String
- showOp :: SeqSortOp -> String
- isVal :: Funcons -> Bool
- isInt :: Funcons -> Bool
- isNat :: Funcons -> Bool
- isList :: Funcons -> Bool
- isMap :: Funcons -> Bool
- isType :: Funcons -> Bool
- isVec :: Funcons -> Bool
- isChar :: Funcons -> Bool
- isTup :: p -> Bool
- isString :: Funcons -> Bool
- isString_ :: HasValues t => Values t -> Bool
- unString :: HasValues t => Values t -> String
- downcastValue :: Funcons -> Values
- downcastType :: Funcons -> Types
- downcastValueType :: Values t -> Types t
- upcastNaturals :: Values t -> Values t
- upcastIntegers :: Values t -> Values t
- upcastRationals :: Values t -> Values t
- upcastCharacter :: HasValues t => Values t -> Maybe Char
- data EvalFunction
- data Strictness
- type StrictFuncon = [Values] -> Rewrite Rewritten
- type PartiallyStrictFuncon = NonStrictFuncon
- type NonStrictFuncon = [Funcons] -> Rewrite Rewritten
- type ValueOp = StrictFuncon
- type NullaryFuncon = Rewrite Rewritten
- type FunconLibrary = Map Name EvalFunction
- libEmpty :: FunconLibrary
- libUnion :: FunconLibrary -> FunconLibrary -> FunconLibrary
- libOverride :: FunconLibrary -> FunconLibrary -> FunconLibrary
- libUnions :: [FunconLibrary] -> FunconLibrary
- libOverrides :: [FunconLibrary] -> FunconLibrary
- libFromList :: [(Name, EvalFunction)] -> FunconLibrary
- library :: FunconLibrary
- fromNullaryValOp :: ([Funcons] -> Funcons) -> ([OpExpr Funcons] -> OpExpr Funcons) -> EvalFunction
- fromValOp :: ([Funcons] -> Funcons) -> ([OpExpr Funcons] -> OpExpr Funcons) -> EvalFunction
- fromSeqValOp :: ([Funcons] -> Funcons) -> ([OpExpr Funcons] -> OpExpr Funcons) -> EvalFunction
- data MSOS a
- data Rewrite a
- data Rewritten
- rewriteTo :: Funcons -> Rewrite Rewritten
- rewriteSeqTo :: [Funcons] -> Rewrite Rewritten
- stepTo :: Funcons -> MSOS StepRes
- stepSeqTo :: [Funcons] -> MSOS StepRes
- compstep :: MSOS StepRes -> Rewrite Rewritten
- rewritten :: Values -> Rewrite Rewritten
- premiseStep :: Funcons -> MSOS StepRes
- premiseEval :: ([Values] -> Rewrite Rewritten) -> (MSOS StepRes -> MSOS StepRes) -> Funcons -> Rewrite Rewritten
- norule :: Funcons -> Rewrite a
- sortErr :: Funcons -> String -> Rewrite a
- partialOp :: Funcons -> String -> Rewrite a
- type Inherited = Map Name [Values]
- getInh :: Name -> MSOS [Values]
- withInh :: Name -> [Values] -> MSOS a -> MSOS a
- type Mutable = Map Name Values
- getMut :: Name -> MSOS Values
- putMut :: Name -> Values -> MSOS ()
- type Output = Map Name [Values]
- writeOut :: Name -> [Values] -> MSOS ()
- readOut :: Name -> MSOS a -> MSOS (a, [Values])
- type Control = Map Name (Maybe Values)
- raiseSignal :: Name -> Values -> MSOS ()
- receiveSignals :: [Name] -> MSOS a -> MSOS (a, [Maybe Values])
- type Input m = Map Name ([[Values]], Maybe (m Funcons))
- withExtraInput :: Name -> [Values] -> MSOS a -> MSOS a
- withExactInput :: Name -> [Values] -> MSOS a -> MSOS a
- data FTerm
- = TVar MetaVar
- | TName Name
- | TApp Name [FTerm]
- | TSeq [FTerm]
- | TSet [FTerm]
- | TMap [FTerm]
- | TBinding FTerm FTerm
- | TFuncon Funcons
- | TSortSeq FTerm SeqSortOp
- | TSortPower FTerm FTerm
- | TSortUnion FTerm FTerm
- | TSortInter FTerm FTerm
- | TSortComplement FTerm
- | TSortComputes FTerm
- | TSortComputesFrom FTerm FTerm
- | TAny
- type Env = Map MetaVar Levelled
- emptyEnv :: Map k a
- fvalues :: [Values] -> [Funcons]
- rewriteTermTo :: FTerm -> Env -> Rewrite Rewritten
- stepTermTo :: FTerm -> Env -> MSOS StepRes
- premise :: FTerm -> [FPattern] -> Env -> MSOS Env
- withInhTerm :: Name -> FTerm -> Env -> MSOS a -> MSOS a
- getInhPatt :: Name -> [VPattern] -> Env -> MSOS Env
- putMutTerm :: Name -> FTerm -> Env -> MSOS ()
- getMutPatt :: Name -> VPattern -> Env -> MSOS Env
- writeOutTerm :: Name -> FTerm -> Env -> MSOS ()
- readOutPatt :: Name -> VPattern -> MSOS Env -> MSOS Env
- receiveSignalPatt :: Maybe Values -> Maybe VPattern -> Env -> MSOS Env
- raiseTerm :: Name -> FTerm -> Env -> MSOS ()
- matchInput :: Name -> VPattern -> Env -> MSOS Env
- withExtraInputTerms :: Name -> [FTerm] -> Env -> MSOS a -> MSOS a
- withExactInputTerms :: Name -> [FTerm] -> Env -> MSOS a -> MSOS a
- withControlTerm :: Name -> Maybe FTerm -> Env -> MSOS a -> MSOS a
- getControlPatt :: Name -> Maybe VPattern -> Env -> MSOS Env
- evalRules :: [Rewrite Rewritten] -> [MSOS StepRes] -> Rewrite Rewritten
- stepRules :: [IException] -> [MSOS StepRes] -> MSOS StepRes
- rewriteRules :: [Rewrite Rewritten] -> Rewrite Rewritten
- data SideCondition
- sideCondition :: SideCondition -> Env -> Rewrite Env
- lifted_sideCondition :: SideCondition -> Env -> MSOS Env
- data VPattern
- data FPattern
- data TPattern
- = TPWildCard
- | TPVar MetaVar
- | TPSeqVar MetaVar SeqSortOp
- | TPLit FTerm
- | TPComputes TPattern
- | TPComputesFrom TPattern TPattern
- | TPADT Name [TPattern]
- vsMatch :: [Values] -> [VPattern] -> Env -> Rewrite Env
- fsMatch :: [Funcons] -> [FPattern] -> Env -> Rewrite Env
- f2vPattern :: FPattern -> VPattern
- lifted_vsMatch :: [Values] -> [VPattern] -> Env -> MSOS Env
- lifted_fsMatch :: [Funcons] -> [FPattern] -> Env -> MSOS Env
- pat2term :: FPattern -> FTerm
- vpat2term :: VPattern -> FTerm
- typat2term :: TPattern -> FTerm
- envRewrite :: MetaVar -> Env -> Rewrite Env
- envStore :: MetaVar -> FTerm -> Env -> Rewrite Env
- lifted_envRewrite :: MetaVar -> Env -> MSOS Env
- lifted_envStore :: MetaVar -> FTerm -> Env -> MSOS Env
- type TypeEnv = Map MetaVar TyAssoc
- data TyAssoc
- class HasTypeVar a where
- subsTypeVar :: TypeEnv -> a -> a
- subsTypeVarWildcard :: Maybe FTerm -> TypeEnv -> a -> a
- limitedSubsTypeVar :: HasTypeVar a => Set MetaVar -> TypeEnv -> a -> a
- limitedSubsTypeVarWildcard :: HasTypeVar a => Set MetaVar -> Maybe FTerm -> TypeEnv -> a -> a
- rewriteType :: Name -> [Values] -> Rewrite Rewritten
- type EntityDefaults = [EntityDefault]
- data EntityDefault
- = DefMutable Name Funcons
- | DefInherited Name Funcons
- | DefOutput Name
- | DefControl Name
- | DefInput Name
- type TypeRelation = Map Name DataTypeMembers
- type TypeParam = (Maybe MetaVar, Maybe SeqSortOp, FTerm)
- data DataTypeMembers = DataTypeMemberss Name [TPattern] [DataTypeAltt]
- data DataTypeAltt
- = DataTypeInclusionn FTerm
- | DataTypeMemberConstructor Name [FTerm] (Maybe [TPattern])
- typeLookup :: Name -> TypeRelation -> Maybe DataTypeMembers
- typeEnvUnion :: TypeRelation -> TypeRelation -> TypeRelation
- typeEnvUnions :: [TypeRelation] -> TypeRelation
- typeEnvFromList :: [(Name, DataTypeMembers)] -> TypeRelation
- emptyTypeRelation :: TypeRelation
Funcon representation
Internal representation of funcon terms.
The generic constructors FName
and FApp
use names to represent
nullary funcons and applications of funcons to other terms.
Funcon terms are easily created using applyFuncon
or via
the smart constructors exported by Funcons.Core.
type ComputationTypes = ComputationTypes Funcons Source #
Representation of builtin types.
Postfix operators for specifying sequences.
applyFuncon :: Name -> [Funcons] -> Funcons Source #
Build funcon terms by applying a funcon name to `zero or more' funcon terms. This function is useful for defining smart constructors, e,g,
handle_thrown_ :: [Funcons] -> Funcons handle_thrown_ = applyFuncon "handle-thrown"
or alternatively,
handle_thrown_ :: Funcons -> Funcons -> Funcons handle_thrown_ x y = applyFuncon "handle-thrown" [x,y]
Smart construction of funcon terms
Funcon terms
env_fromlist_ :: [(String, Funcons)] -> Funcons Source #
Create an environment from a list of bindings (String to Values) This function has been introduced for easy expression of the semantics of builtin identifiers
Values
ieee_float_32_ :: Float -> Funcons Source #
ieee_float_64_ :: Double -> Funcons Source #
Types
type_ :: Types -> Funcons Source #
Creates a tuple of funcon terms. tuple_ :: [Funcons] -> Funcons tuple_ = FTuple
Pretty-print funcon terms
Is a funcon term a certain value?
Up and downcasting between funcon terms
downcastValue :: Funcons -> Values Source #
downcastType :: Funcons -> Types Source #
Returns the unicode representation of an assci value. Otherwise it returns the original value.
Attempt to downcast a funcon term to a value.
downcastValueType :: Values t -> Types t #
upcastNaturals :: Values t -> Values t #
Returns the natural representation of a value if it is a subtype. Otherwise it returns the original value.
upcastIntegers :: Values t -> Values t #
Returns the integer representation of a value if it is a subtype. Otherwise it returns the original value.
upcastRationals :: Values t -> Values t #
Returns the rational representation of a value if it is a subtype. Otherwise it returns the original value.
Evaluation functions
data EvalFunction Source #
Evaluation functions capture the operational behaviour of a funcon.
Evaluation functions come in multiple flavours, each with a different
treatment of the arguments of the funcon.
Before the application of an evaluation funcon, any argument may be
evaluated, depending on the Strictness
of the argument.
NonStrictFuncon NonStrictFuncon | Funcons for which arguments are not evaluated. |
StrictFuncon StrictFuncon | Strict funcons whose arguments are evaluated. |
PartiallyStrictFuncon [Strictness] Strictness NonStrictFuncon | Funcons for which some arguments are evaluated. |
ValueOp ValueOp | Synonym for |
NullaryFuncon NullaryFuncon | Funcons without any arguments. |
data Strictness Source #
Denotes whether an argument of a funcon should be evaluated or not.
type StrictFuncon = [Values] -> Rewrite Rewritten Source #
Type synonym for the evaluation function of strict funcons.
The evaluation function of a StrictFuncon
receives fully evaluated arguments.
type PartiallyStrictFuncon = NonStrictFuncon Source #
Type synonym for the evaluation function of non-strict funcons.
type NonStrictFuncon = [Funcons] -> Rewrite Rewritten Source #
Type synonym for the evaluation function of fully non-strict funcons.
type ValueOp = StrictFuncon Source #
Type synonym for value operations.
type NullaryFuncon = Rewrite Rewritten Source #
Type synonym for the evaluation functions of nullary funcons.
Funcon libraries
type FunconLibrary = Map Name EvalFunction Source #
A funcon library maps funcon names to their evaluation functions.
libEmpty :: FunconLibrary Source #
Creates an empty FunconLibrary
.
libUnion :: FunconLibrary -> FunconLibrary -> FunconLibrary Source #
Unites two FunconLibrary
s.
libOverride :: FunconLibrary -> FunconLibrary -> FunconLibrary Source #
Right-based union of FunconLibrary
s
libUnions :: [FunconLibrary] -> FunconLibrary Source #
Unites a list of FunconLibrary
s.
libOverrides :: [FunconLibrary] -> FunconLibrary Source #
Right-based union of list of FunconLibrary
s
libFromList :: [(Name, EvalFunction)] -> FunconLibrary Source #
Creates a FunconLibrary
from a list.
library :: FunconLibrary Source #
A funcon library with funcons for builtin types.
fromNullaryValOp :: ([Funcons] -> Funcons) -> ([OpExpr Funcons] -> OpExpr Funcons) -> EvalFunction Source #
fromValOp :: ([Funcons] -> Funcons) -> ([OpExpr Funcons] -> OpExpr Funcons) -> EvalFunction Source #
fromSeqValOp :: ([Funcons] -> Funcons) -> ([OpExpr Funcons] -> OpExpr Funcons) -> EvalFunction Source #
Implicit & modular propagation of entities
Monadic type for the propagation of semantic entities and meta-information
on the evaluation of funcons. The meta-information includes a library
of funcons (see FunconLibrary
), a typing environment (see TypeRelation
),
runtime options, etc.
The semantic entities are divided into five classes:
- inherited entities, propagated similar to values of a reader monad.
- mutable entities, propagated similar to values of a state monad.
- output entities, propagation similar to values of a write monad.
- control entities, similar to output entities except only a single control signal can be emitted at once (signals do not form a monoid).
- input entities, propagated like values of a state monad, but access like
value of a reader monad. This package provides simulated input/outout
and real interaction via the
IO
monad. See Funcons.Tools.
For each entity class a map is propagated, mapping entity names to values. This enables modular access to the entities.
Monadic type for the implicit propagation of meta-information on
the evaluation of funcon terms (no semantic entities).
It is separated from MSOS
to ensure
that side-effects (access or modification of semantic entities) can not
occur during syntactic rewrites.
After a term is fully rewritten it is either a value or a term that requires a computational step to proceed. This types forms the interface between syntactic rewrites and computational steps.
Helpers to create rewrites & step rules
rewriteTo :: Funcons -> Rewrite Rewritten Source #
Yield a funcon term as the result of a syntactic rewrite.
This function must be used instead of return
.
The given term is fully rewritten.
rewriteSeqTo :: [Funcons] -> Rewrite Rewritten Source #
Yield a sequence of funcon terms as the result of a rewrite. This is only valid when all terms rewrite to a value
stepTo :: Funcons -> MSOS StepRes Source #
Yield a funcon term as the result of an MSOS
computation.
This function must be used instead of return
.
stepSeqTo :: [Funcons] -> MSOS StepRes Source #
Yield a sequence of funcon terms as the result of a computation. This is only valid when all terms rewrite to a value
compstep :: MSOS StepRes -> Rewrite Rewritten Source #
Yield an MSOS
computation as a fully rewritten term.
This function must be used in order to access entities in the definition
of funcons.
premiseStep :: Funcons -> MSOS StepRes Source #
premiseEval :: ([Values] -> Rewrite Rewritten) -> (MSOS StepRes -> MSOS StepRes) -> Funcons -> Rewrite Rewritten Source #
Execute a premise as either a rewrite or a step. Depending on whether only rewrites are necessary to yield a value, or whether a computational step is necessary, a different continuation is applied (first and second argument). Example usage:
stepScope :: NonStrictFuncon --strict in first argument stepScope [FValue (Map e1), x] = premiseEval x rule1 step1 where rule1 v = rewritten v step1 stepX = do Map e0 <- getInh "environment" x' <- withInh "environment" (Map (union e1 e0)) stepX stepTo (scope_ [FValue e1, x'])
norule :: Funcons -> Rewrite a Source #
Yields an error signaling that no rule is applicable. The funcon term argument may be used to provide a useful error message.
sortErr :: Funcons -> String -> Rewrite a Source #
Yields an error signaling that a sort error was encountered.
These errors render a rule inapplicable and a next rule is attempted
when a backtracking procedure like evalRules
is applied.
The funcon term argument may be used to provide a useful error message.
partialOp :: Funcons -> String -> Rewrite a Source #
Yields an error signaling that a partial operation was applied
to a value outside of its domain (e.g. division by zero).
These errors render a rule inapplicable and a next rule is attempted
when a backtracking procedure like evalRules
is applied.
The funcon term argument may be used to provide a useful error message.
Entities and entity access
withInh :: Name -> [Values] -> MSOS a -> MSOS a Source #
Set the value of an inherited entity.
The new value is only set for MSOS
computation given as a third argument.
readOut :: Name -> MSOS a -> MSOS (a, [Values]) Source #
Read the values of a certain output entity. The output is obtained
from the MSOS
computation given as a second argument.
raiseSignal :: Name -> Values -> MSOS () Source #
Signal a value of some control entity.
receiveSignals :: [Name] -> MSOS a -> MSOS (a, [Maybe Values]) Source #
Receive the value of a control entity from a given MSOS
computation.
type Input m = Map Name ([[Values]], Maybe (m Funcons)) Source #
A map storing the values of input entities.
withExtraInput :: Name -> [Values] -> MSOS a -> MSOS a Source #
Provides extra values to a certain input entity, available
to be consumed by the given MSOS
computation argument.
withExactInput :: Name -> [Values] -> MSOS a -> MSOS a Source #
Provides an exact amount of input for some input entity,
that is to be completely consumed by the given MSOS
computation.
If less output is consumed a 'insufficient input consumed' exception
is thrown.
CBS compilation
This section describes functions that extend the interpreter with backtracking and pattern-matching facilities. These functions are developed for compiling CBS funcon specifications to Haskell. To read about CBS we refer to JLAMP2016. The functions can be used for manual development of funcons, although this is not recommended.
Funcon representation with meta-variables
Funcon term representation identical to Funcons
,
but with meta-variables.
TVar MetaVar | |
TName Name | |
TApp Name [FTerm] | |
TSeq [FTerm] | |
TSet [FTerm] | |
TMap [FTerm] | |
TBinding FTerm FTerm | |
TFuncon Funcons | |
TSortSeq FTerm SeqSortOp | |
TSortPower FTerm FTerm | |
TSortUnion FTerm FTerm | |
TSortInter FTerm FTerm | |
TSortComplement FTerm | |
TSortComputes FTerm | |
TSortComputesFrom FTerm FTerm | |
TAny |
The empty substitution environment. Bindings are inserted by pattern-matching.
Defining rules
rewriteTermTo :: FTerm -> Env -> Rewrite Rewritten Source #
Variant of rewriteTo
that applies substitution.
premise :: FTerm -> [FPattern] -> Env -> MSOS Env Source #
Variant of premiseStep
that applies substitute and pattern-matching.
Entity access
withInhTerm :: Name -> FTerm -> Env -> MSOS a -> MSOS a Source #
Variant of withInh
that performs substitution.
getInhPatt :: Name -> [VPattern] -> Env -> MSOS Env Source #
Version of getInh
that applies pattern-matching.
getMutPatt :: Name -> VPattern -> Env -> MSOS Env Source #
Variant of getMut
that performs pattern-matching.
writeOutTerm :: Name -> FTerm -> Env -> MSOS () Source #
Variant of writeOut
that applies substitution.
readOutPatt :: Name -> VPattern -> MSOS Env -> MSOS Env Source #
Variant of readOut
that performs pattern-matching.
receiveSignalPatt :: Maybe Values -> Maybe VPattern -> Env -> MSOS Env Source #
Variant of receiveSignal
that performs pattern-matching.
raiseTerm :: Name -> FTerm -> Env -> MSOS () Source #
Variant of raiseSignal
that applies substitution.
withExtraInputTerms :: Name -> [FTerm] -> Env -> MSOS a -> MSOS a Source #
Variant of withExtraInput
that performs substitution.
withExactInputTerms :: Name -> [FTerm] -> Env -> MSOS a -> MSOS a Source #
Variant of withExactInput
that performs substitution.
getControlPatt :: Name -> Maybe VPattern -> Env -> MSOS Env Source #
Version of getControl
that applies pattern-matching.
Backtracking
evalRules :: [Rewrite Rewritten] -> [MSOS StepRes] -> Rewrite Rewritten Source #
Function evalRules
implements a backtracking procedure.
It receives two lists of alternatives as arguments, the first
containing all rewrite rules of a funcon and the second all step rules.
The first successful rule is the only rule fully executed.
A rule is unsuccessful if it throws an exception. Some of these
exceptions (partial operation, sort error or pattern-match failure)
cause the next alternative to be tried. Other exceptions
(different forms of internal errors) will be propagated further.
All side-effects of attempting a rule are discarded when a rule turns
out not to be applicable.
First all rewrite rules are attempted, therefore avoiding performing a step until it is absolutely necessary. This is a valid strategy as valid (I)MSOS rules can be considered in any order.
When no rules are successfully executed to completetion a 'no rule exception' is thrown.
data SideCondition Source #
CSB supports five kinds of side conditions.
Each of the side conditions are explained below.
When a side condition is not accepted an exception is thrown that
is caught by the backtrackign procedure evalRules
.
A value is a ground value if it is not a thunk (and not composed out of
thunks).
SCEquality FTerm FTerm | T1 == T2. Accepted only when T1 and T2 rewrite to equal ground values. |
SCInequality FTerm FTerm | T1 =/= T2. Accepted only when T1 and T2 rewrite to unequal ground values. |
SCIsInSort FTerm FTerm | T1 : T2. Accepted only when T2 rewrites to a type and T1 rewrites to a value of that type. |
SCNotInSort FTerm FTerm | ~(T1 : T2). Accepted only when T2 rewrites to a type and T1 rewrites to a value not of that type. |
SCPatternMatch FTerm [VPattern] | T = P. Accepted only when T rewrites to a value that matches the pattern P. (May produce new bindings in |
sideCondition :: SideCondition -> Env -> Rewrite Env Source #
Executes a side condition, given an Env
environment, throwing possible exceptions, and
possibly extending the environment.
lifted_sideCondition :: SideCondition -> Env -> MSOS Env Source #
Variant of sideCondition
that is lifted into the MSOS
monad.
Pattern Matching
Patterns for matching values (Values
).
PADT Name [VPattern] | |
VPWildCard | |
VPMetaVar MetaVar | |
VPAnnotated VPattern FTerm | |
VPSeqVar MetaVar SeqSortOp | |
VPLit Values | |
VPType TPattern |
Patterns for matching funcon terms (FTerm
).
TPWildCard | |
TPVar MetaVar | |
TPSeqVar MetaVar SeqSortOp | |
TPLit FTerm | |
TPComputes TPattern | |
TPComputesFrom TPattern TPattern | |
TPADT Name [TPattern] |
vsMatch :: [Values] -> [VPattern] -> Env -> Rewrite Env Source #
Matching values with value patterns patterns.
If the list of patterns is a singleton list, then vsMatch
attempts
to match the values as a tuple against the pattern as well.
fsMatch :: [Funcons] -> [FPattern] -> Env -> Rewrite Env Source #
Match a sequence of terms to a sequence of patterns.
f2vPattern :: FPattern -> VPattern Source #
typat2term :: TPattern -> FTerm Source #
Meta-environment
envRewrite :: MetaVar -> Env -> Rewrite Env Source #
Apply as many rewrites as possible to the term bound to the given variable in the meta-environment
Type substitution
class HasTypeVar a where Source #
Used for replacing meta-variables T
in pattern annotations `P:T` with
the type to which T
is bound in some type-environment (if any)
subsTypeVar :: TypeEnv -> a -> a Source #
subsTypeVarWildcard :: Maybe FTerm -> TypeEnv -> a -> a Source #
Instances
HasTypeVar FTerm Source # | |
Defined in Funcons.TypeSubstitution | |
HasTypeVar VPattern Source # | |
Defined in Funcons.TypeSubstitution | |
HasTypeVar FPattern Source # | |
Defined in Funcons.TypeSubstitution |
limitedSubsTypeVar :: HasTypeVar a => Set MetaVar -> TypeEnv -> a -> a Source #
Version of subsTypeVar
that does not replace the meta-variables
in the given set
limitedSubsTypeVarWildcard :: HasTypeVar a => Set MetaVar -> Maybe FTerm -> TypeEnv -> a -> a Source #
Version of subsTypeVarWildcard
that does not replace the meta-variables
in the given set
Tools for creating interpreters
Helpers for defining evaluation functions.
rewriteType :: Name -> [Values] -> Rewrite Rewritten Source #
Parameterisable evaluation function function for types.
Default entity values
type EntityDefaults = [EntityDefault] Source #
A list of EntityDefault
s is used to declare (and possibly initialise)
entities.
data EntityDefault Source #
Default values of entities can be specified for inherited and mutable entities.
DefMutable Name Funcons | |
DefInherited Name Funcons | |
DefOutput Name | For the purpose of unit-testing it is advised to notify an interpreter of the existence of control, output and input entities as well. |
DefControl Name | |
DefInput Name |
Type environments
type TypeRelation = Map Name DataTypeMembers Source #
The typing environment maps datatype names to their definitions.
type TypeParam = (Maybe MetaVar, Maybe SeqSortOp, FTerm) Source #
A type parameter is of the form X:T where the name of the parameter,X, is optional. When present, X can be used to specify the type of constructors. Variable X be a sequence variable.
data DataTypeMembers Source #
A datatype has `zero or more' type parameters and `zero or more' alternatives.
DataTypeMemberss Name [TPattern] [DataTypeAltt] |
Instances
Show DataTypeMembers Source # | |
Defined in Funcons.Types showsPrec :: Int -> DataTypeMembers -> ShowS # show :: DataTypeMembers -> String # showList :: [DataTypeMembers] -> ShowS # |
data DataTypeAltt Source #
An alternative is either a datatype constructor or the inclusion
of some other type. The types are arbitrary funcon terms (with possible
variables) that may require evaluation to be resolved to a Types
.
Instances
Show DataTypeAltt Source # | |
Defined in Funcons.Types showsPrec :: Int -> DataTypeAltt -> ShowS # show :: DataTypeAltt -> String # showList :: [DataTypeAltt] -> ShowS # |
typeLookup :: Name -> TypeRelation -> Maybe DataTypeMembers Source #
Lookup the definition of a datatype in the typing environment.
typeEnvUnion :: TypeRelation -> TypeRelation -> TypeRelation Source #
Unites two TypeRelation
s.
typeEnvUnions :: [TypeRelation] -> TypeRelation Source #
Unites a list of TypeRelation
s.
typeEnvFromList :: [(Name, DataTypeMembers)] -> TypeRelation Source #
Creates a TypeRelation
from a list.
emptyTypeRelation :: TypeRelation Source #
The empty TypeRelation
.