module CSPM.DataStructures.Syntax (
CSPMFile(..), allAssertionsInFile, allPrintStatementsInFile,
Decl(..), Match(..),
Assertion(..), Model(..), ModelOption(..), SemanticProperty(..),
DataTypeClause(..),
Exp(..), BinaryMathsOp(..), BinaryBooleanOp(..), UnaryMathsOp(..),
UnaryBooleanOp(..),
Field(..),
Stmt(..),
Pat(..),
InteractiveStmt(..),
STypeScheme(..), STypeConstraint(..), SType(..),
AnCSPMFile, AnDecl, AnMatch, AnPat, AnExp, AnField,
AnStmt, AnDataTypeClause, AnAssertion, AnInteractiveStmt, AnSTypeScheme,
AnSTypeConstraint, AnSType,
PCSPMFile, PDecl, PMatch, PPat, PExp, PField,
PStmt, PDataTypeClause, PAssertion, PInteractiveStmt, PSTypeScheme,
PSTypeConstraint, PSType,
TCCSPMFile, TCDecl, TCMatch, TCPat, TCExp, TCField,
TCStmt, TCDataTypeClause, TCAssertion, TCInteractiveStmt, TCSTypeScheme,
TCSTypeConstraint, TCSType,
getType, getSymbolTable,
) where
import CSPM.DataStructures.Literals
import CSPM.DataStructures.Names
import CSPM.DataStructures.Types
import Util.Annotated
import Util.Exception
type AnCSPMFile id = Annotated () (CSPMFile id)
type AnDecl id = Annotated (Maybe SymbolTable, PSymbolTable) (Decl id)
type AnMatch id = Annotated () (Match id)
type AnPat id = Annotated () (Pat id)
type AnExp id = Annotated (Maybe Type, PType) (Exp id)
type AnField id = Annotated () (Field id)
type AnStmt id = Annotated () (Stmt id)
type AnDataTypeClause id = Annotated () (DataTypeClause id)
type AnAssertion id = Annotated () (Assertion id)
type AnInteractiveStmt id = Annotated () (InteractiveStmt id)
type AnSTypeScheme id = Annotated () (STypeScheme id)
type AnSTypeConstraint id = Annotated () (STypeConstraint id)
type AnSType id = Annotated () (SType id)
getType :: Annotated (Maybe Type, PType) a -> Type
getType an = case fst (annotation an) of
Just t -> t
Nothing -> panic "Cannot get the type of something that is not typechecked"
getSymbolTable :: Annotated (Maybe SymbolTable, PSymbolTable) a -> SymbolTable
getSymbolTable an = case fst (annotation an) of
Just t -> t
Nothing -> panic "Cannot get the symbol table of something that is not typechecked"
type PCSPMFile = AnCSPMFile UnRenamedName
type PDecl = AnDecl UnRenamedName
type PMatch = AnMatch UnRenamedName
type PPat = AnPat UnRenamedName
type PExp = AnExp UnRenamedName
type PStmt = AnStmt UnRenamedName
type PField = AnField UnRenamedName
type PDataTypeClause = AnDataTypeClause UnRenamedName
type PAssertion = AnAssertion UnRenamedName
type PInteractiveStmt = AnInteractiveStmt UnRenamedName
type PSTypeScheme = AnSTypeScheme UnRenamedName
type PSTypeConstraint = AnSTypeConstraint UnRenamedName
type PSType = AnSType UnRenamedName
type TCCSPMFile = AnCSPMFile Name
type TCDecl = AnDecl Name
type TCMatch = AnMatch Name
type TCPat = AnPat Name
type TCExp = AnExp Name
type TCField = AnField Name
type TCStmt = AnStmt Name
type TCDataTypeClause = AnDataTypeClause Name
type TCAssertion = AnAssertion Name
type TCInteractiveStmt = AnInteractiveStmt Name
type TCSTypeScheme = AnSTypeScheme Name
type TCSTypeConstraint = AnSTypeConstraint Name
type TCSType = AnSType Name
data CSPMFile id = CSPMFile [AnDecl id]
deriving (Eq, Ord, Show)
allAssertionsInFile :: AnCSPMFile a -> [AnAssertion a]
allAssertionsInFile (An _ _ (CSPMFile ds)) =
let
assertionsInDecl' = assertionsInDecl . unAnnotate
assertionsInDecl (Assert a) = [a]
assertionsInDecl (Module _ _ dsps dsps') =
concatMap assertionsInDecl' dsps ++
concatMap assertionsInDecl' dsps'
assertionsInDecl (TimedSection _ _ ds) =
concatMap assertionsInDecl' ds
assertionsInDecl _ = []
in concatMap assertionsInDecl' ds
allPrintStatementsInFile :: AnCSPMFile a -> [Located String]
allPrintStatementsInFile (An _ _ (CSPMFile ds)) =
let
printStatementsInDecl (An loc _ (PrintStatement s)) = [L loc s]
printStatementsInDecl _ = []
in concatMap printStatementsInDecl ds
data BinaryBooleanOp =
And
| Or
| Equals
| NotEquals
| LessThan
| GreaterThan
| LessThanEq
| GreaterThanEq
deriving (Eq, Ord, Show)
data UnaryBooleanOp =
Not
deriving (Eq, Ord, Show)
data UnaryMathsOp =
Negate
deriving (Eq, Ord, Show)
data BinaryMathsOp =
Divide | Minus | Mod | Plus | Times
deriving (Eq, Ord, Show)
data Exp id =
App {
appFunction :: AnExp id,
appArguments :: [AnExp id]
}
| BooleanBinaryOp {
booleanBinaryOpOperator :: BinaryBooleanOp,
booleanBinaryOpLeftExpression :: AnExp id,
booleanBinaryOpRightExpression :: AnExp id
}
| BooleanUnaryOp {
unaryBooleanOpOperator :: UnaryBooleanOp,
unaryBooleanExpression :: AnExp id
}
| Concat {
concatLeftList :: AnExp id,
concatRightList :: AnExp id
}
| DotApp {
dotAppLeftArgument :: AnExp id,
dotAppRighArgument :: AnExp id
}
| If {
ifCondition :: AnExp id,
ifThenBranch :: AnExp id,
ifElseBranch :: AnExp id
}
| Lambda {
lambdaBindingPatterns :: [AnPat id],
lambdaRightHandSide :: AnExp id
}
| Let {
letDeclarations :: [AnDecl id],
letExpression :: AnExp id
}
| Lit {
litLiteral :: Literal
}
| List {
listItems :: [AnExp id]
}
| ListComp {
listCompItems :: [AnExp id],
listCompStatements :: [AnStmt id]
}
| ListEnumFrom {
listEnumFromLowerBound :: AnExp id
}
| ListEnumFromTo {
listEnumFromToLowerBound :: AnExp id,
listEnumFromToUpperBound :: AnExp id
}
| ListEnumFromComp {
listEnumFromCompLowerBound :: AnExp id,
listEnumFromCompStatements :: [AnStmt id]
}
| ListEnumFromToComp {
listEnumFromToCompLowerBound :: AnExp id,
listEnumFromToCompUpperBound :: AnExp id,
listEnumFromToCompStatements :: [AnStmt id]
}
| ListLength {
listLengthExpression :: AnExp id
}
| Map {
mapKeyValuePairs :: [(AnExp id, AnExp id)]
}
| MathsBinaryOp {
mathsBinaryOpOperator :: BinaryMathsOp,
mathsBinaryOpLeftExpression :: AnExp id,
mathsBinaryOpRightExpression :: AnExp id
}
| MathsUnaryOp {
mathsUnaryOpOperator :: UnaryMathsOp,
mathsUnaryOpExpression :: AnExp id
}
| Paren {
parenExpression :: AnExp id
}
| Set {
setItems :: [AnExp id]
}
| SetComp {
setCompItems :: [AnExp id],
setCompStatements :: [AnStmt id]
}
| SetEnum {
setEnumItems :: [AnExp id]
}
| SetEnumComp {
setEnumCompItems :: [AnExp id],
setEnumCompStatements :: [AnStmt id]
}
| SetEnumFrom {
setEnumFromLowerBound :: AnExp id
}
| SetEnumFromTo {
setEnumFromToLowerBound :: AnExp id,
setEnumFromToUpperBound :: AnExp id
}
| SetEnumFromComp {
setEnumFromCompLowerBound :: AnExp id,
setEnumFromCompStatements :: [AnStmt id]
}
| SetEnumFromToComp {
setEnumFromToCompLowerBound :: AnExp id,
setEnumFromToCompUpperBound :: AnExp id,
setEnumFromToCompStatements :: [AnStmt id]
}
| Tuple {
tupleItems :: [AnExp id]
}
| Var {
varIdentity :: id
}
| AlphaParallel {
alphaParLeftProcess :: AnExp id,
alphaParAlphabetLeftProcess :: AnExp id,
alphaParAlphabetRightProcess :: AnExp id,
alphaParRightProcess :: AnExp id
}
| Exception {
exceptionLeftProcess :: AnExp id,
exceptionAlphabet :: AnExp id,
exceptionRightProcess :: AnExp id
}
| ExternalChoice {
extChoiceLeftProcess :: AnExp id,
extChoiceRightOperator :: AnExp id
}
| GenParallel {
genParallelLeftProcess :: AnExp id,
genParallelAlphabet :: AnExp id,
genParallelRightProcess :: AnExp id
}
| GuardedExp {
guardedExpCondition :: AnExp id,
guardedExpProcess :: AnExp id
}
| Hiding {
hidingProcess :: AnExp id,
hidingAlphabet :: AnExp id
}
| InternalChoice {
intChoiceLeftProcess :: AnExp id,
intChoiceRightProcess :: AnExp id
}
| Interrupt {
interruptLeftProcess :: AnExp id,
interruptRightProcess :: AnExp id
}
| Interleave {
interleaveLeftProcess :: AnExp id,
interleaveRightProcess :: AnExp id
}
| LinkParallel {
linkParLeftProcess :: AnExp id,
linkParTiedEvents :: [(AnExp id, AnExp id)],
linkParTieStatements :: [AnStmt id],
linkParRightProcess :: AnExp id
}
| Prefix {
prefixChannel :: AnExp id,
prefixFields :: [AnField id],
prefixProcess :: AnExp id
}
| Rename {
renameProcess :: AnExp id,
renameTiedEvents :: [(AnExp id, AnExp id)],
renameTieStatements :: [AnStmt id]
}
| SequentialComp {
seqCompLeftProcess :: AnExp id,
seqCompRightProcess :: AnExp id
}
| SlidingChoice {
slidingChoiceLeftProcess :: AnExp id,
slidingChoiceRightProcess :: AnExp id
}
| SynchronisingExternalChoice {
synchronisingExternalChoiceLeftProcess :: AnExp id,
synchronisingExternalChoiceAlphabet :: AnExp id,
synchronisingExternalChoiceRightProcess :: AnExp id
}
| SynchronisingInterrupt {
synchronisingInterruptLeftProcess :: AnExp id,
synchronisingInterruptAlphabet :: AnExp id,
synchronisingInterruptRightProcess :: AnExp id
}
| ReplicatedAlphaParallel {
repAlphaParReplicatedStatements :: [AnStmt id],
repAlphaParAlphabet :: AnExp id,
repAlphaParProcess :: AnExp id
}
| ReplicatedExternalChoice {
repExtChoiceReplicatedStatements :: [AnStmt id],
repExtChoiceProcess :: AnExp id
}
| ReplicatedInterleave {
repInterleaveReplicatedStatements :: [AnStmt id],
repInterleaveProcess :: AnExp id
}
| ReplicatedInternalChoice {
repIntChoiceReplicatedStatements :: [AnStmt id],
repIntChoiceProcess :: AnExp id
}
| ReplicatedLinkParallel {
repLinkParTiedChannels :: [(AnExp id, AnExp id)],
repLinkParTieStatements :: [AnStmt id],
repLinkParReplicatedStatements :: [AnStmt id],
repLinkParProcess :: AnExp id
}
| ReplicatedParallel {
repParAlphabet :: AnExp id,
repParReplicatedStatements :: [AnStmt id],
repParProcess :: AnExp id
}
| ReplicatedSequentialComp {
repSeqCompStatements :: [AnStmt id],
repSeqCompProcess :: AnExp id
}
| ReplicatedSynchronisingExternalChoice {
repSynchronisingExtChoiceAlphabet :: AnExp id,
repSynchronisingExtChoiceReplicatedStatements :: [AnStmt id],
repSynchronisingExtChoiceProcess :: AnExp id
}
| ExpPatWildCard
| ExpPatDoublePattern (AnExp id) (AnExp id)
| TimedPrefix {
timedPrefixRecursionName :: id,
timedPrefixOriginalPrefix :: AnExp id
}
deriving (Eq, Ord, Show)
data Field id =
Output (AnExp id)
| Input (AnPat id) (Maybe (AnExp id))
| NonDetInput (AnPat id) (Maybe (AnExp id))
deriving (Eq, Ord, Show)
data Stmt id =
Generator (AnPat id) (AnExp id)
| Qualifier (AnExp id)
deriving (Eq, Ord, Show)
data InteractiveStmt id =
Evaluate (AnExp id)
| Bind [AnDecl id]
| RunAssertion (AnAssertion id)
deriving (Eq, Ord, Show)
data Decl id =
FunBind id [AnMatch id] (Maybe (AnSTypeScheme id))
| PatBind (AnPat id) (AnExp id) (Maybe (AnSTypeScheme id))
| Assert (AnAssertion id)
| External {
externalImportedNames :: [id]
}
| Transparent {
transparentImportedNames :: [id]
}
| Channel [id] (Maybe (AnExp id))
| DataType id [AnDataTypeClause id]
| SubType id [AnDataTypeClause id]
| NameType id (AnExp id)
| Module {
moduleName :: id,
moduleArguments :: [AnPat id],
modulePrivateDeclarations :: [AnDecl id],
moduleExportedDeclarations :: [AnDecl id]
}
| TimedSection {
timedSectionTockName :: Maybe Name,
timedSectionFunction :: Maybe (AnExp id),
timedSectionContents :: [AnDecl id]
}
| ParsedTypeAnnotation [id] (AnSTypeScheme id)
| ModuleInstance {
moduleInstanceName :: id,
moduleInstanceOf :: id,
moduleInstanceOfArguments :: [AnExp id],
moduleInstanceNameMap :: [(id, id)],
moduleInstanceOfDeclaration :: Maybe (AnDecl id)
}
| PrintStatement {
printStatement :: String
}
deriving (Eq, Ord, Show)
data Assertion id =
Refinement {
refinementSpecification :: AnExp id,
refinementModel :: Model,
refinementImplementation :: AnExp id,
refinementModelOptions :: [ModelOption id]
}
| PropertyCheck {
propertyCheckProcess :: AnExp id,
propertyCheckProperty :: SemanticProperty,
propertyCheckModel :: Maybe Model
}
| ASNot (AnAssertion id)
deriving (Eq, Ord, Show)
data Model =
Traces
| Failures
| FailuresDivergences
| Refusals
| RefusalsDivergences
| Revivals
| RevivalsDivergences
deriving (Eq, Ord, Show)
data ModelOption id =
TauPriority (AnExp id)
deriving (Eq, Ord, Show)
data SemanticProperty =
DeadlockFreedom
| Deterministic
| LivelockFreedom
deriving (Eq, Ord, Show)
data DataTypeClause id =
DataTypeClause {
dataTypeClauseName :: id,
dataTypeClauseTypeExpression :: Maybe (AnExp id)
}
deriving (Eq, Ord, Show)
data Match id =
Match {
matchPatterns :: [[AnPat id]],
matchRightHandSide :: AnExp id
}
deriving (Eq, Ord, Show)
data Pat id =
PConcat {
pConcatLeftPat :: AnPat id,
pConcatRightPat :: AnPat id
}
| PDotApp {
pDotLeftPat :: AnPat id,
pDotRightPat :: AnPat id
}
| PDoublePattern {
pDoublePatLeftPat :: AnPat id,
pDoublePatRightPat :: AnPat id
}
| PList {
pListItems :: [AnPat id]
}
| PLit {
pLitLiteral :: Literal
}
| PParen {
pParenPattern :: AnPat id
}
| PSet {
pSetItems :: [AnPat id]
}
| PTuple {
pTupleItems :: [AnPat id]
}
| PVar {
pVarIdentity :: id
}
| PWildCard
| PCompList {
pListStartItems :: [AnPat id],
pListMiddleEndItems :: Maybe (AnPat id, [AnPat id]),
pListOriginalPattern :: Pat id
}
| PCompDot {
pDotItems :: [AnPat id],
pDotOriginalpattern :: Pat id
}
deriving (Eq, Ord, Show)
data STypeScheme id =
STypeScheme {
stypeSchemeFreeVars :: [id],
stypeSchemeTypeConstraints :: [AnSTypeConstraint id],
stypeSchemeType :: AnSType id
}
deriving (Eq, Ord, Show)
data STypeConstraint id =
STypeConstraint {
stypeConstraintName :: Constraint,
stypeConstraintVariable :: id
}
deriving (Eq, Ord, Show)
data SType id =
STVar id
| STExtendable (AnSType id) id
| STSet (AnSType id)
| STSeq (AnSType id)
| STDot (AnSType id) (AnSType id)
| STTuple [AnSType id]
| STFunction [AnSType id] (AnSType id)
| STDotable (AnSType id) (AnSType id)
| STParen (AnSType id)
| STMap (AnSType id) (AnSType id)
| STDatatype id
| STProc
| STInt
| STBool
| STChar
| STEvent
deriving (Eq, Ord, Show)