]> Git — Sourcephile - haskell/symantic-parser.git/blob - src/Symantic/Parser/Grammar.hs
replace ValueCode by Production
[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.Fixity
7 , module Symantic.Parser.Grammar.Optimize
8 , module Symantic.Parser.Grammar.ObserveSharing
9 , module Symantic.Parser.Grammar.Production
10 , module Symantic.Parser.Grammar.Write
11 , module Symantic.Parser.Grammar.View
12 , Letable(..)
13 , Letsable(..)
14 ) where
15 import Symantic.Parser.Grammar.Combinators
16 import Symantic.Parser.Grammar.Fixity
17 import Symantic.Parser.Grammar.ObserveSharing
18 import Symantic.Parser.Grammar.Optimize
19 import Symantic.Parser.Grammar.Production
20 import Symantic.Parser.Grammar.View
21 import Symantic.Parser.Grammar.Write
22
23 import Control.DeepSeq (NFData)
24 import Data.Eq (Eq(..))
25 import Data.Function ((.))
26 import Data.String (String)
27 import Data.Typeable (Typeable)
28 import Text.Show (Show(..))
29 import qualified Language.Haskell.TH.Syntax as TH
30
31 -- * Class 'Grammarable'
32 type Grammarable tok repr =
33 ( CombAlternable repr
34 , CombApplicable repr
35 , CombFoldable repr
36 , Letable TH.Name repr
37 , Letsable TH.Name repr
38 , CombLookable repr
39 , CombMatchable repr
40 , CombSatisfiable tok repr
41 , CombSelectable repr
42 , Eq 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