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