| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Fortran.Vars.Types
Contents
Synopsis
- type TypeOf a = Expression a -> Either TypeError Type
- data TypeError
- type ProgramStructureTables = Map ProgramUnitName StructureTable
- type ProgramFileModel = Map ProgramUnitName ProgramUnitModel
- type ProgramUnitModel = (SymbolTable, StorageTable)
- type StorageTable = Map MemoryBlockName MemoryBlock
- data StructureTableEntry
- type Structure = [StructureTableEntry]
- type StructureTable = Map String Structure
- data MemoryBlock = MemoryBlock {
- blockSize :: Maybe Int
- storageClass :: StorageClass
- variables :: [Name]
- type SymbolTable = Map Name SymbolTableEntry
- data SymbolTableEntry
- type Dimensions = [(Int, Int)]
- data StorageClass
- = Static
- | Automatic
- | Constant
- | Common
- | Unspecified
- type Location = (MemoryBlockName, Offset)
- type MemoryBlockName = Name
- type Offset = Int
- data ExpVal
- type Type = SemType
- typeError :: SrcSpan -> String -> TypeError
- data SemType
- data CharacterLen
- type Kind = Int
Documentation
Constructors
| TypeError FilePath SrcSpan String | |
| UnknownType SrcSpan | |
| UnboundVariable Name | |
| UnknownField String |
Instances
type ProgramStructureTables = Map ProgramUnitName StructureTable Source #
Mapping from name of a program unit to relevant structure table
type ProgramFileModel = Map ProgramUnitName ProgramUnitModel Source #
Mapping from the name of a ProgramUnit to
its ProgramUnitModel
type ProgramUnitModel = (SymbolTable, StorageTable) Source #
The model to represent an individual ProgramUnit
type StorageTable = Map MemoryBlockName MemoryBlock Source #
Mapping from the name of a memory block to the information about it
data StructureTableEntry Source #
Data structurue for a single field of a structure
Constructors
| FieldEntry String Type | |
| UnionEntry [Structure] |
Instances
type Structure = [StructureTableEntry] Source #
type StructureTable = Map String Structure Source #
Map from a structure name to its internal structure, specifying members and their corresponding type. This can then be used to check the type of a data reference expression.
data MemoryBlock Source #
Structure to hold information about the named blocks of memory in the program
Constructors
| MemoryBlock | |
Fields
| |
Instances
type SymbolTable = Map Name SymbolTableEntry Source #
Symbol table containing all non-intrisic symbols declared in a program
data SymbolTableEntry Source #
An entry in the SymbolTable for some variable
Constructors
| SParameter | |
| SVariable | |
| SDummy | |
| SExternal | |
Instances
type Dimensions = [(Int, Int)] Source #
The declared dimensions of a staticically typed array variable type is of the form [(dim1_lower, dim1_upper), (dim2_lower, dim2_upper)]
data StorageClass Source #
The declared lifetimes of the variables in memory
Constructors
| Static | |
| Automatic | |
| Constant | |
| Common | |
| Unspecified |
Instances
type Location = (MemoryBlockName, Offset) Source #
The location of a variable, i.e. the MemoryBlockName that
contains it as well as the Offset to its location in memory
type MemoryBlockName = Name Source #
The name of block of memory
The evaluated value of a FORTRAN expression
Instances
typeError :: SrcSpan -> String -> TypeError Source #
Helper method for getting the FilePath out of SrcSpan
Semantic type assigned to variables.
BaseType stores the "type tag" given in syntax. SemTypes add metadata
(kind and length), and resolve some "simple" types to a core type with a
preset kind (e.g. `DOUBLE PRECISION` -> `REAL(8)`).
Fortran 90 (and beyond) features may not be well supported.
Constructors
| TInteger Kind | |
| TReal Kind | |
| TComplex Kind | |
| TLogical Kind | |
| TByte Kind | |
| TCharacter CharacterLen Kind | |
| TArray SemType (Maybe Dimensions) | Nothing denotes dynamic dimensions |
| TCustom String |
Instances
data CharacterLen #
Constructors
| CharLenStar | specified with a * |
| CharLenColon | specified with a : (Fortran2003) FIXME, possibly, with a more robust const-exp: |
| CharLenExp | specified with a non-trivial expression |
| CharLenInt Int | specified with a constant integer |
Instances
Orphan instances
| ToJSON ProgramUnitName Source # | |
Methods toJSON :: ProgramUnitName -> Value # toEncoding :: ProgramUnitName -> Encoding # toJSONList :: [ProgramUnitName] -> Value # toEncodingList :: [ProgramUnitName] -> Encoding # | |
| ToJSON Boz Source # | |
| ToJSON BozPrefix Source # | |
| ToJSONKey ProgramUnitName Source # | |
| FromJSON ProgramUnitName Source # | |
Methods parseJSON :: Value -> Parser ProgramUnitName # parseJSONList :: Value -> Parser [ProgramUnitName] # | |
| FromJSON Boz Source # | |
| FromJSON BozPrefix Source # | |
| FromJSONKey ProgramUnitName Source # | |