nanopass-0.0.3.0: Create compilers using small passes and many intermediate representations.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Nanopass.Internal.Representation

Description

This module holds type definitions that describe the internal representation of language syntaxen as understood by nanopass.

Synopsis

Types for Base Languages

The types Language, Nonterm, Production mediate between Haskell and the theory of context-free grammars (CFGs). Each of them is an intermediate representation that can be seen from two perspectives:

  • What Haskell concept do they map to?
  • What CFG concept do they map to?

We use something like usual, minimal definition of a CFG as a 4-tuple G = (V, Σ, R, S) where

  1. V is a set of non-terminals (named by $sel:nontermName:Nonterm)
  2. Σ is a set of terminals (which are just ordinary Haskell data types)
  3. R is a relation in V × (V ∪ Σ)*. Members of this relation are called rewrite rules (and map to the arguments of a Haskell data constructor).
  4. S is the start symbol, though it is not used by nanopass.

data Language v n Source #

This attributes a name to a set of grammatical types. Languages can have different names in different contexts; importantly, they must not be qualified when defining, but they may need to be dotted when referring to a language from another module.

Constructors

Language 

Fields

Instances

Instances details
Show n => Show (Language v n) Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

showsPrec :: Int -> Language v n -> ShowS #

show :: Language v n -> String #

showList :: [Language v n] -> ShowS #

data LanguageInfo v Source #

Seen as a Haskell entity, each Language is a set of mutually-recursive types. Seen from the persepctive of a CFG, each of these types is a non-terminal used to define the abstract grammar of a language.

See Language for attributing a name to a set of these types.

Constructors

LanguageInfo 

Fields

Instances

Instances details
Show (LanguageInfo v) Source # 
Instance details

Defined in Nanopass.Internal.Representation

data Nonterm v Source #

Seen as a Haskell entity, each Nonterm is a single type with some number of constructors. Seem from the perspective of a CFG, each Nonterm is… well, a non-terminal symbol.

Nonterms are the primary constituent of a Language.

Constructors

Nonterm 

Instances

Instances details
Show (Nonterm v) Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

showsPrec :: Int -> Nonterm v -> ShowS #

show :: Nonterm v -> String #

showList :: [Nonterm v] -> ShowS #

data Production v Source #

Seen as a Haskell entity, each Production maps to a constructor for a Nonterm data type. Seen from the perspective of a CFG, each Production maps to a single rewrite rule.

Productions are the primary constituent of Nonterms.

Constructors

Production 

Fields

Instances

Instances details
Show (Production v) Source # 
Instance details

Defined in Nanopass.Internal.Representation

data TypeDesc v Source #

Seen as a Haskell entity, a TypeDesc gives the type of an argument of a constructor (Production). Seen from the perspective of a CFG, each TypeDesc is a symbol (terminal or non-terminal) on the right-hand side of a rewrite rule.

TypeDescs are the primary constituent of Productions.

Constructors

RecursiveType UpName

a non-terminal symbol/recursive use of a Nonterm type

These types need not be applied to any arguments, the language $sel:langParams:LanguageInfo get auromatically applied.

VarType (Name v LowName)

allows the use of $sel:langParams:LanguageInfo as terminal symbols

CtorType (Name v UpDotName) [TypeDesc v]

allows the use of plain (not defined by nanopass) Haskell types, either as terminal symbols, or as combinators over non-terminal and terminal symbols

ListType (TypeDesc v)

nanopass has built-in knowledge of lists, so they are represented specially as opposed to with CtorType

MaybeType (TypeDesc v)

nanopass has built-in knowledge of optionals, so they are represented specially as opposed to with CtorType

NonEmptyType (TypeDesc v)

nanopass has built-in knowledge of non-empty lists, so they are represented specially as opposed to with CtorType

UnitType

nanopass has built-in knowledge of the unit type, so they are represented specially as opposed to with CtorType

TupleType (TypeDesc v) (TypeDesc v) [TypeDesc v]

nanopass has built-in knowledge of the tuple types, so they are represented specially as opposed to with CtorType

Instances

Instances details
Show (TypeDesc v) Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

showsPrec :: Int -> TypeDesc v -> ShowS #

show :: TypeDesc v -> String #

showList :: [TypeDesc v] -> ShowS #

Eq (TypeDesc v) Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

(==) :: TypeDesc v -> TypeDesc v -> Bool #

(/=) :: TypeDesc v -> TypeDesc v -> Bool #

Types for Modifying Manguages

Types for Passes

data Pass Source #

Instances

Instances details
Show Pass Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

showsPrec :: Int -> Pass -> ShowS #

show :: Pass -> String #

showList :: [Pass] -> ShowS #

Helper Types

data UpName Source #

Strings matching [A-Z][a-zA-Z0-9_]

Instances

Instances details
Show UpName Source # 
Instance details

Defined in Nanopass.Internal.Representation

Eq UpName Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

(==) :: UpName -> UpName -> Bool #

(/=) :: UpName -> UpName -> Bool #

Ord UpName Source # 
Instance details

Defined in Nanopass.Internal.Representation

toUpName :: String -> Maybe UpName Source #

Introduction form for UpName

fromUpName :: UpName -> String Source #

Elimination form for UpName

data LowName Source #

Strings matching [a-z][a-zA-Z0-9_]

Instances

Instances details
Show LowName Source # 
Instance details

Defined in Nanopass.Internal.Representation

Eq LowName Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

(==) :: LowName -> LowName -> Bool #

(/=) :: LowName -> LowName -> Bool #

Ord LowName Source # 
Instance details

Defined in Nanopass.Internal.Representation

toLowName :: String -> Maybe LowName Source #

Introduction form for LowName

fromLowName :: LowName -> String Source #

Elimination form for LowName

data UpDotName Source #

Strings matching [A-Z][a-zA-Z0-9_](:[A-Z][a-zA-Z0-9_])*

toUpDotName :: String -> Maybe UpDotName Source #

Introduction form for UpDotName

fromUpDotName :: UpDotName -> String Source #

Elimination form for UpDotName

splitUpDotName :: UpDotName -> ([UpName], UpName) Source #

Get the last part of a dotted name and it's prefix

unDotted :: UpName -> UpDotName Source #

Conversion from UpName

upDotQualifier :: UpDotName -> [UpName] Source #

Get the parts of a dotted name that come before the last dot

upDotBase :: UpDotName -> UpName Source #

Get the last part of a dotted name

upDotChBase :: UpDotName -> UpName -> UpDotName Source #

Create a dotted name identical to the first, but with the last part replaced

data Name v n where Source #

Constructors

SourceName 

Fields

ValidName 

Fields

Instances

Instances details
HasField "name" (Name v n) n Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

getField :: Name v n -> n #

Show n => Show (Name v n) Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

showsPrec :: Int -> Name v n -> ShowS #

show :: Name v n -> String #

showList :: [Name v n] -> ShowS #

Eq n => Eq (Name v n) Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

(==) :: Name v n -> Name v n -> Bool #

(/=) :: Name v n -> Name v n -> Bool #

Ord n => Ord (Name v n) Source # 
Instance details

Defined in Nanopass.Internal.Representation

Methods

compare :: Name v n -> Name v n -> Ordering #

(<) :: Name v n -> Name v n -> Bool #

(<=) :: Name v n -> Name v n -> Bool #

(>) :: Name v n -> Name v n -> Bool #

(>=) :: Name v n -> Name v n -> Bool #

max :: Name v n -> Name v n -> Name v n #

min :: Name v n -> Name v n -> Name v n #

data Validate Source #

Constructors

Valid 
Unvalidated