]> Git — Sourcephile - haskell/symantic-parser.git/blob - src/Symantic/Parser/Grammar.hs
use symantic-base
[haskell/symantic-parser.git] / src / Symantic / Parser / Grammar.hs
1 {-# LANGUAGE AllowAmbiguousTypes #-} -- For grammar
2 {-# LANGUAGE ConstraintKinds #-} -- For Grammarable
3 module Symantic.Parser.Grammar
4 ( module Symantic.Parser.Grammar
5 , module Symantic.Parser.Grammar.Combinators
6 , module Symantic.Parser.Grammar.Optimize
7 , module Symantic.Parser.Grammar.ObserveSharing
8 , module Symantic.Parser.Grammar.Production
9 , module Symantic.Parser.Grammar.Write
10 , module Symantic.Parser.Grammar.View
11 , Letable(..)
12 , Letsable(..)
13 ) where
14 import Symantic.Parser.Grammar.Combinators
15 import Symantic.Parser.Grammar.ObserveSharing
16 import Symantic.Parser.Grammar.Optimize
17 import Symantic.Parser.Grammar.Production
18 import Symantic.Parser.Grammar.View
19 import Symantic.Parser.Grammar.Write
20
21 import Control.DeepSeq (NFData)
22 import Data.Eq (Eq)
23 import Data.Ord (Ord)
24 import Data.Function ((.))
25 import Data.String (String)
26 import Data.Typeable (Typeable)
27 import Text.Show (Show(..))
28 import qualified Language.Haskell.TH.Syntax as TH
29
30 -- * Class 'Grammarable'
31 type Grammarable tok repr =
32 ( CombAlternable repr
33 , CombApplicable repr
34 , CombFoldable repr
35 , Letable TH.Name repr
36 , Letsable TH.Name repr
37 , CombLookable repr
38 , CombMatchable repr
39 , CombSatisfiable tok repr
40 , CombSelectable repr
41 , Eq tok
42 , Ord tok
43 , TH.Lift tok
44 , NFData tok
45 , Show tok
46 , Typeable tok
47 )
48
49 -- | A usual pipeline to interpret 'Comb'inators:
50 -- 'observeSharing' then 'optimizeGrammar' then a polymorphic @(repr)@.
51 grammar ::
52 Grammarable tok repr =>
53 ObserveSharing TH.Name
54 (OptimizeGrammar repr) a ->
55 repr a
56 grammar = optimizeGrammar . observeSharing
57
58 -- | An usual pipeline to show 'Comb'inators:
59 -- 'observeSharing' then 'optimizeGrammar' then 'viewGrammar' then 'show'.
60 showGrammar :: forall showName a tok repr.
61 repr ~ ObserveSharing TH.Name (OptimizeGrammar (ViewGrammar showName)) =>
62 ShowLetName showName TH.Name =>
63 Grammarable tok repr =>
64 repr a -> String
65 showGrammar = show . viewGrammar . grammar @tok