]> Git — Sourcephile - haskell/symantic-parser.git/blob - src/Symantic/Parser/Grammar.hs
grammar: fix Ord SomeFailure
[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.Ord (Ord)
26 import Data.Function ((.))
27 import Data.String (String)
28 import Data.Typeable (Typeable)
29 import Text.Show (Show(..))
30 import qualified Language.Haskell.TH.Syntax as TH
31
32 -- * Class 'Grammarable'
33 type Grammarable tok repr =
34 ( CombAlternable repr
35 , CombApplicable repr
36 , CombFoldable repr
37 , Letable TH.Name repr
38 , Letsable TH.Name repr
39 , CombLookable repr
40 , CombMatchable repr
41 , CombSatisfiable tok repr
42 , CombSelectable repr
43 , Eq tok
44 , Ord tok
45 , TH.Lift tok
46 , NFData tok
47 , Show tok
48 , Typeable tok
49 )
50
51 -- | A usual pipeline to interpret 'Comb'inators:
52 -- 'observeSharing' then 'optimizeGrammar' then a polymorphic @(repr)@.
53 grammar ::
54 Grammarable tok repr =>
55 ObserveSharing TH.Name
56 (OptimizeGrammar repr) a ->
57 repr a
58 grammar = optimizeGrammar . observeSharing
59
60 -- | An usual pipeline to show 'Comb'inators:
61 -- 'observeSharing' then 'optimizeGrammar' then 'viewGrammar' then 'show'.
62 showGrammar :: forall showName a tok repr.
63 repr ~ ObserveSharing TH.Name (OptimizeGrammar (ViewGrammar showName)) =>
64 ShowLetName showName TH.Name =>
65 Grammarable tok repr =>
66 repr a -> String
67 showGrammar = show . viewGrammar . grammar @tok