Polish code and dumps
authorJulien Moutinho <julm+symantic-parser@sourcephile.fr>
Wed, 21 Oct 2020 03:08:48 +0000 (05:08 +0200)
committerJulien Moutinho <julm+symantic-parser@sourcephile.fr>
Wed, 21 Oct 2020 03:08:48 +0000 (05:08 +0200)
16 files changed:
src/Symantic/Parser/Automaton/Instructions.hs
src/Symantic/Parser/Grammar.hs
src/Symantic/Parser/Grammar/Dump.hs
src/Symantic/Parser/Grammar/Optimize.hs
src/Symantic/Parser/Staging.hs
src/Symantic/Univariant/Letable.hs
test/Golden.hs
test/Golden/Grammar/app.dump [new file with mode: 0644]
test/Golden/Grammar/app.opt.dump [new file with mode: 0644]
test/Golden/Grammar/boom.dump
test/Golden/Grammar/boom.opt.dump [new file with mode: 0644]
test/Golden/Grammar/brainfuck.dump
test/Golden/Grammar/brainfuck.opt.dump [new file with mode: 0644]
test/Golden/Grammar/unit-unit.dump
test/Golden/Grammar/unit-unit.opt.dump [new file with mode: 0644]
test/Golden/Grammar/unit.opt.dump [new file with mode: 0644]

index b6b757d4ac82bfa12f127981478bc86f10c44d5b..ccd455a947abbb1fdc857f8bc27b7593a442e15f 100644 (file)
@@ -1,6 +1,4 @@
-{-# LANGUAGE ConstraintKinds #-}
-{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE NoPolyKinds #-}
+{-# LANGUAGE ConstraintKinds #-} -- For Executable
 {-# LANGUAGE PatternSynonyms #-}
 {-# LANGUAGE ViewPatterns #-}
 module Symantic.Parser.Automaton.Instructions where
@@ -25,32 +23,78 @@ class InputPosition inp where
 -- | 'Instr'uctions for the 'Automaton'.
 data Instr input valueStack (exceptionStack::Peano) returnValue a where
   -- | @('Ret')@ returns the value in a singleton value-stack.
-  Ret :: Instr inp '[ret] es ret a
-  -- | @('Push' x k)@ pushes @(x)@ on the value-stack and continues with the next 'Instr'uction @(k)@.
-  Push :: InstrPure x -> Instr inp (x ': vs) es ret a -> Instr inp vs es ret a
+  Ret ::
+    Instr inp '[ret] es ret a
+  -- | @('Push' x k)@ pushes @(x)@ on the value-stack
+  -- and continues with the next 'Instr'uction @(k)@.
+  Push ::
+    InstrPure x ->
+    Instr inp (x ': vs) es ret a ->
+    Instr inp vs es ret a
   -- | @('Pop' k)@ pushes @(x)@ on the value-stack.
-  Pop :: Instr inp vs es ret a -> Instr inp (x ': vs) es ret a
-  -- | @('LiftI2' f k)@ pops two values from the value-stack, and pushes the result of @(f)@ applied to them.
-  LiftI2 :: InstrPure (x -> y -> z) -> Instr inp (z : vs) es ret a -> Instr inp (y : x : vs) es ret a
+  Pop ::
+    Instr inp vs es ret a ->
+    Instr inp (x ': vs) es ret a
+  -- | @('LiftI2' f k)@ pops two values from the value-stack,
+  -- and pushes the result of @(f)@ applied to them.
+  LiftI2 ::
+    InstrPure (x -> y -> z) ->
+    Instr inp (z : vs) es ret a ->
+    Instr inp (y : x : vs) es ret a
   -- | @('Fail')@ raises an error from the exception-stack.
-  Fail :: Instr inp vs ('Succ es) ret a
-  -- | @('Commit' k)@ removes an exception from the exception-stack and continues with the next 'Instr'uction @(k)@.
-  Commit :: Instr inp vs es ret a -> Instr inp vs ('Succ es) ret a
-  -- | @('Catch' l r)@ tries the @(l)@ 'Instr'uction, if it raises an exception, catches it, pushes the input on the value-stack and continues with the @(r)@ 'Instr'uction.
-  Catch :: Instr inp vs ('Succ es) ret a -> Instr inp (inp ': vs) es ret a -> Instr inp vs es ret a
-  -- | @('Seek' k)@ removes the input from the value-stack and continues with the next 'Instr'uction @(k)@.
-  Seek :: Instr inp vs es r a -> Instr inp (inp : vs) es r a
-  -- | @('Tell' k)@ pushes the input @(inp)@ on the value-stack and continues with the next 'Instr'uction @(k)@.
-  Tell :: Instr inp (inp ': vs) es ret a -> Instr inp vs es ret a
+  Fail ::
+    Instr inp vs ('Succ es) ret a
+  -- | @('Commit' k)@ removes an exception from the exception-stack
+  -- and continues with the next 'Instr'uction @(k)@.
+  Commit ::
+    Instr inp vs es ret a ->
+    Instr inp vs ('Succ es) ret a
+  -- | @('Catch' l r)@ tries the @(l)@ 'Instr'uction,
+  -- if it raises an exception, catches it,
+  -- pushes the input on the value-stack
+  -- and continues with the @(r)@ 'Instr'uction.
+  Catch ::
+    Instr inp vs ('Succ es) ret a ->
+    Instr inp (inp ': vs) es ret a ->
+    Instr inp vs es ret a
+  -- | @('Seek' k)@ removes the input from the value-stack
+  -- and continues with the next 'Instr'uction @(k)@.
+  Seek ::
+    Instr inp vs es r a ->
+    Instr inp (inp : vs) es r a
+  -- | @('Tell' k)@ pushes the input @(inp)@ on the value-stack
+  -- and continues with the next 'Instr'uction @(k)@.
+  Tell ::
+    Instr inp (inp ': vs) es ret a ->
+    Instr inp vs es ret a
   -- | @('Case' l r)@.
-  Case :: Instr inp (x ': vs) es r a -> Instr inp (y ': vs) es r a -> Instr inp (Either x y ': vs) es r a
-  -- | @('Swap' k)@ pops two values on the value-stack, pushes the first popped-out, then the second, and continues with the next 'Instr'uction @(k)@.
-  Swap :: Instr inp (x ': y ': vs) es r a -> Instr inp (y ': x ': vs) es r a
+  Case ::
+    Instr inp (x ': vs) es r a ->
+    Instr inp (y ': vs) es r a ->
+    Instr inp (Either x y ': vs) es r a
+  -- | @('Swap' k)@ pops two values on the value-stack,
+  -- pushes the first popped-out, then the second,
+  -- and continues with the next 'Instr'uction @(k)@.
+  Swap ::
+    Instr inp (x ': y ': vs) es r a ->
+    Instr inp (y ': x ': vs) es r a
   -- | @('Choices' ps bs d)@.
-  Choices :: [InstrPure (x -> Bool)] -> [Instr inp vs es ret a] -> Instr inp vs es ret a -> Instr inp (x ': vs) es ret a
-  Call :: Addr ret -> Instr inp (x ': xs) ('Succ es) ret a -> Instr inp xs ('Succ es) ret a
-  Jump :: Addr ret -> Instr inp '[] ('Succ es) ret a
-  Label :: Addr ret -> Instr inp (xs) ('Succ es) ret a -> Instr inp xs ('Succ es) ret a
+  Choices ::
+    [InstrPure (x -> Bool)] ->
+    [Instr inp vs es ret a] ->
+    Instr inp vs es ret a ->
+    Instr inp (x ': vs) es ret a
+  Label ::
+    Addr ret ->
+    Instr inp xs ('Succ es) ret a ->
+    Instr inp xs ('Succ es) ret a
+  Call ::
+    Addr ret ->
+    Instr inp (x ': xs) ('Succ es) ret a ->
+    Instr inp xs ('Succ es) ret a
+  Jump ::
+    Addr ret ->
+    Instr inp '[] ('Succ es) ret a
 
 -- ** Type 'InstrPure'
 data InstrPure a
@@ -183,7 +227,9 @@ instance Matchable (Automaton inp a) where
   conditional ps bs (Automaton a) (Automaton default_) =
     Automaton $ \k ->
       -- TODO: join points
-      a (Choices (InstrPureHaskell Functor.<$> ps) ((\b -> unAutomaton b k) Functor.<$> bs) (default_ k))
+      a (Choices (InstrPureHaskell Functor.<$> ps)
+                 ((\b -> unAutomaton b k) Functor.<$> bs)
+                 (default_ k))
 instance Lookable (Automaton inp a) where
   look (Automaton x) = Automaton $ \k ->
     Tell (x (Swap (Seek k)))
index 3c9ac6ff4fe8f63a3bacc9c4edf164dfb74bf206..9750b00c198d21a05b6604fa71b153af7ed50302 100644 (file)
@@ -1,4 +1,4 @@
-{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE ConstraintKinds #-} -- For Grammar
 module Symantic.Parser.Grammar
  ( module Symantic.Parser.Grammar
  , module Symantic.Parser.Grammar.Combinators
index 04d9545a30795848626be056c3429993bdd4c184..ad63714479842bf0a6a5e767b81e8bf84c8bc5bf 100644 (file)
@@ -34,7 +34,7 @@ instance IsString (DumpComb a) where
 
 instance Show letName => Letable letName DumpComb where
   def name x = DumpComb $
-    Tree.Node ("def " <> show name) [unDumpComb x]
+    Tree.Node ("def "<>show name) [unDumpComb x]
   ref rec name = DumpComb $
     Tree.Node
       ( (if rec then "rec " else "ref ")
@@ -42,7 +42,7 @@ instance Show letName => Letable letName DumpComb where
       ) []
 instance Applicable DumpComb where
   _f <$> x = DumpComb $ Tree.Node "<$>" [unDumpComb x]
-  pure a = DumpComb $ Tree.Node ("pure "<>show a) []
+  pure a = DumpComb $ Tree.Node ("pure "<>showsPrec 10 a "") []
   x <*> y = DumpComb $ Tree.Node "<*>" [unDumpComb x, unDumpComb y]
 instance Alternable DumpComb where
   empty = DumpComb $ Tree.Node "empty" []
index 0dc3e238c6b10fb1cf6014ca9cc7bab74583ca9f..0cc770c9bca5b07c039e383c73f5a8447ab3b78d 100644 (file)
@@ -134,7 +134,7 @@ instance
   Trans (OptimizeComb letName repr) repr where
   trans = trans . unOptimizeComb
 
-type instance Output (OptimizeComb letName repr) = Comb repr
+type instance Output (OptimizeComb _letName repr) = Comb repr
 instance Trans (OptimizeComb letName repr) (Comb repr) where
   trans = unOptimizeComb
 instance Trans (Comb repr) (OptimizeComb letName repr) where
@@ -175,7 +175,7 @@ optimizeCombNode = \case
   -- Functor Homomorphism Law
   f :<$> Pure x ->
     -- trace "Functor Homomorphism Law" $
-    Pure (f Hask.:@ x)
+    Pure (f Hask..@ x)
 
   -- App Right Absorption Law
   Empty :<*> _ ->
@@ -194,7 +194,7 @@ optimizeCombNode = \case
   -- App Interchange Law
   u :<*> Pure x ->
     -- trace "App Interchange Law" $
-    optimizeCombNode (Hask.Flip Hask.:@ (Hask.:$) Hask.:@ x :<$> u)
+    optimizeCombNode (Hask.Flip Hask..@ (Hask.:$) Hask..@ x :<$> u)
   -- App Left Absorption Law
   p :<* (_ :<$> q) ->
     -- trace "App Left Absorption Law" $
@@ -339,7 +339,8 @@ optimizeCombNode = \case
   -- Branch Fusion Law
   Branch (Branch b Empty (Pure (trans -> lr))) Empty br ->
     -- trace "Branch Fusion Law" $
-    optimizeCombNode (Branch (optimizeCombNode (Pure (Hask.Haskell (ValueCode (Value v) c)) :<*> b)) Empty br)
+    optimizeCombNode (Branch (optimizeCombNode (Pure (Hask.Haskell (ValueCode (Value v) c)) :<*> b))
+                             Empty br)
     where
     v Left{} = Left ()
     v (Right r) = case getValue lr r of
@@ -352,7 +353,8 @@ optimizeCombNode = \case
   -- Branch Distributivity Law
   f :<$> Branch b l r ->
     -- trace "Branch Distributivity Law" $
-    optimizeCombNode (Branch b (optimizeCombNode ((Hask..@) (Hask..) f :<$> l)) (optimizeCombNode ((Hask..@) (Hask..) f :<$> r)))
+    optimizeCombNode (Branch b (optimizeCombNode ((Hask..@) (Hask..) f :<$> l))
+                               (optimizeCombNode ((Hask..@) (Hask..) f :<$> r)))
 
   -- Match Absorption Law
   Match _ _ Empty d ->
@@ -366,17 +368,20 @@ optimizeCombNode = \case
   -- Match Pure Law
   Match ps bs (Pure (trans -> a)) d ->
     -- trace "Match Pure Law" $
-    foldr (\(trans -> p, b) next -> if getValue p (getValue a) then b else next) d (List.zip ps bs)
+    foldr (\(trans -> p, b) next ->
+      if getValue p (getValue a) then b else next
+    ) d (List.zip ps bs)
   -- Match Distributivity Law
   f :<$> Match ps bs a d ->
     -- trace "Match Distributivity Law" $
-    Match ps (optimizeCombNode . (f :<$>) Functor.<$> bs) a (optimizeCombNode (f :<$> d))
+    Match ps (optimizeCombNode . (f :<$>) Functor.<$> bs) a
+             (optimizeCombNode (f :<$> d))
 
   {- Possibly useless laws to be tested
   Empty  :*> _ -> Empty
   Empty :<*  _ -> Empty
   -- App Definition of *> Law
-  Hask.Flip Hask.:@ Hask.Const :<$> p :<*> q ->
+  Hask.Flip Hask..@ Hask.Const :<$> p :<*> q ->
     -- trace "EXTRALAW: App Definition of *> Law" $
     p :*> q
   -- App Definition of <* Law
@@ -389,7 +394,7 @@ optimizeCombNode = \case
   -- by the Composition Law and Homomorphism Law)
   f :<$> (g :<$> p) ->
     -- trace "EXTRALAW: Functor Composition Law" $
-    optimizeCombNode ((Hask.:.) Hask.:@ f Hask.:@ g :<$> p)
+    optimizeCombNode ((Hask.:.) Hask..@ f Hask..@ g :<$> p)
   -- Applicable Failure Weakening Law
   u :<*  Empty ->
     -- trace "EXTRALAW: App Failure Weakening Law" $
@@ -418,8 +423,6 @@ optimizeCombNode = \case
     optimizeCombNode (optimizeCombNode (Look p) :$> x)
   NegLook (p :$> _) -> optimizeCombNode (NegLook p)
 
-  -- Pure merge optimisation
-  -- Pure x :<*> Pure y -> Pure (x Hask.:@ y)
   -}
 
   x -> x
index 98f3acc60328802d1949c240565e82882711e943..58539f87377a5d72892839dd4b2a48f76d9e5e19 100644 (file)
@@ -34,8 +34,8 @@ newtype Value a = Value { unValue :: a }
 newtype Code a = Code { unCode :: TExpQ a }
 
 -- * Class 'Haskellable'
--- | Final encoding of some Haskellable functions
--- useful for some optimizations in 'optGram'.
+-- | Final encoding of some Haskell functions
+-- useful for some optimizations in 'optimizeComb'.
 class Haskellable (repr :: * -> *) where
   (.) :: repr ((b->c) -> (a->b) -> a -> c)
   ($) :: repr ((a->b) -> a -> b)
@@ -53,10 +53,9 @@ class Haskellable (repr :: * -> *) where
   right :: repr (r -> Either l r)
   nothing :: repr (Maybe a)
   just :: repr (a -> Maybe a)
--- instance Haskellable Identity
 
 -- ** Type 'Haskellable'
--- | Initial encoding of 'Haskellable'
+-- | Initial encoding of 'Haskellable'.
 data Haskell a where
   Haskell :: ValueCode a -> Haskell a
   (:.) :: Haskell ((b->c) -> (a->b) -> a -> c)
@@ -71,29 +70,33 @@ infixr 9 ., :.
 infixl 9 .@, :@
 instance Show (Haskell a) where
   showsPrec p = \case
-   Haskell{} -> showString "Haskell"
-   (:.) -> showString "(.)"
-   (:$) -> showString "($)"
-   (:@) f x ->
-    showParen (p > 0)
-    Fun.$ showString "(@) "
-    Fun.. showsPrec 10 f
-    Fun.. showString " "
-    Fun.. showsPrec 10 x
-   Const -> showString "const"
-   Flip -> showString "flip"
-   Id -> showString "id"
-   Unit -> showString "()"
+    Haskell{} -> showString "Haskell"
+    (:.) -> showString "(.)"
+    (:$) -> showString "($)"
+    (:@) ((:.) :@ f) g ->
+      showParen (p >= 9)
+      Fun.$ showsPrec 9 f
+      Fun.. showString " . "
+      Fun.. showsPrec 9 g
+    (:@) f x ->
+      showParen (p >= 10)
+      Fun.$ showsPrec 10 f
+      Fun.. showString " "
+      Fun.. showsPrec 10 x
+    Const -> showString "const"
+    Flip -> showString "flip"
+    Id -> showString "id"
+    Unit -> showString "()"
 instance Trans Haskell ValueCode where
   trans = \case
-   Haskell x -> x
-   (:.) -> (.)
-   (:$) -> ($)
-   (:@) f x -> (.@) (trans f) (trans x)
-   Const -> const
-   Flip -> flip
-   Id -> id
-   Unit -> unit
+    Haskell x -> x
+    (:.) -> (.)
+    (:$) -> ($)
+    (:@) f x -> (.@) (trans f) (trans x)
+    Const -> const
+    Flip -> flip
+    Id -> id
+    Unit -> unit
 instance Trans ValueCode Haskell where
   trans = Haskell
 type instance Output Haskell = ValueCode
@@ -101,7 +104,11 @@ type instance Output Haskell = ValueCode
 instance Haskellable Haskell where
   (.)     = (:.)
   ($)     = (:$)
-  (.@)    = (:@)
+  -- Small optimizations, mainly to reduce dump sizes.
+  Id .@ x = x
+  (Const :@ x) .@ _y = x
+  ((Flip :@ Const) :@ _x) .@ y = y
+  f .@ x  = f :@ x
   const   = Const
   flip    = Flip
   id      = Id
index 1181bff52bedab71731b503b4b1799833f625989..b65063f6cdaf2a1dcef958d1dd75784e803036ec 100644 (file)
@@ -7,6 +7,7 @@ import Control.Applicative (Applicative(..))
 import Control.Monad (Monad(..))
 import Data.Bool (Bool(..))
 import Data.Eq (Eq(..))
+import Data.Foldable (foldMap)
 import Data.Function (($), (.))
 import Data.Functor ((<$>))
 import Data.Functor.Compose (Compose(..))
@@ -17,7 +18,6 @@ import Data.Int (Int)
 import Data.Maybe (Maybe(..), isNothing)
 import Data.Monoid (Monoid(..))
 import Data.Ord (Ord(..))
-import Data.Tuple (fst)
 -- import GHC.Exts (Int(..))
 -- import GHC.Prim (unsafeCoerce#)
 import GHC.StableName (StableName(..), makeStableName, hashStableName, eqStableName)
@@ -31,18 +31,20 @@ import qualified Control.Monad.Trans.Reader as MT
 import qualified Control.Monad.Trans.State as MT
 import qualified Data.HashMap.Strict as HM
 import qualified Data.HashSet as HS
-import qualified Data.List as List
 
 import Symantic.Univariant.Trans
 
 -- import Debug.Trace (trace)
 
 -- * Class 'Letable'
--- | This class is not for manual usage like usual symantic operators, here 'def' and 'ref' are introduced by 'observeSharing'.
+-- | This class is not for manual usage like usual symantic operators,
+-- here 'def' and 'ref' are introduced by 'observeSharing'.
 class Letable letName repr where
   -- | @('def' letName x)@ let-binds @(letName)@ to be equal to @(x)@.
   def :: letName -> repr a -> repr a
-  -- | @('ref' isRec letName)@ is a reference to @(letName)@. @(isRec)@ is 'True' iif. this 'ref'erence is recursive, ie. is reachable within its 'def'inition.
+  -- | @('ref' isRec letName)@ is a reference to @(letName)@.
+  -- @(isRec)@ is 'True' iif. this 'ref'erence is recursive,
+  -- ie. is reachable within its 'def'inition.
   ref :: Bool -> letName -> repr a
   default def ::
     Liftable1 repr => Letable letName (Output repr) =>
@@ -60,6 +62,8 @@ class MakeLetName letName where
 -- * Type 'SharingName'
 -- | Note that the observable sharing enabled by 'StableName'
 -- is not perfect as it will not observe all the sharing explicitely done.
+--
+-- Note also that the observed sharing could be different between ghc and ghci.
 data SharingName = forall a. SharingName (StableName a)
 -- | @('makeSharingName' x)@ is like @('makeStableName' x)@ but it also forces
 -- evaluation of @(x)@ to ensure that the 'StableName' is correct first time,
@@ -72,6 +76,7 @@ data SharingName = forall a. SharingName (StableName a)
 -- Note that maybe [pseq should be used here](https://gitlab.haskell.org/ghc/ghc/-/issues/2916).
 makeSharingName :: a -> SharingName
 makeSharingName !x = SharingName $ unsafePerformIO $ makeStableName x
+
 instance Eq SharingName where
   SharingName x == SharingName y = eqStableName x y
 instance Hashable SharingName where
@@ -103,8 +108,7 @@ observeSharing (ObserveSharing m) = do
           , oss_recs = HS.empty
           }
   let refs = HS.fromList $
-        (fst <$>) $
-        List.filter (\(_letName, refCount) -> refCount > 0) $
+        foldMap (\(letName, refCount) -> if refCount > 0 then [letName] else []) $
         HM.elems $ oss_refs st
   -- trace (show refs) $
   unCleanDefs a refs
@@ -194,7 +198,7 @@ instance
 newtype CleanDefs letName repr a = CleanDefs { unCleanDefs ::
   HS.HashSet letName -> repr a }
 
-type instance Output (CleanDefs letName repr) = repr
+type instance Output (CleanDefs _letName repr) = repr
 instance Trans repr (CleanDefs letName repr) where
   trans = CleanDefs . pure
 instance Trans1 repr (CleanDefs letName repr) where
index 08547df290d1b35c3b474e2fc98689f4fb50946b..40d27311f7313bf54d7c3bf75477769ee43c57cb 100644 (file)
@@ -1,3 +1,5 @@
+{-# LANGUAGE NoMonomorphismRestriction #-}
+{-# LANGUAGE Rank2Types #-}
 module Golden where
 
 import Control.Monad (Monad(..))
@@ -6,6 +8,7 @@ import Data.Function (($))
 import Data.Semigroup (Semigroup(..))
 import Data.String (String, IsString(..))
 import System.IO (IO, FilePath)
+import Text.Show (Show(..))
 import Test.Tasty
 import Test.Tasty.Golden
 import qualified Data.ByteString.Lazy as BSL
@@ -15,6 +18,7 @@ import qualified Data.Text.Lazy.Encoding as TL
 import qualified Language.Haskell.TH.Syntax as TH
 
 import qualified Symantic.Parser as P
+import qualified Symantic.Parser.Staging as Hask
 import Golden.Grammar
 
 goldensIO :: IO TestTree
@@ -22,23 +26,34 @@ goldensIO = return $ testGroup "Golden"
   [ goldensGrammar
   ]
 
+
 goldensGrammar :: TestTree
 goldensGrammar = testGroup "Grammar"
   [ testGroup "DumpComb" $
-    let file p = "test/Golden/Grammar/"<>p<>".dump" in
-    let test name repr =
-          goldenVsStringDiff (file name) diffGolden (file name) $ do
-            -- XXX: Resetting 'TH.counter' makes 'makeLetName' deterministic,
-            -- except when profiling is enabled, in this case those tests may fail
-            -- due to a different numbering of the 'def' and 'ref' combinators.
-            IORef.writeIORef TH.counter 0
-            return $ fromString $ P.showGrammar repr in
-    [ test "unit" P.unit
+    tests $ \name repr ->
+      let file = "test/Golden/Grammar/"<>name<>".dump" in
+      goldenVsStringDiff file diffGolden file $ do
+        -- XXX: Resetting 'TH.counter' makes 'makeLetName' deterministic,
+        -- except when profiling is enabled, in this case those tests may fail
+        -- due to a different numbering of the 'def' and 'ref' combinators.
+        IORef.writeIORef TH.counter 0
+        return $ fromString $ show $ P.dumpComb $ P.observeSharing repr
+  , testGroup "OptimizeComb" $
+    tests $ \name repr ->
+      let file = "test/Golden/Grammar/"<>name<>".opt.dump" in
+      goldenVsStringDiff file diffGolden file $ do
+        IORef.writeIORef TH.counter 0
+        return $ fromString $ show $ P.dumpComb $ P.optimizeComb $ P.observeSharing repr
+  ]
+  where
+  tests :: P.Grammar repr => (forall a. String -> repr a -> TestTree) -> [TestTree]
+  tests test =
+    [ test "unit" $ P.unit
     , test "unit-unit" $ P.unit P.*> P.unit
-    , test "boom" boom
-    , test "brainfuck" brainfuck
+    , test "app" $ P.pure (Hask.Haskell Hask.id) P.<*> P.unit
+    , test "boom" $ boom
+    , test "brainfuck" $ brainfuck
     ]
-  ]
 
 -- * Golden testing utilities
 
diff --git a/test/Golden/Grammar/app.dump b/test/Golden/Grammar/app.dump
new file mode 100644 (file)
index 0000000..697cdf9
--- /dev/null
@@ -0,0 +1,3 @@
+<*>
++ pure Haskell
+` pure ()
diff --git a/test/Golden/Grammar/app.opt.dump b/test/Golden/Grammar/app.opt.dump
new file mode 100644 (file)
index 0000000..a8160b3
--- /dev/null
@@ -0,0 +1 @@
+pure (Haskell ())
index 6fc289bed493a69686eb8e7ec654b9fd703de551..80fc928a45e60f9bbe517ea773de99d664ec447d 100644 (file)
@@ -1,30 +1,48 @@
 <*>
 + <*>
 | + <*>
-| | + <*>
-| | | + pure (@) ((@) (.) ((@) (.) ((@) ((@) flip ($)) ((@) const id)))) ((@) ((@) (.) ((@) (.) (.))) ((@) ((@) (.) ((@) (.) (.))) ((@) ((@) (.) ((@) (.) ((@) const id))) ((@) const id))))
-| | | ` def let_3
-| | |   ` <*>
-| | |     + <*>
-| | |     | + pure (@) const id
-| | |     | ` def let_5
-| | |     |   ` <*>
-| | |     |     + <*>
-| | |     |     | + pure (@) const id
-| | |     |     | ` rec let_3
-| | |     |     ` rec let_5
-| | |     ` rec let_3
-| | ` def let_2
-| |   ` pure ()
-| ` def let_1
-|   ` <*>
-|     + <*>
-|     | + pure (@) const id
-|     | ` def let_4
-|     |   ` <*>
-|     |     + <*>
-|     |     | + pure (@) const id
-|     |     | ` rec let_1
-|     |     ` rec let_4
-|     ` rec let_1
-` ref let_2
+| | + pure const
+| | ` pure id
+| ` <*>
+|   + <*>
+|   | + <*>
+|   | | + pure const
+|   | | ` pure id
+|   | ` def let_3
+|   |   ` <*>
+|   |     + <*>
+|   |     | + <*>
+|   |     | | + pure const
+|   |     | | ` pure id
+|   |     | ` def let_5
+|   |     |   ` <*>
+|   |     |     + <*>
+|   |     |     | + <*>
+|   |     |     | | + pure const
+|   |     |     | | ` pure id
+|   |     |     | ` rec let_3
+|   |     |     ` rec let_5
+|   |     ` rec let_3
+|   ` def let_1
+|     ` pure ()
+` <*>
+  + <*>
+  | + <*>
+  | | + pure const
+  | | ` pure id
+  | ` def let_2
+  |   ` <*>
+  |     + <*>
+  |     | + <*>
+  |     | | + pure const
+  |     | | ` pure id
+  |     | ` def let_4
+  |     |   ` <*>
+  |     |     + <*>
+  |     |     | + <*>
+  |     |     | | + pure const
+  |     |     | | ` pure id
+  |     |     | ` rec let_2
+  |     |     ` rec let_4
+  |     ` rec let_2
+  ` ref let_1
diff --git a/test/Golden/Grammar/boom.opt.dump b/test/Golden/Grammar/boom.opt.dump
new file mode 100644 (file)
index 0000000..2407cc8
--- /dev/null
@@ -0,0 +1,30 @@
+<*>
++ <*>
+| + <*>
+| | + <*>
+| | | + pure ((.) ((flip ($)) (const id)) . ((.) (.) . ((.) (.) . ((.) (const id) . const id))))
+| | | ` def let_3
+| | |   ` <*>
+| | |     + <*>
+| | |     | + pure (const id)
+| | |     | ` def let_5
+| | |     |   ` <*>
+| | |     |     + <*>
+| | |     |     | + pure (const id)
+| | |     |     | ` rec let_3
+| | |     |     ` rec let_5
+| | |     ` rec let_3
+| | ` def let_1
+| |   ` pure ()
+| ` def let_2
+|   ` <*>
+|     + <*>
+|     | + pure (const id)
+|     | ` def let_4
+|     |   ` <*>
+|     |     + <*>
+|     |     | + pure (const id)
+|     |     | ` rec let_2
+|     |     ` rec let_4
+|     ` rec let_2
+` ref let_1
index 60e4ce6eb3a22963058542447dde7f4f620f02d7..2423f58e697843f82440329d0ec2fc4713b05b6c 100644 (file)
@@ -1,48 +1,85 @@
 <*>
 + <*>
-| + pure (@) const id
-| ` def let_2
+| + <*>
+| | + pure const
+| | ` pure id
+| ` def let_1
 |   ` <*>
-|     + pure (@) ((@) (.) ((@) ((@) flip ($)) ())) ((@) const id)
-|     ` chainPost
-|       + pure ()
-|       ` <*>
-|         + pure (@) ((@) ((@) (.) ((@) (.) ((@) ((@) flip ($)) id))) const) id
-|         ` satisfy
-` def let_1
+|     + <*>
+|     | + <*>
+|     | | + pure const
+|     | | ` pure id
+|     | ` chainPost
+|     |   + pure ()
+|     |   ` <*>
+|     |     + <*>
+|     |     | + pure flip
+|     |     | ` pure const
+|     |     ` def let_2
+|     |       ` satisfy
+|     ` pure ()
+` def let_3
   ` chainPre
     + <*>
-    | + conditional
-    | | + bs
-    | | | + <*>
-    | | | | + pure (@) ((@) (.) ((@) (.) Haskell)) ((@) ((@) (.) const) ((@) const Haskell))
-    | | | | ` satisfy
-    | | | + <*>
-    | | | | + pure (@) ((@) (.) ((@) (.) Haskell)) ((@) ((@) (.) const) ((@) const Haskell))
-    | | | | ` satisfy
-    | | | + <*>
-    | | | | + pure (@) ((@) (.) ((@) (.) Haskell)) ((@) ((@) (.) const) ((@) const Haskell))
-    | | | | ` satisfy
-    | | | + <*>
-    | | | | + pure (@) ((@) (.) ((@) (.) Haskell)) ((@) ((@) (.) const) ((@) const Haskell))
-    | | | | ` satisfy
-    | | | + <*>
-    | | | | + pure (@) ((@) (.) ((@) (.) Haskell)) ((@) ((@) (.) const) ((@) const Haskell))
-    | | | | ` satisfy
-    | | | + <*>
-    | | | | + pure (@) ((@) (.) ((@) (.) Haskell)) ((@) ((@) (.) const) ((@) const Haskell))
-    | | | | ` satisfy
-    | | | ` <*>
-    | | |   + <*>
-    | | |   | + <*>
-    | | |   | | + <*>
-    | | |   | | | + pure (@) ((@) (.) ((@) (.) ((@) (.) ((@) (.) ((@) (.) Haskell))))) ((@) ((@) (.) ((@) (.) ((@) (.) ((@) (.) const)))) ((@) ((@) (.) ((@) (.) ((@) (.) ((@) ((@) flip ($)) ((@) const Haskell))))) ((@) ((@) (.) ((@) (.) ((@) (.) (.)))) ((@) ((@) (.) ((@) (.) ((@) (.) const))) ((@) ((@) (.) ((@) (.) ((@) ((@) flip ($)) Haskell))) ((@) ((@) (.) ((@) (.) (.))) ((@) ((@) (.) ((@) (.) ((@) const id))) const)))))))
-    | | |   | | | ` satisfy
-    | | |   | | ` ref let_2
-    | | |   | ` rec let_1
-    | | |   ` satisfy
-    | | + look
-    | | | ` satisfy
-    | | ` empty
-    | ` ref let_2
+    | + pure Haskell
+    | ` <*>
+    |   + <*>
+    |   | + pure const
+    |   | ` conditional
+    |   |   + bs
+    |   |   | + <*>
+    |   |   | | + <*>
+    |   |   | | | + pure const
+    |   |   | | | ` pure Haskell
+    |   |   | | ` ref let_2
+    |   |   | + <*>
+    |   |   | | + <*>
+    |   |   | | | + pure const
+    |   |   | | | ` pure Haskell
+    |   |   | | ` ref let_2
+    |   |   | + <*>
+    |   |   | | + <*>
+    |   |   | | | + pure const
+    |   |   | | | ` pure Haskell
+    |   |   | | ` ref let_2
+    |   |   | + <*>
+    |   |   | | + <*>
+    |   |   | | | + pure const
+    |   |   | | | ` pure Haskell
+    |   |   | | ` ref let_2
+    |   |   | + <*>
+    |   |   | | + <*>
+    |   |   | | | + pure const
+    |   |   | | | ` pure Haskell
+    |   |   | | ` ref let_2
+    |   |   | + <*>
+    |   |   | | + <*>
+    |   |   | | | + pure const
+    |   |   | | | ` pure Haskell
+    |   |   | | ` ref let_2
+    |   |   | ` <*>
+    |   |   |   + <*>
+    |   |   |   | + pure const
+    |   |   |   | ` <*>
+    |   |   |   |   + <*>
+    |   |   |   |   | + <*>
+    |   |   |   |   | | + pure const
+    |   |   |   |   | | ` pure id
+    |   |   |   |   | ` <*>
+    |   |   |   |   |   + <*>
+    |   |   |   |   |   | + pure const
+    |   |   |   |   |   | ` ref let_2
+    |   |   |   |   |   ` ref let_1
+    |   |   |   |   ` <*>
+    |   |   |   |     + pure Haskell
+    |   |   |   |     ` rec let_3
+    |   |   |   ` <*>
+    |   |   |     + <*>
+    |   |   |     | + pure const
+    |   |   |     | ` pure Haskell
+    |   |   |     ` ref let_2
+    |   |   + look
+    |   |   | ` ref let_2
+    |   |   ` empty
+    |   ` ref let_1
     ` pure Haskell
diff --git a/test/Golden/Grammar/brainfuck.opt.dump b/test/Golden/Grammar/brainfuck.opt.dump
new file mode 100644 (file)
index 0000000..3125e68
--- /dev/null
@@ -0,0 +1,48 @@
+<*>
++ <*>
+| + pure (const id)
+| ` def let_1
+|   ` <*>
+|     + pure ((flip ($)) () . const id)
+|     ` chainPost
+|       + pure ()
+|       ` <*>
+|         + pure (((.) ((flip ($)) id) . const) id)
+|         ` satisfy
+` def let_2
+  ` chainPre
+    + <*>
+    | + conditional
+    | | + bs
+    | | | + <*>
+    | | | | + pure ((.) Haskell . (const . const Haskell))
+    | | | | ` satisfy
+    | | | + <*>
+    | | | | + pure ((.) Haskell . (const . const Haskell))
+    | | | | ` satisfy
+    | | | + <*>
+    | | | | + pure ((.) Haskell . (const . const Haskell))
+    | | | | ` satisfy
+    | | | + <*>
+    | | | | + pure ((.) Haskell . (const . const Haskell))
+    | | | | ` satisfy
+    | | | + <*>
+    | | | | + pure ((.) Haskell . (const . const Haskell))
+    | | | | ` satisfy
+    | | | + <*>
+    | | | | + pure ((.) Haskell . (const . const Haskell))
+    | | | | ` satisfy
+    | | | ` <*>
+    | | |   + <*>
+    | | |   | + <*>
+    | | |   | | + <*>
+    | | |   | | | + pure ((.) ((.) ((.) ((.) Haskell))) . ((.) ((.) ((.) const)) . ((.) ((.) ((flip ($)) (const Haskell))) . ((.) ((.) (.)) . ((.) ((.) const) . ((.) ((flip ($)) Haskell) . ((.) (.) . ((.) (const id) . const))))))))
+    | | |   | | | ` satisfy
+    | | |   | | ` ref let_1
+    | | |   | ` rec let_2
+    | | |   ` satisfy
+    | | + look
+    | | | ` satisfy
+    | | ` empty
+    | ` ref let_1
+    ` pure Haskell
index 2cbac0b2a1f101491fff8f1653900a675883d89c..b6f346a1f45afccc9a4b600435e6147eab2e6e5b 100644 (file)
@@ -1,6 +1,8 @@
 <*>
 + <*>
-| + pure (@) const id
+| + <*>
+| | + pure const
+| | ` pure id
 | ` def let_1
 |   ` pure ()
 ` ref let_1
diff --git a/test/Golden/Grammar/unit-unit.opt.dump b/test/Golden/Grammar/unit-unit.opt.dump
new file mode 100644 (file)
index 0000000..41da345
--- /dev/null
@@ -0,0 +1,6 @@
+<*>
++ <*>
+| + pure (const id)
+| ` def let_1
+|   ` pure ()
+` ref let_1
diff --git a/test/Golden/Grammar/unit.opt.dump b/test/Golden/Grammar/unit.opt.dump
new file mode 100644 (file)
index 0000000..04b7e20
--- /dev/null
@@ -0,0 +1 @@
+pure ()