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