]> Git — Sourcephile - haskell/symantic.git/blob - symantic-grammar/Language/Symantic/Grammar/EBNF.hs
Sync with ghc-8.2.2 and megaparsec-6.3.0.
[haskell/symantic.git] / symantic-grammar / Language / Symantic / Grammar / EBNF.hs
1 module Language.Symantic.Grammar.EBNF where
2
3 import Control.Applicative (Applicative(..))
4 import Control.Monad
5 import Data.Semigroup
6 import Data.Text (Text)
7 import qualified Data.Text as Text
8
9 import Language.Symantic.Grammar.Meta
10 import Language.Symantic.Grammar.Fixity
11
12 -- * Type 'EBNF'
13 -- | Extended Backus-Naur-Form, following the
14 -- <http://standards.iso.org/ittf/PubliclyAvailableStandards/s026153_ISO_IEC_14977_1996(E).zip ISO-IEC-14977>
15 -- notations, augmented with the following notations:
16 --
17 -- * @("U+", code_point)@: for <http://unicode.org/versions/Unicode8.0.0/ ISO-IEC-10646> (aka. Unicode).
18 -- * @(char, "…", char)@: for character range.
19 -- * @(rule, "&", rule)@: for the intersection.
20 -- * @(rule, "-", rule)@: for the difference.
21 -- * @(rule, " ", rule)@: for rule application.
22 --
23 -- Inherited attributes are:
24 --
25 -- * 'RuleMode' is the requested rendering mode of a 'Rule' (body or reference).
26 -- * 'Infix' and 'Side' are the properties of the parent operator,
27 -- used to enclose the operand in parenthesis only when needed.
28 --
29 -- Synthetized attributes are:
30 --
31 -- * 'Text' of the 'EBNF' rendition.
32 newtype EBNF a = EBNF { unEBNF :: RuleMode -> (Infix, Side) -> Text }
33 instance Gram_Reader st EBNF where
34 askBefore (EBNF e) = EBNF e
35 askAfter (EBNF e) = EBNF e
36 instance Gram_State st EBNF where
37 stateBefore (EBNF e) = EBNF e
38 stateAfter (EBNF e) = EBNF e
39 instance Gram_Error err EBNF where
40 catch (EBNF e) = EBNF e
41
42 -- | Get textual rendition of given 'EBNF'.
43 runEBNF :: EBNF a -> Text
44 runEBNF (EBNF g) = g RuleMode_Body (infixN0, SideL)
45
46 -- | Get textual rendition of given 'RuleEBNF'.
47 renderEBNF :: RuleEBNF a -> Text
48 renderEBNF = runEBNF . unRuleEBNF
49
50 -- | 'EBNF' returns a constant rendition.
51 ebnf_const :: Text -> EBNF a
52 ebnf_const t = EBNF $ \_rm _op -> t
53
54 -- | 'EBNF' which adds an argument to be applied.
55 ebnf_arg :: EBNF a -> EBNF b -> EBNF ()
56 ebnf_arg (EBNF a) (EBNF b) = EBNF $ \bo po -> parenInfix po op $
57 a bo (op, SideL) <> " " <> b bo (op, SideR)
58 where op = infixL 11
59 infixl 5 `ebnf_arg`
60
61 -- ** Type 'RuleMode'
62 data RuleMode
63 = RuleMode_Body -- ^ Request to generate the body of the rule.
64 | RuleMode_Ref -- ^ Request to generate a reference to the rule.
65 deriving (Eq, Show)
66
67 -- * Type 'Rule'
68 type Rule a = a -> a
69
70 -- ** Class 'Gram_Rule'
71 class Gram_Rule g where
72 rule :: Text -> Rule (g a)
73 rule _n = id
74 rule1 :: Text -> Rule (g a -> g b)
75 rule1 _n g = g
76 rule2 :: Text -> Rule (g a -> g b -> g c)
77 rule2 _n g = g
78 rule3 :: Text -> Rule (g a -> g b -> g c -> g d)
79 rule3 _n g = g
80 rule4 :: Text -> Rule (g a -> g b -> g c -> g d -> g e)
81 rule4 _n g = g
82
83 -- * Type 'RuleEBNF'
84 newtype RuleEBNF a = RuleEBNF { unRuleEBNF :: EBNF a }
85 deriving (Functor, Applicative)
86 deriving instance Gram_RuleEBNF RuleEBNF
87 deriving instance Gram_Error err RuleEBNF
88 deriving instance Gram_Reader st RuleEBNF
89 deriving instance Gram_State st RuleEBNF
90 instance Gram_Rule RuleEBNF where
91 rule n = ruleEBNF (ebnf_const n)
92 rule1 n g a = ruleEBNF (ebnf_const n `ebnf_arg` unRuleEBNF a) (g a)
93 rule2 n g a b = ruleEBNF (ebnf_const n `ebnf_arg` unRuleEBNF a `ebnf_arg` unRuleEBNF b) (g a b)
94 rule3 n g a b c = ruleEBNF (ebnf_const n `ebnf_arg` unRuleEBNF a `ebnf_arg` unRuleEBNF b `ebnf_arg` unRuleEBNF c) (g a b c)
95 rule4 n g a b c d = ruleEBNF (ebnf_const n `ebnf_arg` unRuleEBNF a `ebnf_arg` unRuleEBNF b `ebnf_arg` unRuleEBNF c `ebnf_arg` unRuleEBNF d) (g a b c d)
96
97 -- ** Class 'Gram_RuleEBNF'
98 -- | Symantics for rendering 'EBNF' rules.
99 --
100 -- * 'ruleEBNF' renders a rule, either its body or a reference to it, according to 'RuleMode'.
101 -- * 'argEBNF' renders an argument.
102 class Gram_RuleEBNF g where
103 ruleEBNF :: EBNF () -> g a -> RuleEBNF a
104 argEBNF :: Text -> g a
105 instance Show (EBNF a) where
106 show = Text.unpack . runEBNF
107 instance Functor EBNF where
108 fmap _f (EBNF x) = EBNF x
109 instance Applicative EBNF where
110 pure _ = ebnf_const $ "\"\""
111 EBNF f <*> EBNF x = EBNF $ \bo po -> parenInfix po op $
112 f bo (op, SideL) <> ", " <> x bo (op, SideR)
113 where op = infixB SideL 10
114 instance Gram_Rule EBNF where
115 rule n g = EBNF $ \rm po ->
116 case rm of
117 RuleMode_Body -> unEBNF g RuleMode_Ref po
118 RuleMode_Ref -> n
119 rule1 n g a = EBNF $ \rm po ->
120 case rm of
121 RuleMode_Body -> unEBNF (g a) RuleMode_Ref po
122 RuleMode_Ref -> unEBNF (ebnf_const n `ebnf_arg` a) RuleMode_Ref po
123 rule2 n g a b = EBNF $ \rm po ->
124 case rm of
125 RuleMode_Body -> unEBNF (g a b) RuleMode_Ref po
126 RuleMode_Ref -> unEBNF (ebnf_const n `ebnf_arg` a `ebnf_arg` b) RuleMode_Ref po
127 rule3 n g a b c = EBNF $ \rm po ->
128 case rm of
129 RuleMode_Body -> unEBNF (g a b c) RuleMode_Ref po
130 RuleMode_Ref -> unEBNF (ebnf_const n `ebnf_arg` a `ebnf_arg` b `ebnf_arg` c) RuleMode_Ref po
131 rule4 n g a b c d = EBNF $ \rm po ->
132 case rm of
133 RuleMode_Body -> unEBNF (g a b c d) RuleMode_Ref po
134 RuleMode_Ref -> unEBNF (ebnf_const n `ebnf_arg` a `ebnf_arg` b `ebnf_arg` c `ebnf_arg` d) RuleMode_Ref po
135 instance Gram_RuleEBNF EBNF where
136 argEBNF = ebnf_const
137 ruleEBNF call body =
138 RuleEBNF $ EBNF $ \mo po ->
139 case mo of
140 RuleMode_Ref -> unEBNF call mo po
141 RuleMode_Body ->
142 Text.intercalate " "
143 [ unEBNF call RuleMode_Ref (infixN0, SideL)
144 , "="
145 , unEBNF body RuleMode_Ref (infixN0, SideR)
146 , ";"
147 ]