1 module Language.Symantic.Grammar.Operators where
3 import Control.Applicative (Applicative(..))
5 import Data.Foldable hiding (any)
6 import Prelude hiding (any)
8 import Language.Symantic.Grammar.EBNF
9 import Language.Symantic.Grammar.Terminal
10 import Language.Symantic.Grammar.Regular
11 import Language.Symantic.Grammar.ContextFree
24 :: CF g a -- ^ expression
25 -> CF g (Unifix, a -> a) -- ^ prefix operator
26 -> CF g (Infix , a -> a -> a) -- ^ infix operator
27 -> CF g (Unifix, a -> a) -- ^ postfix operator
28 -> CF g (Either Error_Fixity a)
29 operators g prG iG poG =
35 -> CF g (Unifix, a -> a)
36 -> CF g (Infix , a -> a -> a)
37 -> CF g (Unifix, a -> a)
38 -> CF g (Either Error_Fixity (OpTree a))
39 go = rule4 "operators" $ \aG preG inG postG ->
43 (foldl' (flip insert_unifix) (OpNode0 a) posts)
46 Just (in_, b) -> insert_infix nod_a in_ b
47 Nothing -> Right nod_a)
51 <*> option Nothing (curry Just <$> try inG <*> go aG preG inG postG)
53 insert_unifix :: (Unifix, a -> a) -> OpTree a -> OpTree a
54 insert_unifix a@(uni_a@(Prefix prece_a), op_a) nod_b =
56 OpNode0{} -> OpNode1 uni_a op_a nod_b
57 OpNode1 Prefix{} _op_b _nod -> OpNode1 uni_a op_a nod_b
58 OpNode1 uni_b@(Postfix prece_b) op_b nod ->
59 case prece_b `compare` prece_a of
60 GT -> OpNode1 uni_a op_a nod_b
61 EQ -> OpNode1 uni_a op_a nod_b
62 LT -> OpNode1 uni_b op_b $ insert_unifix a nod
63 OpNode2 inf_b op_b l r ->
64 case infix_prece inf_b `compare` prece_a of
65 GT -> OpNode1 uni_a op_a nod_b
66 EQ -> OpNode1 uni_a op_a nod_b
67 LT -> OpNode2 inf_b op_b (insert_unifix a l) r
68 insert_unifix a@(uni_a@(Postfix prece_a), op_a) nod_b =
70 OpNode0{} -> OpNode1 uni_a op_a nod_b
71 OpNode1 uni_b@(Prefix prece_b) op_b nod ->
72 case prece_b `compare` prece_a of
73 GT -> OpNode1 uni_a op_a nod_b
74 EQ -> OpNode1 uni_a op_a nod_b
75 LT -> OpNode1 uni_b op_b $ insert_unifix a nod
76 OpNode1 Postfix{} _op_b _nod -> OpNode1 uni_a op_a nod_b
77 OpNode2 inf_b op_b l r ->
78 case infix_prece inf_b `compare` prece_a of
79 GT -> OpNode1 uni_a op_a nod_b
80 EQ -> OpNode1 uni_a op_a nod_b
81 LT -> OpNode2 inf_b op_b l (insert_unifix a r)
85 -> (Infix, a -> a -> a)
86 -> Either Error_Fixity (OpTree a)
87 -> Either Error_Fixity (OpTree a)
88 insert_infix nod_a in_@(inf_a, op_a) e_nod_b = do
91 OpNode0{} -> Right $ OpNode2 inf_a op_a nod_a nod_b
92 OpNode1 uni_b op_b nod ->
93 case unifix_prece uni_b `compare` infix_prece inf_a of
94 EQ -> Right $ OpNode2 inf_a op_a nod_a nod_b
95 GT -> Right $ OpNode2 inf_a op_a nod_a nod_b
97 n <- insert_infix nod_a in_ (Right nod)
98 Right $ OpNode1 uni_b op_b n
99 OpNode2 inf_b op_b l r ->
100 case infix_prece inf_b `compare` infix_prece inf_a of
101 GT -> Right $ OpNode2 inf_a op_a nod_a nod_b
103 n <- insert_infix nod_a in_ (Right l)
104 Right $ OpNode2 inf_b op_b n r
110 case (ass <$> infix_assoc inf_b, ass <$> infix_assoc inf_a) of
111 (Just L, Just L) -> do
112 n <- insert_infix nod_a in_ (Right l)
113 Right $ OpNode2 inf_b op_b n r
115 Right $ OpNode2 inf_a op_a nod_a nod_b
116 _ -> Left $ Error_Fixity_Infix_not_combinable inf_a inf_b
117 -- NOTE: non-associating infix ops
118 -- of the same precedence cannot be mixed.
119 infixrG :: CF g a -> CF g (a -> a -> a) -> CF g a
120 infixrG = rule2 "infixr" $ \g opG ->
122 Just (op, b) -> a `op` b
125 <*> option Nothing (try $ curry Just <$> opG <*> infixrG g opG)
126 infixlG :: CF g a -> CF g (a -> a -> a) -> CF g a
127 infixlG = rule2 "infixl" $ \g opG ->
128 -- NOTE: infixl uses the same grammar than infixr,
129 -- but build the parsed value by applying
130 -- the operator in the opposite way.
133 go :: CF g a -> CF g (a -> a -> a) -> CF g ((a -> a) -> a)
136 Just (op, kb) -> \k -> kb (k a `op`)
139 <*> option Nothing (try $ curry Just <$> opG <*> go g opG)
140 deriving instance Gram_Op g => Gram_Op (CF g)
141 instance Gram_Op RuleDef
142 instance Gram_Op EBNF
144 -- ** Type 'Error_Fixity'
146 = Error_Fixity_Infix_not_combinable Infix Infix
147 | Error_Fixity_NeedPostfixOrInfix
148 | Error_Fixity_NeedPrefix
149 | Error_Fixity_NeedPostfix
150 | Error_Fixity_NeedInfix
153 -- ** Type 'NeedFixity'
158 deriving (Eq, Ord, Show)
162 = FixityPrefix Unifix (a -> a)
163 | FixityPostfix Unifix (a -> a)
164 | FixityInfix Infix (a -> a -> a)
168 = Prefix { unifix_prece :: Precedence }
169 | Postfix { unifix_prece :: Precedence }
175 | OpNode1 Unifix (a -> a) (OpTree a)
176 | OpNode2 Infix (a -> a -> a) (OpTree a) (OpTree a)
178 -- | Collapse an 'OpTree'.
179 evalOpTree :: OpTree a -> a
180 evalOpTree (OpNode0 a) = a
181 evalOpTree (OpNode1 _uni op n) = op $ evalOpTree n
182 evalOpTree (OpNode2 _inf op l r) = evalOpTree l `op` evalOpTree r
184 gram_operators :: (Gram_Op g, Gram_RuleDef g) => [CF g ()]
186 [ void $ operators (rule_arg "expr") (rule_arg "prefix") (rule_arg "infix") (rule_arg "postfix")