Copyright | (C) 2025 - Eitan Chatav |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Eitan Chatav <eitan.chatav@gmail.com> |
Stability | provisional |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Text.Grammar.Distributor
Contents
Description
See Joachim Breitner, Showcasing Applicative for idea to unify grammars.
Synopsis
- type Grammar a = forall p. Grammatical p => p a a
- type Grammarr a b = forall p. Grammatical p => p a a -> p b b
- class (Alternator p, Filtrator p, Tokenized Char Char p, forall t. t ~ p () () => IsString t) => Grammatical p where
- inClass :: String -> p Char Char
- notInClass :: String -> p Char Char
- inCategory :: GeneralCategory -> p Char Char
- notInCategory :: GeneralCategory -> p Char Char
- rule :: String -> p a b -> p a b
- ruleRec :: String -> (p a b -> p a b) -> p a b
- data RegEx
- regexString :: RegEx -> String
- regexGrammar :: Grammar RegEx
- genReadS :: Grammar a -> ReadS a
- readGrammar :: Grammar a -> String -> [a]
- genShowS :: Alternative f => Grammar a -> a -> f ShowS
- showGrammar :: Alternative f => Grammar a -> a -> f String
- genRegEx :: Grammar a -> RegEx
- genGrammar :: Grammar a -> [(String, RegEx)]
- printGrammar :: Grammar a -> IO ()
Grammar
type Grammar a = forall p. Grammatical p => p a a Source #
Grammar
is a Backus-Naur form grammar,
extended by regular expressions,
embedded in Haskell.
To see an example of a Grammar
, look at regexGrammar
.
type Grammarr a b = forall p. Grammatical p => p a a -> p b b Source #
class (Alternator p, Filtrator p, Tokenized Char Char p, forall t. t ~ p () () => IsString t) => Grammatical p where Source #
The Grammatical
class extends Alternator
& Filtrator
which gives it Kleene's regular expression combinators. It also has
rule
and ruleRec
for defining grammar rules and
recursive grammar rules, i.e. nonterminal expressions. Finally,
terminal expressions can be expressed as string literals since
Grammatical
also implies IsString
.
Prism
s and PartialIso
s can act
on Grammatical
terms via the >?<
combinator,
analogously to how constructors act on Applicative
parsers
with <$>
.
One can create new "generators" from a Grammar
by defining
instances of Grammatical
. For instance, one could create
generators for Parsec style parsers, and use rule
for
labeling of parse errors.
Minimal complete definition
Nothing
Methods
inClass :: String -> p Char Char Source #
Only characters which are in the given String
.
notInClass :: String -> p Char Char Source #
Only characters which are not in the given String
.
inCategory :: GeneralCategory -> p Char Char Source #
Only characters which are in the given GeneralCategory
.
notInCategory :: GeneralCategory -> p Char Char Source #
Only characters which are not in the given GeneralCategory
.
rule :: String -> p a b -> p a b Source #
A nonterminal rule.
ruleRec :: String -> (p a b -> p a b) -> p a b Source #
A recursive, nonterminal rule.
Instances
RegEx
A version of regular expressions extended by nonterminals.
Constructors
Terminal String | abc123etc\. |
Sequence RegEx RegEx | xy |
Fail | \q |
Alternate RegEx RegEx | x|y |
KleeneOpt RegEx | x? |
KleeneStar RegEx | x* |
KleenePlus RegEx | x+ |
AnyChar | . |
InClass String | [abc] |
NotInClass String | [^abc] |
InCategory GeneralCategory | \p{Lu} |
NotInCategory GeneralCategory | \P{Ll} |
NonTerminal String | \q{rule-name} |
Instances
regexString :: RegEx -> String Source #
regexGrammar :: Grammar RegEx Source #
regexGrammar
provides an important example of a Grammar
.
Take a look at the source to see its definition.
>>>
printGrammar regexGrammar
start = \q{regex} alternate = \q{sequence}(\|\q{sequence})* any = \. atom = \q{nonterminal}|\q{fail}|\q{class-in}|\q{class-not-in}|\q{category-in}|\q{category-not-in}|\q{char}|\q{any}|\q{parenthesized} category = Ll|Lu|Lt|Lm|Lo|Mn|Mc|Me|Nd|Nl|No|Pc|Pd|Ps|Pe|Pi|Pf|Po|Sm|Sc|Sk|So|Zs|Zl|Zp|Cc|Cf|Cs|Co|Cn category-in = \\p\{\q{category}\} category-not-in = \\P\{\q{category}\} char = \q{char-literal}|\q{char-escaped} char-escaped = \\[\$\(\)\*\+\.\?\[\\\]\^\{\|\}] char-literal = [^\$\(\)\*\+\.\?\[\\\]\^\{\|\}] class-in = \[\q{char}*\] class-not-in = \[\^\q{char}*\] expression = \q{terminal}|\q{kleene-optional}|\q{kleene-star}|\q{kleene-plus}|\q{atom} fail = \\q kleene-optional = \q{atom}\? kleene-plus = \q{atom}\+ kleene-star = \q{atom}\* nonterminal = \\q\{\q{char}*\} parenthesized = \(\q{regex}\) regex = \q{alternate} sequence = \q{expression}* terminal = \q{char}+
Generators
showGrammar :: Alternative f => Grammar a -> a -> f String Source #