Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Grammar repr = (Applicable repr, Alternable repr, Letable Name repr, Selectable repr, Matchable repr, Foldable repr, Lookable repr)
- grammar :: Grammar repr => ObserveSharing Name (OptimizeComb Name repr) a -> repr a
- showGrammar :: ObserveSharing Name (OptimizeComb Name DumpComb) 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.Dump
- class Letable letName repr where
Documentation
type Grammar repr = (Applicable repr, Alternable repr, Letable Name repr, Selectable repr, Matchable repr, Foldable repr, Lookable repr) Source #
grammar :: Grammar repr => ObserveSharing Name (OptimizeComb Name repr) a -> repr a Source #
A usual pipeline to interpret Comb
inators:
observeSharing
then optimizeComb
then a polymorphic (repr)
.
showGrammar :: ObserveSharing Name (OptimizeComb Name DumpComb) a -> String Source #
A usual pipeline to show Comb
inators:
observeSharing
then optimizeComb
then dumpComb
then show
.
module Symantic.Parser.Grammar.Dump
class Letable letName repr where Source #
This class is not for manual usage like usual symantic operators,
here def
and ref
are introduced by observeSharing
.
Nothing
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 ref
erence is recursive,
ie. is reachable within its def
inition.
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
Show letName => Letable letName WriteComb Source # | |
Show letName => Letable letName DumpComb Source # | |
Letable Name (Comb repr) Source # | |
Letable Name (Machine 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 def :: letName -> ObserveSharing letName repr a -> ObserveSharing letName repr a Source # ref :: Bool -> letName -> ObserveSharing letName repr a Source # | |
Letable letName (Comb repr) => Letable letName (OptimizeComb letName repr) Source # | |
Defined in Symantic.Parser.Grammar.Optimize def :: letName -> OptimizeComb letName repr a -> OptimizeComb letName repr a Source # ref :: Bool -> letName -> OptimizeComb letName repr a Source # |