{-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE UndecidableInstances #-} module Symantic.Parser.Grammar.Optimize where import Data.Bool (Bool) import Data.Char (Char) import Data.Either (Either(..), either) import Data.Eq (Eq(..)) import qualified Prelude as Pre import Symantic.Base.Univariant import Symantic.Parser.Grammar.Combinators import Symantic.Parser.Grammar.ObserveSharing import Symantic.Parser.Staging hiding (Haskell(..)) import qualified Symantic.Parser.Staging as Hask -- import qualified Language.Haskell.TH.Syntax as TH -- * Type 'Grammar' data Grammar a where Pure :: Hask.Haskell a -> Grammar a Satisfy :: Hask.Haskell (Char -> Bool) -> Grammar Char Item :: Grammar Char Try :: Grammar a -> Grammar a Look :: Grammar a -> Grammar a NegLook :: Grammar a -> Grammar () (:<*>) :: Grammar (a -> b) -> Grammar a -> Grammar b (:<|>) :: Grammar a -> Grammar a -> Grammar a Empty :: Grammar a Branch :: Grammar (Either a b) -> Grammar (a -> c) -> Grammar (b -> c) -> Grammar c Match :: Eq a => [Hask.Haskell (a -> Bool)] -> [Grammar b] -> Grammar a -> Grammar b -> Grammar b ChainPre :: Grammar (a -> a) -> Grammar a -> Grammar a ChainPost :: Grammar a -> Grammar (a -> a) -> Grammar a Def :: Pointer -> Grammar a -> Grammar a Ref :: Bool -> Pointer -> Grammar a pattern (:<$>) :: Hask.Haskell (a -> b) -> Grammar a -> Grammar b pattern (:$>) :: Grammar a -> Hask.Haskell b -> Grammar b pattern (:<$) :: Hask.Haskell a -> Grammar b -> Grammar a pattern (:*>) :: Grammar a -> Grammar b -> Grammar b pattern (:<*) :: Grammar a -> Grammar b -> Grammar a pattern x :<$> p = Pure x :<*> p pattern p :$> x = p :*> Pure x pattern x :<$ p = Pure x :<* p pattern x :<* p = Hask.Const :<$> x :<*> p pattern p :*> x = Hask.Id :<$ p :<*> x infixl 3 :<|> infixl 4 :<*>, :<*, :*> infixl 4 :<$>, :<$, :$> instance Applicable Grammar where pure = Pure (<*>) = (:<*>) instance Alternable Grammar where (<|>) = (:<|>) empty = Empty try = Try instance Selectable Grammar where branch = Branch instance Matchable Grammar where conditional = Match instance Foldable Grammar where chainPre = ChainPre chainPost = ChainPost instance Charable Grammar where satisfy = Satisfy instance Lookable Grammar where look = Look negLook = NegLook instance Letable Grammar where def = Def ref = Ref instance ( Applicable repr , Alternable repr , Selectable repr , Foldable repr , Charable repr , Lookable repr , Matchable repr , Letable repr ) => Symantic Grammar repr where sym = \case Pure a -> pure a Satisfy p -> satisfy p Item -> item Try x -> try (sym x) Look x -> look (sym x) NegLook x -> negLook (sym x) x :<*> y -> sym x <*> sym y x :<|> y -> sym x <|> sym y Empty -> empty Branch lr l r -> branch (sym lr) (sym l) (sym r) Match cs bs a b -> conditional cs (sym Pre.<$> bs) (sym a) (sym b) ChainPre x y -> chainPre (sym x) (sym y) ChainPost x y -> chainPost (sym x) (sym y) Def n x -> def n (sym x) Ref r n -> ref r n {- type instance Unlift Grammar = repr instance ( Applicable repr , Alternable repr , Selectable repr , Foldable repr , Charable repr , Lookable repr , Matchable repr , Letable repr ) => Unliftable Grammar where unlift = \case Pure a -> pure a Satisfy p -> satisfy p Item -> item Try x -> try (unlift x) Look x -> look (unlift x) NegLook x -> negLook (unlift x) x :<*> y -> unlift x <*> unlift y x :<|> y -> unlift x <|> unlift y Empty -> empty Branch lr l r -> branch (unlift lr) (unlift l) (unlift r) Match cs bs a b -> conditional cs (unlift Pre.<$> bs) (unlift a) (unlift b) ChainPre x y -> chainPre (unlift x) (unlift y) ChainPost x y -> chainPost (unlift x) (unlift y) Ref{..} -> let_ let_rec let_name unComb :: ( Applicable repr , Alternable repr , Selectable repr , Foldable repr , Charable repr , Lookable repr , Matchable repr , Letable repr ) => Grammar repr a -> repr a unComb = unlift -} optimizeGrammar :: Grammar a -> Grammar a optimizeGrammar = \case -- Recurse into shared and/or recursive 'let' definition Def n x -> Def n (optimizeGrammar x) -- Applicable Right Absorption Law Empty :<*> _ -> Empty Empty :*> _ -> Empty Empty :<* _ -> Empty -- Applicable Failure Weakening Law u :<*> Empty -> optimizeGrammar (u :*> Empty) u :<* Empty -> optimizeGrammar (u :*> Empty) -- Branch Absorption Law Branch Empty _ _ -> empty -- Branch Weakening Law Branch b Empty Empty -> optimizeGrammar (b :*> Empty) -- Applicable Identity Law Hask.Id :<$> x -> x -- Flip const optimisation Hask.Flip Hask.:@ Hask.Const :<$> u -> optimizeGrammar (u :*> Pure Hask.Id) -- Homomorphism Law f :<$> Pure x -> Pure (f Hask.:@ x) -- Functor Composition Law -- (a shortcut that could also have been be caught -- by the Composition Law and Homomorphism law) f :<$> (g :<$> p) -> optimizeGrammar ((Hask.:.) Hask.:@ f Hask.:@ g :<$> p) -- Composition Law u :<*> (v :<*> w) -> optimizeGrammar (optimizeGrammar (optimizeGrammar ((Hask.:.) :<$> u) :<*> v) :<*> w) -- Definition of *> Hask.Flip Hask.:@ Hask.Const :<$> p :<*> q -> p :*> q -- Definition of <* Hask.Const :<$> p :<*> q -> p :<* q -- Reassociation Law 1 (u :*> v) :<*> w -> optimizeGrammar (u :*> optimizeGrammar (v :<*> w)) -- Interchange Law u :<*> Pure x -> optimizeGrammar (Hask.Flip Hask.:@ (Hask.:$) Hask.:@ x :<$> u) -- Right Absorption Law (_ :<$> p) :*> q -> p :*> q -- Left Absorption Law p :<* (_ :<$> q) -> p :<* q -- Reassociation Law 2 u :<*> (v :<* w) -> optimizeGrammar (optimizeGrammar (u :<*> v) :<* w) -- Reassociation Law 3 u :<*> (v :$> x) -> optimizeGrammar (optimizeGrammar (u :<*> Pure x) :<* v) -- Left Catch Law p@Pure{} :<|> _ -> p -- Left Neutral Law Empty :<|> u -> u -- Right Neutral Law u :<|> Empty -> u -- Associativity Law (u :<|> v) :<|> w -> u :<|> optimizeGrammar (v :<|> w) -- Identity law Pure _ :*> u -> u -- Identity law (u :$> _) :*> v -> u :*> v -- Associativity Law u :*> (v :*> w) -> optimizeGrammar (optimizeGrammar (u :*> v) :*> w) -- Identity law u :<* Pure _ -> u -- Identity law u :<* (v :$> _) -> optimizeGrammar (u :<* v) -- Commutativity Law x :<$ u -> optimizeGrammar (u :$> x) -- Associativity Law (u :<* v) :<* w -> optimizeGrammar (u :<* optimizeGrammar (v :<* w)) -- Pure lookahead Look p@Pure{} -> p -- Dead lookahead Look p@Empty -> p -- Pure negative-lookahead NegLook Pure{} -> Empty -- Dead negative-lookahead NegLook Empty -> Pure Hask.unit -- Double Negation Law NegLook (NegLook p) -> optimizeGrammar (Look (Try p) :*> Pure Hask.unit) -- Zero Consumption Law NegLook (Try p) -> optimizeGrammar (NegLook p) -- Idempotence Law Look (Look p) -> Look p -- Right Identity Law NegLook (Look p) -> optimizeGrammar (NegLook p) -- Left Identity Law Look (NegLook p) -> NegLook p -- Transparency Law NegLook (Try p :<|> q) -> optimizeGrammar (optimizeGrammar (NegLook p) :*> optimizeGrammar (NegLook q)) -- Distributivity Law Look p :<|> Look q -> optimizeGrammar (Look (optimizeGrammar (Try p :<|> q))) -- Interchange Law Look (p :$> x) -> optimizeGrammar (optimizeGrammar (Look p) :$> x) -- Interchange law Look (f :<$> p) -> optimizeGrammar (f :<$> optimizeGrammar (Look p)) -- Absorption Law p :<*> NegLook q -> optimizeGrammar (optimizeGrammar (p :<*> Pure Hask.unit) :<* NegLook q) -- Idempotence Law NegLook (p :$> _) -> optimizeGrammar (NegLook p) -- Idempotence Law NegLook (_ :<$> p) -> optimizeGrammar (NegLook p) -- Interchange Law Try (p :$> x) -> optimizeGrammar (optimizeGrammar (Try p) :$> x) -- Interchange law Try (f :<$> p) -> optimizeGrammar (f :<$> optimizeGrammar (Try p)) -- pure Left/Right laws Branch (Pure (unlift -> lr)) l r -> case getValue lr of Left v -> optimizeGrammar (l :<*> Pure (Hask.Haskell (ValueCode (Value v) c))) where c = Code [|| case $$(getCode lr) of Left x -> x ||] Right v -> optimizeGrammar (r :<*> Pure (Hask.Haskell (ValueCode (Value v) c))) where c = Code [|| case $$(getCode lr) of Right x -> x ||] -- Generalised Identity law Branch b (Pure (unlift -> l)) (Pure (unlift -> r)) -> optimizeGrammar (Hask.Haskell (ValueCode v c) :<$> b) where v = Value (either (getValue l) (getValue r)) c = Code [|| either $$(getCode l) $$(getCode r) ||] -- Interchange law Branch (x :*> y) p q -> optimizeGrammar (x :*> optimizeGrammar (Branch y p q)) -- Negated Branch law Branch b l Empty -> Branch (Pure (Hask.Haskell (ValueCode v c)) :<*> b) Empty l where v = Value (either Right Left) c = Code [||either Right Left||] -- Branch Fusion law Branch (Branch b Empty (Pure (unlift -> lr))) Empty br -> optimizeGrammar (Branch (optimizeGrammar (Pure (Hask.Haskell (ValueCode (Value v) c)) :<*> b)) Empty br) where v Left{} = Left () v (Right r) = case getValue lr r of Left _ -> Left () Right rr -> Right rr c = Code [|| \case Left{} -> Left () Right r -> case $$(getCode lr) r of Left _ -> Left () Right rr -> Right rr ||] -- Distributivity Law f :<$> Branch b l r -> optimizeGrammar (Branch b (optimizeGrammar ((Hask..@) (Hask..) f :<$> l)) (optimizeGrammar ((Hask..@) (Hask..) f :<$> r))) x -> x