libcspm-0.2.0: A library providing a parser, type checker and evaluator for CSPM.

CSPM.DataStructures.Syntax

Contents

Description

This module represents the abstract syntax tree of machine CSP. Most of the datatypes are parameterised over the type of variables that they contain. Before renaming (by CSPM.Renamer) the variables are of type UnRenamedName, wheras after renaming they are of type Name (and are hence associated with their bindings instances). Furthermore, nearly all pieces of syntax are annoated with their location in the source code, and (sometimes) with their type (but only after type checking). This is done using the Annotated datatype.

Synopsis

Modules

Declarations

data Decl id Source

Constructors

FunBind id [AnMatch id]

A function binding, e.g. func(x,y)(z) = 0.

PatBind (AnPat id) (AnExp id)

The binding of a pattern to an expression, e.g. (p,q) = e.

Assert (Assertion id)

An assertion in a file, e.g. assert P [T= Q.

External

An import of an external function, e.g. external test,

Fields

externalImportedNames :: [id]
 
Transparent

An import of a transparent function, e.g. transparent normal.

Fields

transparentImportedNames :: [id]
 
Channel [id] (Maybe (AnExp id))

A channel declaration, e.g. channel c, d : {0..1}.{0..1}.

DataType id [AnDataTypeClause id]

A datatype declaration, e.g. datatype T = Clause1 | Clause2.

NameType id (AnExp id)

A nametype declaration, e.g. nametype T2 = T.T.

data Match id Source

Matches occur on the left hand side of a function declaration and there is one Match for each clause of the declaration. For example, given the declaration:

      f() = 0
      f(x^xs) = 1+f(xs)

there would be two matches.

Constructors

Match 

Fields

matchPatterns :: [[AnPat id]]

The patterns that need to be matched. This is a list of lists as functions may be curried, like f(x,y)(z) = ....

matchRightHandSide :: AnExp id

The expression to be evaluated if the match succeeds.

Assertions

data Assertion id Source

Constructors

Refinement

A refinement assertion, e.g. assert P [F= Q.

PropertyCheck

A check of property, like deadlock freedom, e.g. assert P :[deadlock free [F]].

BoolAssertion (AnExp id)

A boolean assertion, not currently supported.

ASNot (Assertion id)

The negation of an assertion, not currently supported.

Data Type Clauses

data DataTypeClause id Source

The clause of a datatype, e.g. if a datatype declaration was:

 datatype T = A.Int.Bool | B.Bool | C

Then T would have three datatype clauses, one for each of its tags (i.e. A, B and C).

Constructors

DataTypeClause 

Fields

dataTypeClauseName :: id

The name of the datatype clause.

dataTypeClauseTypeExpression :: Maybe (AnExp id)

The expression that gives the set of values that can be dotted with this clause. For example, in the above example the datatype clause for A would have Int.Bool as its type expression.

Expressions

data Exp id Source

An expression.

Constructors

App

Function application.

Fields

appFunction :: AnExp id

The function.

appArguments :: [AnExp id]

The arguments applied to the function

BooleanBinaryOp

Application of a binary boolean operator.

BooleanUnaryOp

Application of a unary boolean operator.

Concat

List concatenation, e.g. x^y.

DotApp

Dot operator application, e.g. c.x.

If

If statements, e.g. if cond then e1 else e2.

Fields

ifCondition :: AnExp id

The condition of the if.

ifThenBranch :: AnExp id

The then branch.

ifElseBranch :: AnExp id
 
Lambda

Lambda functions, e.g. (x,y) @ e(x,y).

Let

Let declarations, e.g. let func = e1 within e2.

Fields

letDeclarations :: [AnDecl id]
 
letExpression :: AnExp id
 
Lit

Literals, e.g. true or 1.

Fields

litLiteral :: Literal
 
List

List literals, e.g. 1,2,3.

Fields

listItems :: [AnExp id]
 
ListComp

List comprehensions, e.g. x,y | (x,y) <- e.

Fields

listCompItems :: [AnExp id]
 
listCompStatements :: [AnStmt id]
 
ListEnumFrom

Infinite list of integers from the given value, e.g. 1...

ListEnumFromTo

Bounded list of integers between the given values, e.g. 1..3.

ListLength

The length of the list, e.g. #list.

MathsBinaryOp

Application of binary maths operator, e.g. x+y.

MathsUnaryOp

Application of unary maths operator, e.g. -x.

Paren

A user provided bracket, e.g. (e).

Fields

parenExpression :: AnExp id
 
Set

Set literals, e.g. {1,2,3}.

Fields

setItems :: [AnExp id]
 
SetComp

Set comprehensions, e.g. {x,y | (x,y) <- e}.

Fields

setCompItems :: [AnExp id]
 
setCompStatements :: [AnStmt id]
 
SetEnum

Enumerated Sets, i.e. sets that complete the events, e.g. {| c.x |}.

Fields

setEnumItems :: [AnExp id]
 
SetEnumComp

Set comprehension version of SetEnum, e.g. {| c.x | x <- xs |}.

SetEnumFrom

The infinite set of integers from the given value, e.g. {5..}.

SetEnumFromTo

The bounded set of integers between the two given values, e.g. {5..6}.

Fields

setEnumFromToLowerBound :: AnExp id

The lower bound.

setEnumFromToUpperBound :: AnExp id

The upper bound.

Tuple

Tuples, e.g. (1,2).

Fields

tupleItems :: [AnExp id]
 
Var

Variables, e.g. x.

Fields

varIdentity :: id
 
AlphaParallel

Alphabetised parallel, e.g. P [A || B] Q.

Fields

alphaParLeftProcess :: AnExp id

Process 1.

alphaParAlphabetLeftProcess :: AnExp id

Alphabet of process 1.

alphaParAlphabetRightProcess :: AnExp id

Alphabet of process 2.

alphaParRightProcess :: AnExp id

Process 2.

Exception

Exception operator, e.g. P [| A |> Q.

ExternalChoice

External choice, e.g. P [] Q.

GenParallel

Generalised parallel, e.g. P [| A |] Q.

GuardedExp

Guarded expressions, e.g. b & P where b is a boolean expression. This is equivalent to if b then P else STOP.

Hiding

Hiding of events, e.g. P A.

Fields

hidingProcess :: AnExp id

The process the hiding is applied to.

hidingAlphabet :: AnExp id

The set of events to be hidden.

InternalChoice

Internal choice, e.g. P |~| Q.

Interrupt

Interrupt (where the left process is turned off once the right process performs an event), e.g. P / Q.

Interleave

Interleaving of processes, e.g. P ||| Q.

LinkParallel 
Prefix

Event prefixing, e.g. c$x?y!z -> P.

Rename

Event renaming, e.g. P [[ a.x <- b.x | x <- X ]].

Fields

renameProcess :: AnExp id

The process that is renamed.

renameTiedEvents :: [(AnExp id, AnExp id)]

The events that are renamed, in the format of (old, new).

renameTieStatements :: [AnStmt id]

The statements for the ties.

SequentialComp

Sequential composition, e.g. P; Q.

SlidingChoice

Sliding choice, e.g. P |> Q.

ReplicatedAlphaParallel

Replicated alphabetised parallel, e.g. || x : X @ [| A(x) |] P(x).

ReplicatedExternalChoice

Replicated external choice, e.g. [] x : X @ P(x).

ReplicatedInterleave

Replicated interleave, e.g. ||| x : X @ P(x).

ReplicatedInternalChoice

Replicated internal choice, e.g. |~| x : X @ P(x).

ReplicatedLinkParallel

Replicated link parallel, e.g. [a.x <- b.x | x <- X(y)] y : Y @ P(y).

Fields

repLinkParTiedChannels :: [(AnExp id, AnExp id)]

The tied events.

repLinkParTieStatements :: [AnStmt id]

The statements for the ties.

repLinkParReplicatedStatements :: [AnStmt id]

The Stmts - the process (and ties) are evaluated once for each value generated by these.

repLinkParProcess :: AnExp id

The process

ReplicatedParallel

Replicated parallel, e.g. [| A |] x : X @ P(x).

ExpPatWildCard

Used only for parsing - never appears in an AST.

ExpPatDoublePattern (AnExp id) (AnExp id)

Used only for parsing - never appears in an AST.

Fields

Fields occur within prefix statements. For example, if the prefix was c$x?y!z then there would be three fields, of type NonDetInput, Input and Output respectively.

data Field id Source

Constructors

Output (AnExp id)
!x
Input (AnPat id) (Maybe (AnExp id))
?x:A
NonDetInput (AnPat id) (Maybe (AnExp id))

$x:A (see P395 UCS)

Statements

Statements occur on the right hand side of a list comprehension, or in the context of replicated operators. For example, in ... | x <- y, func(b), x <- y and func(b) are both statements, of type Generator and Qualifier respectively.

data Stmt id Source

Constructors

Generator (AnPat id) (AnExp id) 
Qualifier (AnExp id) 

Patterns

Patterns match against values and may bind some components of the values to variables.

data Pat id Source

Constructors

PConcat

The concatenation of two patterns, e.g. p1^p2.

PDotApp

The dot of two patterns, e.g. p1.p2.

Fields

pDotLeftPat :: AnPat id
 
pDotRightPat :: AnPat id
 
PDoublePattern

A double pattern match, e.g. p1@@p2.

PList

A literal pattern list, e.g. p1,p2,p3.

Fields

pListItems :: [AnPat id]
 
PLit

A literal pattern, e.g. true, or 0.

Fields

pLitLiteral :: Literal
 
PParen

A user supplied parenthesis in a pattern.

Fields

pParenPattern :: AnPat id
 
PSet

A set pattern. Only singleton patterns, or zero patterns are supported. This is checked by the desugarer. For example, {p1,p2} is not allowed, but {p1} and {} are allowed.

Fields

pSetItems :: [AnPat id]
 
PTuple

A tuple pattern, e.g. (p1,p2,p3).

Fields

pTupleItems :: [AnPat id]
 
PVar

A variable pattern, e.g. x, or A where A is a datatype clause. If the variable is a datatype clause then it only matches that datatype tag, whereas for anything else it matches anything.

Fields

pVarIdentity :: id
 
PWildCard

Matches anything but does not bind it.

PCompList

Since you can write list patterns such as:

 f(<x,y>^xs^<z,p>^<9,0>)
 f(<x,y>)
 f(xs^<x,y>)

we need an easy may of matching them. Thus, we compile the patterns to a PCompList instead.

PCompList ps (Just (p, ps')) corresponds to a list where it starts with ps (where each p in ps matches exactly one list element, has a middle of p (which must be a variable pattern, or a wildcard) and and end matching exactly ps' (again, where each p in ps matches exactly one list component).

PCompDot

Like with a PCompList we flatten nested dot patterns to make it easier to evaluate.

Fields

pDotItems :: [AnPat id]
 
pDotOriginalpattern :: Pat id
 

Interactive Statements

Interactive statements are intended to be input by an interactive editor.

Type Synonyms

As the types are parameterised over the type of names it can be laborious to type the names. Therefore, some shortcuts are provided.

type AnPat id = Annotated () (Pat id)Source

type AnStmt id = Annotated () (Stmt id)Source

Pre-Renaming Types

Post-Renaming Types

Helpers