1 -- | Symantics to handle 'Prefix', 'Postfix' or 'Infix' operators,
2 -- of different 'Precedence's and possibly with left and/or right 'Associativity'.
3 module Language.Symantic.Grammar.Operators where
5 import Control.Applicative (Applicative(..))
6 import Control.Monad (void)
7 import Data.Foldable hiding (any)
8 import Prelude hiding (any)
10 import Language.Symantic.Grammar.Fixity
11 import Language.Symantic.Grammar.EBNF
12 import Language.Symantic.Grammar.Terminal
13 import Language.Symantic.Grammar.Regular
14 import Language.Symantic.Grammar.ContextFree
17 -- | Symantics for operators.
28 :: CF g a -- ^ expression
29 -> CF g (Unifix, a -> a) -- ^ prefix operator
30 -> CF g (Infix , a -> a -> a) -- ^ infix operator
31 -> CF g (Unifix, a -> a) -- ^ postfix operator
32 -> CF g (Either Error_Fixity a)
33 operators g prefixG infixG postfixG =
34 (evalOpTree <$>) <$> go g prefixG infixG postfixG
38 -> CF g (Unifix, a -> a)
39 -> CF g (Infix , a -> a -> a)
40 -> CF g (Unifix, a -> a)
41 -> CF g (Either Error_Fixity (OpTree a))
42 go = rule4 "operators" $ \aG preG inG postG ->
46 (foldl' (flip insertUnifix) (OpTree0 a) posts)
49 Just (in_, b) -> insertInfix nod_a in_ b
50 Nothing -> Right nod_a)
54 <*> option Nothing (curry Just <$> try inG <*> go aG preG inG postG)
55 infixrG :: CF g a -> CF g (a -> a -> a) -> CF g a
56 infixrG = rule2 "infixr" $ \g opG ->
58 Just (op, b) -> a `op` b
61 <*> option Nothing (try $ curry Just <$> opG <*> infixrG g opG)
62 infixlG :: CF g a -> CF g (a -> a -> a) -> CF g a
63 infixlG = rule2 "infixl" $ \g opG ->
64 -- NOTE: infixl uses the same grammar than infixr,
65 -- but build the parsed value by applying
66 -- the operator in the opposite way.
69 go :: CF g a -> CF g (a -> a -> a) -> CF g ((a -> a) -> a)
72 Just (op, kb) -> \k -> kb (k a `op`)
75 <*> option Nothing (try $ curry Just <$> opG <*> go g opG)
76 deriving instance Gram_Op g => Gram_Op (CF g)
77 instance Gram_Op RuleEBNF
80 -- ** Type 'Error_Fixity'
82 = Error_Fixity_Infix_not_combinable Infix Infix
84 Error_Fixity_NeedPostfixOrInfix
85 Error_Fixity_NeedPrefix
86 Error_Fixity_NeedPostfix
87 Error_Fixity_NeedInfix
92 -- | Tree of operators.
94 -- Useful to recombine operators according to their 'Precedence'.
97 | OpTree1 Unifix (a -> a) (OpTree a)
98 | OpTree2 Infix (a -> a -> a) (OpTree a) (OpTree a)
99 instance Show a => Show (OpTree a) where
100 showsPrec n (OpTree0 a) =
101 showParen (n > 10) $ showString "OpTree0 "
103 showsPrec n (OpTree1 f _ a) =
104 showParen (n > 10) $ showString "OpTree1 "
106 . showChar ' ' . showsPrec 11 a
107 showsPrec n (OpTree2 f _ a b) =
108 showParen (n > 10) $ showString "OpTree2 "
110 . showChar ' ' . showsPrec 11 a
111 . showChar ' ' . showsPrec 11 b
113 -- | Insert an 'Unifix' operator into an 'OpTree'.
114 insertUnifix :: (Unifix, a -> a) -> OpTree a -> OpTree a
115 insertUnifix a@(uni_a@(Prefix prece_a), op_a) nod_b =
117 OpTree0{} -> OpTree1 uni_a op_a nod_b
118 OpTree1 Prefix{} _op_b _nod -> OpTree1 uni_a op_a nod_b
119 OpTree1 uni_b@(Postfix prece_b) op_b nod ->
120 case prece_b `compare` prece_a of
121 GT -> OpTree1 uni_a op_a nod_b
122 EQ -> OpTree1 uni_a op_a nod_b
123 LT -> OpTree1 uni_b op_b $ insertUnifix a nod
124 OpTree2 inf_b op_b l r ->
125 case infix_prece inf_b `compare` prece_a of
126 GT -> OpTree1 uni_a op_a nod_b
127 EQ -> OpTree1 uni_a op_a nod_b
128 LT -> OpTree2 inf_b op_b (insertUnifix a l) r
129 insertUnifix a@(uni_a@(Postfix prece_a), op_a) nod_b =
131 OpTree0{} -> OpTree1 uni_a op_a nod_b
132 OpTree1 uni_b@(Prefix prece_b) op_b nod ->
133 case prece_b `compare` prece_a of
134 GT -> OpTree1 uni_a op_a nod_b
135 EQ -> OpTree1 uni_a op_a nod_b
136 LT -> OpTree1 uni_b op_b $ insertUnifix a nod
137 OpTree1 Postfix{} _op_b _nod -> OpTree1 uni_a op_a nod_b
138 OpTree2 inf_b op_b l r ->
139 case infix_prece inf_b `compare` prece_a of
140 GT -> OpTree1 uni_a op_a nod_b
141 EQ -> OpTree1 uni_a op_a nod_b
142 LT -> OpTree2 inf_b op_b l (insertUnifix a r)
144 -- | Insert an 'Infix' operator into an 'OpTree'.
147 -> (Infix, a -> a -> a)
148 -> Either Error_Fixity (OpTree a)
149 -> Either Error_Fixity (OpTree a)
150 insertInfix nod_a in_@(inf_a, op_a) e_nod_b = do
153 OpTree0{} -> Right $ OpTree2 inf_a op_a nod_a nod_b
154 OpTree1 uni_b op_b nod ->
155 case unifix_prece uni_b `compare` infix_prece inf_a of
156 EQ -> Right $ OpTree2 inf_a op_a nod_a nod_b
157 GT -> Right $ OpTree2 inf_a op_a nod_a nod_b
159 n <- insertInfix nod_a in_ (Right nod)
160 Right $ OpTree1 uni_b op_b n
161 OpTree2 inf_b op_b l r ->
162 case infix_prece inf_b `compare` infix_prece inf_a of
163 GT -> Right $ OpTree2 inf_a op_a nod_a nod_b
165 n <- insertInfix nod_a in_ (Right l)
166 Right $ OpTree2 inf_b op_b n r
172 case (ass <$> infix_assoc inf_b, ass <$> infix_assoc inf_a) of
173 (Just SideL, Just SideL) -> do
174 n <- insertInfix nod_a in_ (Right l)
175 Right $ OpTree2 inf_b op_b n r
176 (Just SideR, Just SideR) ->
177 Right $ OpTree2 inf_a op_a nod_a nod_b
178 _ -> Left $ Error_Fixity_Infix_not_combinable inf_a inf_b
179 -- NOTE: non-associating infix ops
180 -- of the same precedence cannot be mixed.
182 -- | Collapse an 'OpTree'.
183 evalOpTree :: OpTree a -> a
184 evalOpTree (OpTree0 a) = a
185 evalOpTree (OpTree1 _uni op n) = op $ evalOpTree n
186 evalOpTree (OpTree2 _inf op l r) = evalOpTree l `op` evalOpTree r
188 gram_operators :: (Gram_Op g, Gram_RuleEBNF g) => [CF g ()]
190 [ void $ operators (argEBNF "expr") (argEBNF "prefix") (argEBNF "infix") (argEBNF "postfix")