| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Symantic.Parser.Grammar
Synopsis
- type Grammar tok repr = (Applicable repr, Alternable repr, Satisfiable tok repr, Letable Name repr, Selectable repr, Matchable repr, Foldable repr, Lookable repr)
- grammar :: Grammar tok repr => ObserveSharing Name (OptimizeGrammar repr) a -> repr a
- showGrammar :: ObserveSharing Name (OptimizeGrammar (ViewGrammar showName)) a -> String
- module Symantic.Parser.Grammar.Combinators
- module Symantic.Parser.Grammar.Fixity
- module Symantic.Parser.Grammar.Optimize
- module Symantic.Parser.Grammar.ObserveSharing
- module Symantic.Parser.Grammar.Write
- module Symantic.Parser.Grammar.View
- class Letable letName repr where
Documentation
type Grammar tok repr = (Applicable repr, Alternable repr, Satisfiable tok repr, Letable Name repr, Selectable repr, Matchable repr, Foldable repr, Lookable repr) Source #
grammar :: Grammar tok repr => ObserveSharing Name (OptimizeGrammar repr) a -> repr a Source #
A usual pipeline to interpret Combinators:
observeSharing then optimizeGrammar then a polymorphic (repr).
showGrammar :: ObserveSharing Name (OptimizeGrammar (ViewGrammar showName)) a -> String Source #
An usual pipeline to show Combinators:
observeSharing then optimizeGrammar then viewGrammar then show.
module Symantic.Parser.Grammar.View
class Letable letName repr where Source #
This class is not for end-users like usual symantic operators,
here def and ref are introduced by observeSharing.
Minimal complete definition
Nothing
Methods
def :: letName -> repr a -> repr a Source #
( let-binds def letName x)(letName) to be equal to (x).
ref :: Bool -> letName -> repr a Source #
( is a reference to ref isRec letName)(letName).
(isRec) is True iif. this reference is recursive,
ie. is reachable within its definition.
def :: Liftable1 repr => Letable letName (Output repr) => letName -> repr a -> repr a Source #
( let-binds def letName x)(letName) to be equal to (x).
ref :: Liftable repr => Letable letName (Output repr) => Bool -> letName -> repr a Source #
Instances
| ShowLetName sN letName => Letable letName (WriteGrammar sN) Source # | |
Defined in Symantic.Parser.Grammar.Write Methods def :: letName -> WriteGrammar sN a -> WriteGrammar sN a Source # ref :: Bool -> letName -> WriteGrammar sN a Source # | |
| ShowLetName sN letName => Letable letName (ViewGrammar sN) Source # | |
Defined in Symantic.Parser.Grammar.View Methods def :: letName -> ViewGrammar sN a -> ViewGrammar sN a Source # ref :: Bool -> letName -> ViewGrammar sN a Source # | |
| (Letable letName repr, Typeable letName) => Letable letName (SomeComb repr) Source # | |
| Routinable repr => Letable Name (Program repr inp) Source # | |
| (Letable letName repr, Eq letName, Hashable letName) => Letable letName (CleanDefs letName repr) Source # | |
| (Letable letName repr, MakeLetName letName, Eq letName, Hashable letName) => Letable letName (ObserveSharing letName repr) Source # | |
Defined in Symantic.Univariant.Letable Methods def :: letName -> ObserveSharing letName repr a -> ObserveSharing letName repr a Source # ref :: Bool -> letName -> ObserveSharing letName repr a Source # | |
| Letable letName repr => Trans (Comb (Letable letName) repr) repr Source # | |
| data Comb (Letable letName) repr Source # | |