CSPM-Interpreter-0.1.0.1: An interpreter for CSPMSource codeContentsIndex
CSPM.Interpreter.Types
PortabilityGHC-only
Stabilityexperimental
MaintainerFontaine@cs.uni-duesseldorf.de
Description
Definitions of most of the types used in the interpreter. Also Instance declarations for the core language type families. INT is the type (index) for the CSPM interpreter.
Documentation
data INT Source
show/hide Instances
type Event = [Field]Source
type Field = ValueSource
type FieldSet = SSet FieldSource
type Process = Process INTSource
type Digest = MD5DigestSource
data ClosureSet Source
Constructors
ClosureSet
closureSetTrie :: PrefixTrie
closureSetDigest :: Digest
show/hide Instances
data RenamingRelation Source
Constructors
RenamingRelation
renamingPairs :: Set (Event, Event)
renamingDomain :: Set Event
renamingRange :: Set Event
renamingDigest :: Digest
show/hide Instances
data ClosureState Source
Constructors
ClosureStateNormal
origClosureSet :: ClosureSet
currentPrefixTrie :: PrefixTrie
ClosureStateFailed
origClosureSet :: ClosureSet
ClosureStateSucc
origClosureSet :: ClosureSet
currentPrefixTrie :: PrefixTrie
show/hide Instances
data SwitchedOffProc Source
Constructors
SwitchedOffProc
switchedOffDigest :: Digest
switchedOffExpr :: LExp
switchedOffProcess :: Process
show/hide Instances
data PrefixState Source
Constructors
PrefixState
prefixEnv :: Env
prefixFields :: [LCommField]
prefixBody :: LExp
prefixRHS :: Process
prefixDigest :: Digest
prefixPatternFailed :: Bool
show/hide Instances
data GenericBufferPrefix Source
Constructors
GBOut [Value] PrefixState
GBInput PrefixState
GBInputGuard FieldSet PrefixState
GBInputGeneric [Value] PrefixState
GBFinished PrefixState
show/hide Instances
type Bindings = IntMap ValueSource
data Env Source
Constructors
Env
argBindings :: Bindings
letBindings :: Bindings
letDigests :: IntMap Digest
show/hide Instances
initialEnvirionment :: IO EnvSource
emptyEnvirionment :: EnvSource
newtype EM x Source
Constructors
EM
unEM :: Reader Env x
show/hide Instances
getArgBindings :: Env -> BindingsSource
getLetBindings :: Env -> BindingsSource
setArgBindings :: Env -> Bindings -> EnvSource
setLetBindings :: Env -> Bindings -> EnvSource
getEnv :: EM EnvSource
class Monad m => Eval m whereSource
Methods
evalM :: LExp -> m ValueSource
data Value Source
Constructors
VInt Integer
VBool Bool
VList [Value]
VTuple [Value]
VDotTuple [Value]
VSet (Set Value)
VClosure ClosureSet
VFun FunClosure
VProcess Process
VChannel Channel
VUnit
VAllInts
VAllSequents (Set Value)
VConstructor Constructor
VDataType [Constructor]
VNameType [FieldSet]
VPartialApplied FunClosure [Value]
show/hide Instances
data FunClosure Source
Constructors
FunClosure
getFunCases :: [FunCase]
getFunEnv :: Env
getFunArgNum :: Int
getFunId :: Digest
show/hide Instances
data Constructor Source
Constructors
Constructor
constrId :: Int
constrName :: String
constrFields :: [FieldSet]
show/hide Instances
data Channel Source
Constructors
Channel
chanId :: Int
chanName :: String
chanLen :: Int
chanFields :: [FieldSet]
show/hide Instances
isChannelField :: Field -> BoolSource
getChannel :: Field -> ChannelSource
data PrefixTrie Source
Constructors
PTNil
PTAny PrefixTrie
PTMap (Map Value PrefixTrie)
PTRec (Set Value) PrefixTrie
PTSingle Value PrefixTrie
PTClosure PrefixTrie
show/hide Instances
data InterpreterError Source
Constructors
ScriptError
errMsg :: String
errLoc :: Maybe SrcLoc
errVal :: Maybe Value
FeatureNotImplemented
errMsg :: String
errLoc :: Maybe SrcLoc
TypingError
errMsg :: String
errLoc :: Maybe SrcLoc
errVal :: Maybe Value
InternalError
errMsg :: String
errLoc :: Maybe SrcLoc
errVal :: Maybe Value
PatternMatchError
errMsg :: String
errLoc :: Maybe SrcLoc
show/hide Instances
throwScriptError :: String -> Maybe SrcLoc -> Maybe Value -> aSource
throwFeatureNotImplemented :: String -> Maybe SrcLoc -> aSource
throwTypingError :: String -> Maybe SrcLoc -> Maybe Value -> aSource
throwInternalError :: String -> Maybe SrcLoc -> Maybe Value -> aSource
throwPatternMatchError :: String -> Maybe SrcLoc -> aSource
Produced by Haddock version 2.6.1