1 {-# LANGUAGE PatternSynonyms #-} -- For Instr
2 {-# LANGUAGE ViewPatterns #-} -- For unSomeInstr
3 -- | Initial encoding with bottom-up optimizations of 'Instr'uctions,
4 -- re-optimizing downward as needed after each optimization.
5 -- There is only one optimization (for 'pushValue') so far,
6 -- but the introspection enabled by the 'Instr' data-type
7 -- is also useful to optimize with more context in the 'Machine'.
8 module Symantic.Parser.Machine.Optimize where
10 import Data.Bifunctor (second)
11 import Data.Bool (Bool(..))
12 import Data.Either (Either)
13 import Data.Function ((.))
14 import Data.Kind (Constraint)
15 import Data.Maybe (Maybe(..))
17 import Data.String (String)
18 import Type.Reflection (Typeable, typeRep, eqTypeRep, (:~~:)(..))
19 import qualified Data.Functor as Functor
20 import qualified Language.Haskell.TH as TH
22 import Symantic.Derive
23 import Symantic.Parser.Grammar
24 import Symantic.Parser.Machine.Input
25 import Symantic.Parser.Machine.Instructions
27 -- * Data family 'Instr'
28 -- | 'Instr'uctions of the 'Machine'.
29 -- This is an extensible data-type.
31 (instr :: ReprInstr -> Constraint)
32 :: ReprInstr -> ReprInstr
33 type instance Derived (Instr instr repr inp vs) = repr inp vs
35 -- | Convenient utility to pattern-match a 'SomeInstr'.
36 pattern Instr :: Typeable comb =>
37 Instr comb repr inp vs a ->
38 SomeInstr repr inp vs a
39 pattern Instr x <- (unSomeInstr -> Just x)
41 -- ** Type 'SomeInstr'
42 -- | Some 'Instr'uction existentialized over the actual instruction symantic class.
43 -- Useful to handle a list of 'Instr'uctions
44 -- without requiring impredicative quantification.
45 -- Must be used by pattern-matching
46 -- on the 'SomeInstr' data-constructor,
47 -- to bring the constraints in scope.
49 -- As in 'SomeComb', a first pass of optimizations
50 -- is directly applied in it
51 -- to avoid introducing an extra newtype,
52 -- this also gives a more undestandable code.
53 data SomeInstr repr inp vs a =
55 ( Derivable (Instr instr repr inp vs)
57 ) => SomeInstr (Instr instr repr inp vs a)
59 type instance Derived (SomeInstr repr inp vs) = repr inp vs
60 instance Derivable (SomeInstr repr inp vs) where
61 derive (SomeInstr x) = derive x
63 -- | @(unSomeInstr i :: 'Maybe' ('Instr' comb repr inp vs a))@
64 -- extract the data-constructor from the given 'SomeInstr'
65 -- iif. it belongs to the @('Instr' comb repr a)@ data-instance.
67 forall instr repr inp vs a.
69 SomeInstr repr inp vs a ->
70 Maybe (Instr instr repr inp vs a)
71 unSomeInstr (SomeInstr (i::Instr i repr inp vs a)) =
72 case typeRep @instr `eqTypeRep` typeRep @i of
75 case typeRep @InstrComment `eqTypeRep` typeRep @i of
76 Just HRefl | Comment _msg x <- i -> unSomeInstr x
80 data instance Instr InstrComment repr inp vs a where
83 SomeInstr repr inp vs a ->
84 Instr InstrComment repr inp vs a
85 instance InstrComment repr => Derivable (Instr InstrComment repr inp vs) where
87 Comment msg k -> comment msg (derive k)
88 instance InstrComment repr => InstrComment (SomeInstr repr) where
89 comment msg = SomeInstr . Comment msg
92 data instance Instr InstrValuable repr inp vs a where
95 SomeInstr repr inp (v ': vs) a ->
96 Instr InstrValuable repr inp vs a
98 SomeInstr repr inp vs a ->
99 Instr InstrValuable repr inp (v ': vs) a
101 Splice (x -> y -> z) ->
102 SomeInstr repr inp (z : vs) a ->
103 Instr InstrValuable repr inp (y : x : vs) a
105 SomeInstr repr inp (x ': y ': vs) a ->
106 Instr InstrValuable repr inp (y ': x ': vs) a
107 instance InstrValuable repr => Derivable (Instr InstrValuable repr inp vs) where
109 PushValue v k -> pushValue v (derive k)
110 PopValue k -> popValue (derive k)
111 Lift2Value v k -> lift2Value v (derive k)
112 SwapValue k -> swapValue (derive k)
113 instance InstrValuable repr => InstrValuable (SomeInstr repr) where
114 -- 'PopValue' after a 'PushValue' is a no-op.
115 pushValue _v (Instr (PopValue i)) = i
116 pushValue v i = SomeInstr (PushValue v i)
117 popValue = SomeInstr . PopValue
118 lift2Value f = SomeInstr . Lift2Value f
119 swapValue = SomeInstr . SwapValue
121 -- InstrExceptionable
122 data instance Instr InstrExceptionable repr inp vs a where
125 Instr InstrExceptionable repr inp vs a
128 Instr InstrExceptionable repr inp vs a
131 SomeInstr repr inp vs ret ->
132 Instr InstrExceptionable repr inp vs ret
135 SomeInstr repr inp vs ret ->
136 SomeInstr repr inp (InputPosition inp ': vs) ret ->
137 Instr InstrExceptionable repr inp vs ret
138 instance InstrExceptionable repr => Derivable (Instr InstrExceptionable repr inp vs) where
140 Raise exn -> raise exn
142 Commit exn k -> commit exn (derive k)
143 Catch exn l r -> catch exn (derive l) (derive r)
144 instance InstrExceptionable repr => InstrExceptionable (SomeInstr repr) where
145 raise = SomeInstr . Raise
146 fail = SomeInstr . Fail
147 commit exn = SomeInstr . Commit exn
148 catch exn x = SomeInstr . Catch exn x
151 data instance Instr InstrBranchable repr inp vs a where
153 SomeInstr repr inp (x ': vs) a ->
154 SomeInstr repr inp (y ': vs) a ->
155 Instr InstrBranchable repr inp (Either x y ': vs) a
157 [(Splice (v -> Bool), SomeInstr repr inp vs a)] ->
158 SomeInstr repr inp vs a ->
159 Instr InstrBranchable repr inp (v ': vs) a
160 instance InstrBranchable repr => Derivable (Instr InstrBranchable repr inp vs) where
162 CaseBranch l r -> caseBranch (derive l) (derive r)
163 ChoicesBranch bs d -> choicesBranch (second derive Functor.<$> bs) (derive d)
164 instance InstrBranchable repr => InstrBranchable (SomeInstr repr) where
165 caseBranch l = SomeInstr . CaseBranch l
166 choicesBranch bs = SomeInstr . ChoicesBranch bs
169 data instance Instr InstrCallable repr inp vs a where
171 LetBindings TH.Name (SomeInstr repr inp '[]) ->
172 SomeInstr repr inp vs a ->
173 Instr InstrCallable repr inp vs a
177 SomeInstr repr inp (v ': vs) a ->
178 Instr InstrCallable repr inp vs a
180 Instr InstrCallable repr inp '[a] a
184 Instr InstrCallable repr inp '[] a
185 instance InstrCallable repr => Derivable (Instr InstrCallable repr inp vs) where
187 DefLet subs k -> defLet ((\(SomeLet sub) -> SomeLet (derive sub)) Functor.<$> subs) (derive k)
188 Jump isRec n -> jump isRec n
189 Call isRec n k -> call isRec n (derive k)
191 instance InstrCallable repr => InstrCallable (SomeInstr repr) where
192 defLet subs = SomeInstr . DefLet subs
193 jump isRec = SomeInstr . Jump isRec
194 call isRec n = SomeInstr . Call isRec n
198 data instance Instr InstrJoinable repr inp vs a where
201 SomeInstr repr inp (v ': vs) a ->
202 SomeInstr repr inp vs a ->
203 Instr InstrJoinable repr inp vs a
206 Instr InstrJoinable repr inp (v ': vs) a
207 instance InstrJoinable repr => Derivable (Instr InstrJoinable repr inp vs) where
209 DefJoin n sub k -> defJoin n (derive sub) (derive k)
210 RefJoin n -> refJoin n
211 instance InstrJoinable repr => InstrJoinable (SomeInstr repr) where
212 defJoin n sub = SomeInstr . DefJoin n sub
213 refJoin = SomeInstr . RefJoin
216 data instance Instr InstrInputable repr inp vs a where
218 SomeInstr repr inp (InputPosition inp ': vs) a ->
219 Instr InstrInputable repr inp vs a
221 SomeInstr repr inp vs a ->
222 Instr InstrInputable repr inp (InputPosition inp ': vs) a
223 instance InstrInputable repr => Derivable (Instr InstrInputable repr inp vs) where
225 PushInput k -> saveInput (derive k)
226 LoadInput k -> loadInput (derive k)
227 instance InstrInputable repr => InstrInputable (SomeInstr repr) where
228 saveInput = SomeInstr . PushInput
229 loadInput = SomeInstr . LoadInput
232 data instance Instr (InstrReadable tok) repr inp vs a where
235 Splice (InputToken inp -> Bool) ->
236 SomeInstr repr inp (InputToken inp ': vs) a ->
237 Instr (InstrReadable tok) repr inp vs a
239 ( InstrReadable tok repr, tok ~ InputToken inp ) =>
240 Derivable (Instr (InstrReadable tok) repr inp vs) where
242 Read fs p k -> read fs p (derive k)
244 ( InstrReadable tok repr, Typeable tok ) =>
245 InstrReadable tok (SomeInstr repr) where
246 read fs p = SomeInstr . Read fs p
249 data instance Instr InstrIterable repr inp vs a where
252 SomeInstr repr inp '[] a ->
253 SomeInstr repr inp (InputPosition inp ': vs) a ->
254 Instr InstrIterable repr inp vs a
256 InstrIterable repr =>
257 Derivable (Instr InstrIterable repr inp vs) where
259 Iter n op k -> iter n (derive op) (derive k)
261 InstrIterable repr =>
262 InstrIterable (SomeInstr repr) where
263 iter n op = SomeInstr . Iter n op
266 data instance Instr InstrRegisterable repr inp vs a where
268 UnscopedRegister v ->
269 SomeInstr repr inp vs a ->
270 Instr InstrRegisterable repr inp (v : vs) a
272 UnscopedRegister v ->
273 SomeInstr repr inp (v : vs) a ->
274 Instr InstrRegisterable repr inp vs a
276 UnscopedRegister v ->
277 SomeInstr repr inp vs a ->
278 Instr InstrRegisterable repr inp (v : vs) a
280 InstrRegisterable repr =>
281 Derivable (Instr InstrRegisterable repr inp vs) where
283 NewRegister r k -> newRegister r (derive k)
284 ReadRegister r k -> readRegister r (derive k)
285 WriteRegister r k -> writeRegister r (derive k)
287 InstrRegisterable repr =>
288 InstrRegisterable (SomeInstr repr) where
289 newRegister r = SomeInstr . NewRegister r
290 readRegister r = SomeInstr . ReadRegister r
291 writeRegister r = SomeInstr . WriteRegister r