vhdl-0.1.2.1: VHDL AST and pretty printer

Portabilitynon-portable (Template Haskell)
Stabilityexperimental
Maintainerchristiaan.baaij@gmail.com

Language.VHDL.AST

Description

A VHDL 93 subset AST (Abstract Syntax Tree), coded so that it can be easy to extend, please see docVHDLvhdl93-syntax.html as reference in order to extend it (this AST is based on that grammar)

Synopsis

Documentation

fromVHDLId :: VHDLId -> StringSource

Obtain the String of a VHDL identifier

unsafeVHDLBasicId :: String -> VHDLIdSource

unsafely create a basic VHDLId (without cheking if the string is correct)

unsafeVHDLExtId :: String -> VHDLIdSource

unsafely create an exteded VHDLId (without cheking if the string is correct)

mkVHDLBasicId :: String -> EProne VHDLIdSource

Create a VHDL basic identifier from a String, previously checking if the String is correct

mkVHDLExtId :: String -> EProne VHDLIdSource

Create a VHDL extended identifier from a String, previously checking if the String is correct. The input string must not include the initial and ending backslashes nad the intermediate backslashes shouldn't be escaped.

unsafeIdAppend :: VHDLId -> String -> VHDLIdSource

Unsafely append a string to a VHDL identifier (i.e. without checking if the resulting identifier is valid)

specialChars :: [Char]Source

special characters as defined in the VHDL93 standard

otherSpecialChars :: [Char]Source

other special characters as defined in the VHDL93 standard

reservedWords :: [String]Source

Reserved identifiers

data IfaceSigDec Source

interface_signal_declaration We don't allow the id1,id2,id3 syntax, only one identifier is allowed at once The Mode is mandatory Bus is not allowed Preasigned values are not allowed Subtype indications are not allowed, just a typemark Constraints are not allowed: just add a new type with the constarint in ForSyDe.vhd if it is required

type TypeMark = SimpleNameSource

type_mark We don't distinguish between type names and subtype names We dont' support selected names, only simple names because we won't need name selection (i.e. Use clauses will make name selection unnecesary)

data Mode Source

mode INOUT | BUFFER | LINKAGE are not allowed

Constructors

In 
Out 

Instances

data ArchBody Source

architecture_body [ ARCHITECTURE ] and [ architecture_simple_name ] are not allowed

data PackageDec Source

package_declaration [ PACKAGE ] and [ package_simple_name ] are not allowed

data PackageDecItem Source

package_declarative_item only type declarations, subtype declarations and subprogram specifications (working as subprogram_declaration) allowed

data PackageBody Source

package_body [ PACKAGE ] and [ package_simple_name ] are not allowed

type PackageBodyDecItem = SubProgBodySource

only subprogram_body is allowed

data SubtypeDec Source

subtype-declaration

data SubtypeIn Source

subtype_indication resolution functions are not permitted

type Constraint = IndexConstraintSource

constraint Only index constraints are allowed

data Range Source

range the direction must always be "to"

Instances

type DiscreteRange = RangeSource

discrete_range only ranges are allowed

data TypeDec Source

type_declaration only full_type_declarations are allowed

Constructors

TypeDec VHDLId TypeDef 

Instances

data TypeDef Source

type_declaration only composite types and enumeration types (a specific scalar type)

Instances

data ArrayTypeDef Source

array_type_definition unconstrained_array_definition constrained_array_definition A TypeMark is used instead of a subtype_indication. If subtyping is required, declare a subtype explicitly.

data RecordTypeDef Source

record_type_definition [ record_type_simple_name ] not allowed

Constructors

RecordTypeDef [ElementDec] 

data ElementDec Source

element_declaration multi-identifier element declarations not allowed element_subtype_definition is simplified to a type_mark

Constructors

ElementDec VHDLId TypeMark 

data EnumTypeDef Source

enumeration_type_definition enumeration literals can only be identifiers

Constructors

EnumTypeDef [VHDLId] 

data IntegerTypeDef Source

integer_type_definition integer literals can only be numbers

type SimpleName = VHDLIdSource

simple_name

data SelectedName Source

selected_name

Constructors

Prefix :.: Suffix 

data IndexedName Source

indexed_name note that according to the VHDL93 grammar the index list cannot be empty

Constructors

IndexedName Prefix [Expr] 

type Prefix = VHDLNameSource

prefix only names (no function calls)

data Suffix Source

suffix no character or operator symbols are accepted

Constructors

SSimple SimpleName 
All 

Instances

data SliceName Source

slice_name

data AttribName Source

attribute_name signatures are not allowed

data BlockDecItem Source

block_declarative_item Only subprogram bodies and signal declarations are allowed

data SubProgBody Source

subprogram_body No subprogram kind nor designator is allowed

data SubProgDecItem Source

subprogram_declarative_item only varaible declarations are allowed.

data VarDec Source

variable_declaration identifier lists are not allowed

Constructors

VarDec VHDLId SubtypeIn (Maybe Expr) 

Instances

data SubProgSpec Source

subprogram_specification Only Functions are allowed [Pure | Impure] is not allowed Only an identifier is valid as the designator In the formal parameter list only variable declarations are accepted

data IfaceVarDec Source

interface_variable_declaration [variable] is not allowed We don't allow the id1,id2,id3 syntax, only one identifier is allowed Mode is not allowed Resolution functions and constraints are not allowed, thus a TypeMark is used instead of a subtype_indication. If subtyping is required, declare a subtype explicitly.

data SeqSm Source

sequential_statement Only If, case, return, for loops, assignment, wait for procedure calls allowed. Only for loops are allowed (thus loop_statement doesn't exist) and cannot be provided labels. The target cannot be an aggregate. General wait statements are not allowed, only wait for It is incorrect to have an empty [CaseSmAlt]

Instances

data ElseIf Source

helper type, they doesn't exist in the origianl grammar

Constructors

ElseIf Expr [SeqSm] 

Instances

data Else Source

helper type, it doesn't exist in the origianl grammar

Constructors

Else [SeqSm] 

Instances

data CaseSmAlt Source

case_statement_alternative it is incorrect to have an empty [Choice]

Constructors

CaseSmAlt [Choice] [SeqSm] 

data Choice Source

choice although any expression is allowed the grammar specfically only allows simple_expressions (not covered in this AST)

Constructors

ChoiceE Expr 
Others 

Instances

data SigDec Source

signal_declaration We don't allow the id1,id2,id3 syntax, only one identifier is allowed at once Resolution functions and constraints are not allowed, thus a TypeMark is used instead of a subtype_indication Signal kinds are not allowed

Constructors

SigDec VHDLId TypeMark (Maybe Expr) 

Instances

data ConcSm Source

concurrent_statement only block statements, component instantiations and signal assignments are allowed

Instances

data BlockSm Source

block_statement Generics are not supported The port_clause (with only signals) and port_map_aspect are mandatory The ending [ block_label ] is not allowed

Instances

newtype PMapAspect Source

port_map_aspect

Constructors

PMapAspect [AssocElem] 

type Label = VHDLIdSource

label

data AssocElem Source

association_element

type FormalPart = SimpleNameSource

formal_part We only accept a formal_designator (which is a name after all), in the forme of simple name (no need for selected names) function_name ( formal_designator ) and type_mark ( formal_designator ) are not allowed

type ActualPart = ActualDesigSource

actual_part We only accept an actual_designator, function_name ( actual_designator ) and type_mark ( actual_designator ) are not allowed

data ActualDesig Source

actual_designator

Constructors

ADName VHDLName 
ADExpr Expr 
Open 

data ConSigAssignSm Source

concurrent_signal_assignment_statement Only conditional_signal_assignment is allowed (without options) The LHS (targets) are simply signal names, no aggregates

Constructors

VHDLName :<==: ConWforms 

data ConWforms Source

conditional_waveforms

Constructors

ConWforms [WhenElse] Wform (Maybe When) 

data WhenElse Source

Helper type, it doesn't exist in the VHDL grammar

Constructors

WhenElse Wform Expr 

newtype When Source

Helper type, it doesn't exist in the VHDL grammar

Constructors

When Expr 

Instances

data Wform Source

waveform although it is possible to leave [Expr] empty, that's obviously not valid VHDL waveform

Constructors

Wform [WformElem] 
Unaffected 

Instances

data WformElem Source

waveform_element Null is not accepted

Constructors

WformElem Expr (Maybe Expr) 

data CompInsSm Source

component_instantiation_statement No generics supported The port map aspect is mandatory

data ProcSm Source

process_statement The label is mandatory Only simple names are accepted in the sensitivity list No declarative part is allowed

Constructors

ProcSm Label [SimpleName] [SeqSm] 

Instances

data InsUnit Source

instantiated_unit Only Entities are allowed and their architecture cannot be specified

Constructors

IUEntity VHDLName 

Instances

data GenSm Source

Instances

data Expr Source

expression, instead of creating an AST like the grammar (see commented section below) we made our own expressions which are easier to handle, but which don't don't show operand precedence (that is a responsibility of the pretty printer)

Instances

logicalPrec :: IntSource

Logical Operators precedence

relationalPrec :: IntSource

Relational Operators Precedence

shiftPrec :: IntSource

Shift Operators Precedence

plusPrec :: IntSource

Plus Operators precedence

signPrec :: IntSource

Sign Operators Precedence

multPrec :: IntSource

Multplying Operators Precedecne

miscPrec :: IntSource

Miscellaneous Operators Precedence

data ElemAssoc Source

element_association only one choice is allowed

Constructors

ElemAssoc (Maybe Choice) Expr 

type Literal = StringSource

literal Literals are expressed as a string (remember we are generating code, not parsing)

data FCall Source

function_call

Constructors

FCall VHDLName [AssocElem] 

Instances