Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module holds type definitions that describe the internal representation of language syntaxen as understood by nanopass.
Synopsis
- data Language v n = Language {
- langName :: Name v n
- langInfo :: LanguageInfo v
- data LanguageInfo v = LanguageInfo {
- langParams :: ![Name v LowName]
- nonterms :: !(Map UpName (Nonterm v))
- originalProgram :: !(Maybe String)
- baseDefdLang :: !(Maybe (Language 'Valid UpDotName))
- data Nonterm v = Nonterm {
- nontermName :: !(Name v UpName)
- productions :: !(Map UpName (Production v))
- data Production v = Production {}
- data TypeDesc v
- data LangMod = LangMod {}
- data NontermsEdit
- data ProductionsEdit
- data Pass = Pass {}
- data UpName
- toUpName :: String -> Maybe UpName
- fromUpName :: UpName -> String
- data LowName
- toLowName :: String -> Maybe LowName
- fromLowName :: LowName -> String
- data UpDotName
- toUpDotName :: String -> Maybe UpDotName
- fromUpDotName :: UpDotName -> String
- splitUpDotName :: UpDotName -> ([UpName], UpName)
- unDotted :: UpName -> UpDotName
- upDotQualifier :: UpDotName -> [UpName]
- upDotBase :: UpDotName -> UpName
- upDotChBase :: UpDotName -> UpName -> UpDotName
- data Name v n where
- SourceName :: {..} -> Name 'Unvalidated n
- ValidName :: {..} -> Name 'Valid n
- data Validate
- = Valid
- | Unvalidated
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
- V is a set of non-terminals (named by
$sel:nontermName:Nonterm
) - Σ is a set of terminals (which are just ordinary Haskell data types)
- 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).
- S is the start symbol, though it is not used by nanopass.
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.
Language | |
|
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.
Instances
Show (LanguageInfo v) Source # | |
Defined in Nanopass.Internal.Representation showsPrec :: Int -> LanguageInfo v -> ShowS # show :: LanguageInfo v -> String # showList :: [LanguageInfo v] -> ShowS # |
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.
Nonterm | |
|
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.
Production
s are the primary constituent of Nonterm
s.
Instances
Show (Production v) Source # | |
Defined in Nanopass.Internal.Representation showsPrec :: Int -> Production v -> ShowS # show :: Production v -> String # showList :: [Production v] -> ShowS # |
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.
TypeDesc
s are the primary constituent of Production
s.
RecursiveType UpName | a non-terminal symbol/recursive use of a These types need not be applied to any arguments, the language |
VarType (Name v LowName) | allows the use of |
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 |
MaybeType (TypeDesc v) | nanopass has built-in knowledge of optionals, so they are represented specially as opposed to with |
NonEmptyType (TypeDesc v) | nanopass has built-in knowledge of non-empty lists, so they are represented specially as opposed to with |
UnitType | nanopass has built-in knowledge of the unit type, so they are represented specially as opposed to with |
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 |
Types for Modifying Manguages
LangMod | |
|
data NontermsEdit Source #
Instances
Show NontermsEdit Source # | |
Defined in Nanopass.Internal.Representation showsPrec :: Int -> NontermsEdit -> ShowS # show :: NontermsEdit -> String # showList :: [NontermsEdit] -> ShowS # |
data ProductionsEdit Source #
Instances
Show ProductionsEdit Source # | |
Defined in Nanopass.Internal.Representation showsPrec :: Int -> ProductionsEdit -> ShowS # show :: ProductionsEdit -> String # showList :: [ProductionsEdit] -> ShowS # |
Types for Passes
Helper Types
Strings matching [A-Z][a-zA-Z0-9_]
Strings matching [a-z][a-zA-Z0-9_]
Strings matching [A-Z][a-zA-Z0-9_](:[A-Z][a-zA-Z0-9_])*
splitUpDotName :: UpDotName -> ([UpName], UpName) Source #
Get the last part of a dotted name and it's prefix
upDotQualifier :: UpDotName -> [UpName] Source #
Get the parts of a dotted name that come before the last dot
upDotChBase :: UpDotName -> UpName -> UpDotName Source #
Create a dotted name identical to the first, but with the last part replaced
SourceName | |
| |
ValidName | |