More updates to the AST documentation.

This consists mostly of syntax tweaks, although I've also added documentation
to a few types that didn't already have it.
This commit is contained in:
Adam Sampson 2007-08-13 20:31:07 +00:00
parent feebea4473
commit eab08e7af2

257
AST.hs
View File

@ -6,18 +6,26 @@ import Data.Generics
import Metadata import Metadata
-- | The general type of a name.
-- This is used by the parser to indicate what sort of name it's expecting in a
-- particular context; in later passes you can look at how the name is actually
-- defined, which is more useful.
data NameType = data NameType =
ChannelName | DataTypeName | FunctionName | FieldName | PortName ChannelName | DataTypeName | FunctionName | FieldName | PortName
| ProcName | ProtocolName | RecordName | TagName | TimerName | VariableName | ProcName | ProtocolName | RecordName | TagName | TimerName | VariableName
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | A name structure for variable names in the AST. -- | An identifier defined in the source code.
-- This can be any of the 'NameType' types.
data Name = Name { data Name = Name {
-- | The meta tag that indicates the location of this instance (use) of the name -- | Metadata.
nameMeta :: Meta, nameMeta :: Meta,
-- | The type of the thing referred to by this Name -- | The general type of the name.
nameType :: NameType, nameType :: NameType,
-- | The resolved name -- | The internal version of the name.
-- This isn't necessary the same as it appeared in the source code; if
-- you're displaying it to the user in an error message, you should
-- probably look up the original name in the corresponding 'NameDef'.
nameName :: String nameName :: String
} }
deriving (Typeable, Data) deriving (Typeable, Data)
@ -28,36 +36,46 @@ instance Show Name where
instance Eq Name where instance Eq Name where
(==) a b = nameName a == nameName b (==) a b = nameName a == nameName b
-- | A structure for holding information about the definition of a name -- | The definition of a name.
data NameDef = NameDef { data NameDef = NameDef {
-- | The meta tag that indicates the location of the definition -- | Metadata.
ndMeta :: Meta, ndMeta :: Meta,
-- | The resolved name -- | The internal version of the name.
ndName :: String, ndName :: String,
-- | The original (raw, unresolved) name -- | The name as it appeared in the source code.
-- This can be used for error reporting.
ndOrigName :: String, ndOrigName :: String,
-- | The type of the thing being named -- | The general type of the name.
ndNameType :: NameType, ndNameType :: NameType,
-- | The specification type (e.g. declaration, IS, RETYPES) -- | The specification type of the name's definition (see 'SpecType').
ndType :: SpecType, ndType :: SpecType,
-- | The abbreviation mode (e.g. VAL abbreviation) -- | The abbreviation mode of the name's definition (see 'AbbrevMode').
ndAbbrevMode :: AbbrevMode, ndAbbrevMode :: AbbrevMode,
-- | The placement of the variable (e.g. PLACE AT) -- | The placement mode of the name's definition (see 'Placement').
ndPlacement :: Placement ndPlacement :: Placement
} }
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | A data or protocol type.
-- The two concepts aren't unified in occam, but they are here, because it
-- makes sense to be able to ask what type a particular name is defined to
-- have.
data Type = data Type =
Bool Bool
| Byte | Byte
| Int | Int16 | Int32 | Int64 | Int | Int16 | Int32 | Int64
| Real32 | Real64 | Real32 | Real64
-- | For N-dimensional arrays, the [Dimension] list will be of length N -- | An array.
-- For N-dimensional arrays, the [Dimension] list will be of length N.
| Array [Dimension] Type | Array [Dimension] Type
-- | A user-defined data type.
| UserDataType Name | UserDataType Name
-- | A record type.
| Record Name | Record Name
-- | A user-defined protocol.
| UserProtocol Name | UserProtocol Name
| Chan Type | Chan Type
-- | A counted input or output.
| Counted Type Type | Counted Type Type
| Any | Any
| Timer | Timer
@ -87,41 +105,60 @@ instance Show Type where
show Timer = "TIMER" show Timer = "TIMER"
show (Port t) = "PORT OF " ++ show t show (Port t) = "PORT OF " ++ show t
-- | occam arrays are permitted to have empty unknown dimensions, hence Dimension is not simply an integer -- | An array dimension.
-- Depending on the context, an array type may have empty dimensions, which is
-- why this isn't just an Int.
data Dimension = data Dimension =
Dimension Int Dimension Int
| UnknownDimension | UnknownDimension
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | How a variable is placed in memory.
-- Placement is used in occam to map preexisting memory and IO space to
-- variables.
data Placement = data Placement =
-- | No placement -- allocate the variable as usual.
-- Traditional occam compilers will allocate the variable either in the
-- workspace or in vectorspace as appropriate.
Unplaced Unplaced
-- | Allocate in the workspace (i.e. on the stack).
| PlaceInWorkspace | PlaceInWorkspace
-- | Allocate in vectorspace (i.e. on the heap).
| PlaceInVecspace | PlaceInVecspace
-- | Use an existing address.
| PlaceAt Expression | PlaceAt Expression
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Data type conversion modes.
-- Which of these are legal depends on the type; in general you only use modes
-- other than 'DefaultConversion' when going to or from floating-point types.
data ConversionMode = data ConversionMode =
DefaultConversion DefaultConversion
| Round | Round
| Trunc | Trunc
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Various different subscripts that can be used in occams -- | A subscript that can be applied to a variable or an expression.
data Subscript = data Subscript =
-- | A single array subscript -- | Select a single element of an array.
Subscript Meta Expression Subscript Meta Expression
-- | A subscript that names a field of a record type -- | Select a named field of a record type.
| SubscriptField Meta Name | SubscriptField Meta Name
-- | A subscript pair that creates an array slice. -- | Select a slice of an array.
-- The first Expression is the FROM; the initial value to begin at, inclusive -- The first 'Expression' is the @FROM@; the initial value to begin at,
-- The second Expression is the FOR; the count of items to include in the slice. -- inclusive.
-- The second 'Expression' is the @FOR@; the count of items to include in the
-- slice.
| SubscriptFromFor Meta Expression Expression | SubscriptFromFor Meta Expression Expression
-- | Like SubscriptFromFor, but without a FOR; it goes to the end of the array -- | Like 'SubscriptFromFor', but without a @FOR@; it goes to the end of the
-- array.
| SubscriptFrom Meta Expression | SubscriptFrom Meta Expression
-- | Like SubscriptFromFor, but without a FROM; it starts from the beginning of the array -- | Like 'SubscriptFromFor', but without a @FROM@; it starts from the
-- beginning of the array.
| SubscriptFor Meta Expression | SubscriptFor Meta Expression
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | The representation of a literal.
data LiteralRepr = data LiteralRepr =
RealLiteral Meta String RealLiteral Meta String
| IntLiteral Meta String | IntLiteral Meta String
@ -139,27 +176,30 @@ data ArrayElem =
| ArrayElemExpr Expression | ArrayElemExpr Expression
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | A variable can either be plain (e.g. "c") or subscripted (e.g. "c[0]" or "person[name]" -- | A variable.
data Variable = data Variable =
-- | A plain variable (e.g. @c@).
Variable Meta Name Variable Meta Name
-- | A subscripted variable (e.g. @c[0]@ or @person[name]@).
| SubscriptedVariable Meta Subscript Variable | SubscriptedVariable Meta Subscript Variable
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | An expression.
data Expression = data Expression =
-- | A monadic/unary operator -- | A monadic (unary) operator.
Monadic Meta MonadicOp Expression Monadic Meta MonadicOp Expression
-- | A dyadic/binary operator -- | A dyadic (binary) operator.
| Dyadic Meta DyadicOp Expression Expression | Dyadic Meta DyadicOp Expression Expression
-- | The most positive value of a given type -- | The most positive value of a given type.
| MostPos Meta Type | MostPos Meta Type
-- | The most negative value of a given type -- | The most negative value of a given type.
| MostNeg Meta Type | MostNeg Meta Type
-- | The size of a given array type, see SizeExpr -- | The size of the outermost dimension of an array type (see 'SizeExpr').
| SizeType Meta Type | SizeType Meta Type
-- | The size of a given array in number of sub-components. -- | The size of the outermost dimension of an array expression.
-- As the occam 2 reference manual explains, given [8][4]INT a:, SIZE a is 8 and SIZE a[0] is 4 -- Given @[8][4]INT a:@, @SIZE a@ is 8 and @SIZE a[0]@ is 4.
| SizeExpr Meta Expression | SizeExpr Meta Expression
-- | See SizeExpr -- | The size of the outermost dimension of an array variable (see 'SizeExpr').
| SizeVariable Meta Variable | SizeVariable Meta Variable
| Conversion Meta ConversionMode Type Expression | Conversion Meta ConversionMode Type Expression
| ExprVariable Meta Variable | ExprVariable Meta Variable
@ -174,17 +214,23 @@ data Expression =
| OffsetOf Meta Type Name | OffsetOf Meta Type Name
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | A list of expressions.
data ExpressionList = data ExpressionList =
-- | A list of expressions resulting from a function call.
FunctionCallList Meta Name [Expression] FunctionCallList Meta Name [Expression]
-- | A list of expressions resulting from, well, a list of expressions.
| ExpressionList Meta [Expression] | ExpressionList Meta [Expression]
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | A monadic (unary) operator.
-- Nothing to do with Haskell monads.
data MonadicOp = data MonadicOp =
MonadicSubtr MonadicSubtr
| MonadicBitNot | MonadicBitNot
| MonadicNot | MonadicNot
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | A dyadic (binary) operator.
data DyadicOp = data DyadicOp =
Add | Subtr | Mul | Div | Rem Add | Subtr | Mul | Div | Rem
| Plus | Minus | Times | Plus | Minus | Times
@ -195,147 +241,180 @@ data DyadicOp =
| After | After
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Input items in occam can either be counted arrays, or single variables -- | An item in an input.
data InputItem = data InputItem =
-- | The first variable is the count, the second is the array -- | A counted input.
-- The count is read into the first variable, and the array items into the second.
InCounted Meta Variable Variable InCounted Meta Variable Variable
-- | A simple input into a single variable.
| InVariable Meta Variable | InVariable Meta Variable
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Output items in occam can either be counted arrays, or single variables -- | An item in an output -- the counterpart of 'InputItem'.
data OutputItem = data OutputItem =
-- | The first expression is the count, the second is the array -- | A counted output.
-- The count is the first expression; the array items are the second.
OutCounted Meta Expression Expression OutCounted Meta Expression Expression
-- | A simple output from an expression.
| OutExpression Meta Expression | OutExpression Meta Expression
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | The Name names the replicator index, the first expression is the base and the second expression is the FOR -- | A replicator.
-- The 'Name' names the replicator index, the first expression is the base and
-- the second expression is the count.
-- (In the future this will have additional constructors for stepped replicators.)
data Replicator = For Meta Name Expression Expression data Replicator = For Meta Name Expression Expression
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | A choice in an IF statement -- | A choice in an @IF@ process.
data Choice = Choice Meta Expression Process data Choice = Choice Meta Expression Process
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | A guard in an ALT -- | A guard in an @ALT@.
data Alternative = data Alternative =
-- | A plain guard. The channel/timer is the Variable, and the destination (or AFTER clause) is inside the InputMode. -- | A plain guard.
-- The process is the body of the guard -- The channel or timer is the 'Variable', and the destination (or @AFTER@
-- clause) is inside the 'InputMode'. The process is the body of the guard.
Alternative Meta Variable InputMode Process Alternative Meta Variable InputMode Process
-- | A conditional guard. The Expression is the pre-condition, everything else is as Alternative above -- | A conditional guard.
-- The 'Expression' is the pre-condition, everything else is as 'Alternative'
-- above.
| AlternativeCond Meta Expression Variable InputMode Process | AlternativeCond Meta Expression Variable InputMode Process
-- | A skip guard (always ready). The Expression is the pre-condition. -- | A @SKIP@ guard (one that is always ready).
-- The 'Expression' is the pre-condition.
| AlternativeSkip Meta Expression Process | AlternativeSkip Meta Expression Process
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | An option in a CASE statement -- | An option in a @CASE@ process.
data Option = data Option =
-- | A single CASE option can have multiple expressions to match against -- | A regular option.
-- These can match multiple values.
Option Meta [Expression] Process Option Meta [Expression] Process
-- | The else guard is picked if no other options match. It does not have to be the last option. -- | A default option, used if nothing else matches.
-- It does not have to be the last option.
| Else Meta Process | Else Meta Process
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | An option in an "? CASE" (input-case) statement -- | An option in a @? CASE@ process.
-- The name is the protocol tag, followed by zero or more input items, followed by the process to be -- The name is the protocol tag, followed by zero or more input items, followed
-- executed if that option is matched -- by the process to be executed if that option is matched.
data Variant = Variant Meta Name [InputItem] Process data Variant = Variant Meta Name [InputItem] Process
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- |This represents something that can contain local replicators and specifications. -- | This represents something that can contain local replicators and specifications.
-- (This ought to be a parametric type, "Structured Variant" etc., but doing so -- (This ought to be a parametric type, @Structured Variant@ etc., but doing so
-- makes using generic functions across it hard.) -- makes using generic functions across it hard.)
data Structured = data Structured =
Rep Meta Replicator Structured Rep Meta Replicator Structured
| Spec Meta Specification Structured | Spec Meta Specification Structured
| ProcThen Meta Process Structured | ProcThen Meta Process Structured
| OnlyV Meta Variant -- ^ Variant (CASE) input process | OnlyV Meta Variant -- ^ Variant (@CASE@) input process
| OnlyC Meta Choice -- ^ IF process | OnlyC Meta Choice -- ^ @IF@ process
| OnlyO Meta Option -- ^ CASE process | OnlyO Meta Option -- ^ @CASE@ process
| OnlyA Meta Alternative -- ^ ALT process | OnlyA Meta Alternative -- ^ @ALT@ process
| OnlyP Meta Process -- ^ SEQ, PAR | OnlyP Meta Process -- ^ @SEQ@, @PAR@
| OnlyEL Meta ExpressionList -- ^ VALOF | OnlyEL Meta ExpressionList -- ^ @VALOF@
| Several Meta [Structured] | Several Meta [Structured]
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | The mode in which an input operates.
data InputMode = data InputMode =
-- | A plain input from a channel.
InputSimple Meta [InputItem] InputSimple Meta [InputItem]
-- | A variant input from a channel.
| InputCase Meta Structured | InputCase Meta Structured
-- | Read the value of a timer.
| InputTimerRead Meta InputItem | InputTimerRead Meta InputItem
-- | Wait for a particular time to go past on a timer.
| InputTimerAfter Meta Expression | InputTimerAfter Meta Expression
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Abbreviation mode. -- | Abbreviation mode.
-- This describes how a name is being accessed.
-- In the future this will have additional modes for @RESULT@, @INITIAL@, etc.
data AbbrevMode = data AbbrevMode =
-- | No abbreviation -- | The original declaration of a name.
Original Original
-- | An abbreviation (by reference) -- | An abbreviation by reference.
| Abbrev | Abbrev
-- | An abbreviation (by value) -- | An abbreviation by value.
| ValAbbrev | ValAbbrev
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Used for introducing specifications (process/function declarations, variables, type definitions, abbreviations, etc) -- | Anything that introduces a new name.
data Specification = data Specification =
Specification Meta Name SpecType Specification Meta Name SpecType
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Used when declaring a Specification -- | The type of a 'Specification'.
data SpecType = data SpecType =
-- | Places a variable at a given memory location -- | Set placement for an existing variable.
Place Meta Expression Place Meta Expression
-- | Declares a variable of the given type -- | Declare a variable.
| Declaration Meta Type | Declaration Meta Type
-- | Declares an abbreviation -- | Declare an abbreviation of a variable.
| Is Meta AbbrevMode Type Variable | Is Meta AbbrevMode Type Variable
-- | Declares a constant to be a particular expression -- | Declare an abbreviation of an expression.
| IsExpr Meta AbbrevMode Type Expression | IsExpr Meta AbbrevMode Type Expression
-- | Declares an array that abbreviates some channels (the list of Variable). -- | Declare an abbreviation of an array of channels.
| IsChannelArray Meta Type [Variable] | IsChannelArray Meta Type [Variable]
-- | Declares a data type (like a typedef) -- | Declare a user data type.
| DataType Meta Type | DataType Meta Type
-- | Declares a new record type. The Bool is True if the record is PACKED, False otherwise. -- | Declare a new record type.
-- The list of (Name,Type) are the members of the record -- The 'Bool' indicates whether the record is @PACKED@.
-- The list is the fields of the record.
| RecordType Meta Bool [(Name, Type)] | RecordType Meta Bool [(Name, Type)]
-- | Declares a simple (sequential) protocol that has the type-list in order as its data items. -- | Declare a simple protocol.
-- The list contains the types of the items.
| Protocol Meta [Type] | Protocol Meta [Type]
-- | Declares a protocol with choice. Each (Name, [Type]) is a tag name, -- | Declare a variant protocol.
-- followed by various data items (as per simple sequential protocols). -- The list pairs tag names with item types.
| ProtocolCase Meta [(Name, [Type])] | ProtocolCase Meta [(Name, [Type])]
-- | Declares a procedure. SpecMode is inline or plain. -- | Declare a @PROC@.
-- The list of Formal are the parameters to the procedure, and the Process
-- is the actual body of the procedure.
| Proc Meta SpecMode [Formal] Process | Proc Meta SpecMode [Formal] Process
-- | Declares a function. Much the same as Proc, but the list of Type is the return type. -- | Declare a @FUNCTION@.
| Function Meta SpecMode [Type] [Formal] Structured | Function Meta SpecMode [Type] [Formal] Structured
-- | Declares a retyping abbreviation. Type is the new type. Variable is the variable being retyped -- | Declare a retyping abbreviation of a variable.
| Retypes Meta AbbrevMode Type Variable | Retypes Meta AbbrevMode Type Variable
-- | Declares a retyping abbreviation. Type is the new type. Expression is the expression being retyped -- | Declare a retyping abbreviation of an expression.
| RetypesExpr Meta AbbrevMode Type Expression | RetypesExpr Meta AbbrevMode Type Expression
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Specification mode for @PROC@s and @FUNCTION@s.
-- This indicates whether a function is inlined by the compiler.
data SpecMode = data SpecMode =
PlainSpec | InlineSpec PlainSpec | InlineSpec
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Formal parameters, as in procedure parameter definitions -- | Formal parameters for @PROC@s and @FUNCTION@s.
data Formal = data Formal =
Formal AbbrevMode Type Name Formal AbbrevMode Type Name
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | Actual parameters to calls of functions/procedures -- | Actual parameters for @PROC@s and @FUNCTION@s.
data Actual = data Actual =
-- | A variable used as a parameter. -- | A variable used as a parameter.
-- I believe AbbrevMode here is included only for convenience - and the same for Type -- 'AbbrevMode' and 'Type' are here for parity with 'Formal'; they can be
-- figured out from the variable.
ActualVariable AbbrevMode Type Variable ActualVariable AbbrevMode Type Variable
-- | An expression used as a parameter -- | An expression used as a parameter.
| ActualExpression Type Expression | ActualExpression Type Expression
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | The mode in which a @PAR@ operates.
data ParMode = data ParMode =
PlainPar | PriPar | PlacedPar -- | Regular @PAR@.
PlainPar
-- | Prioritised @PAR@.
-- Earlier processes run at higher priority.
| PriPar
-- | Placed @PAR@.
-- 'Processor' instances inside this indicate which processor each parallel
-- process runs on.
| PlacedPar
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)
-- | A process.
data Process = data Process =
Assign Meta [Variable] ExpressionList Assign Meta [Variable] ExpressionList
| Input Meta Variable InputMode | Input Meta Variable InputMode
@ -343,15 +422,27 @@ data Process =
| OutputCase Meta Variable Name [OutputItem] | OutputCase Meta Variable Name [OutputItem]
| Skip Meta | Skip Meta
| Stop Meta | Stop Meta
-- | The main process.
-- This is an artefact of how occam is structured. An occam program consists
-- of a series of scoped definitions; the last @PROC@ defined is run.
-- However, this means that a program as parsed must consist of a series of
-- 'Spec's with a magic value at the end to indicate where the program starts
-- -- and that's what this is for.
| Main Meta | Main Meta
| Seq Meta Structured | Seq Meta Structured
| If Meta Structured | If Meta Structured
| Case Meta Expression Structured | Case Meta Expression Structured
| While Meta Expression Process | While Meta Expression Process
| Par Meta ParMode Structured | Par Meta ParMode Structured
-- | A @PROCESSOR@ process.
-- The occam2.1 syntax says this is just a process, although it shouldn't be
-- legal outside a @PLACED PAR@.
| Processor Meta Expression Process | Processor Meta Expression Process
| Alt Meta Bool Structured | Alt Meta Bool Structured
| ProcCall Meta Name [Actual] | ProcCall Meta Name [Actual]
-- | A call of a built-in @PROC@.
-- This may go away in the future, since which @PROC@s are intrinsics depends
-- on the backend.
| IntrinsicProcCall Meta String [Actual] | IntrinsicProcCall Meta String [Actual]
deriving (Show, Eq, Typeable, Data) deriving (Show, Eq, Typeable, Data)