machine: normalOrderReduction at the last moment
authorJulien Moutinho <julm+symantic-parser@sourcephile.fr>
Fri, 30 Jul 2021 13:07:27 +0000 (15:07 +0200)
committerJulien Moutinho <julm+symantic-parser@sourcephile.fr>
Fri, 30 Jul 2021 13:14:15 +0000 (15:14 +0200)
61 files changed:
src/Symantic/Parser/Grammar.hs
src/Symantic/Parser/Grammar/ObserveSharing.hs
src/Symantic/Parser/Grammar/Optimize.hs
src/Symantic/Parser/Grammar/Production.hs
src/Symantic/Parser/Grammar/View.hs
src/Symantic/Parser/Grammar/Write.hs
src/Symantic/Parser/Machine/Optimize.hs
src/Symantic/Parser/Machine/Program.hs
src/Symantic/Parser/Machine/View.hs
test/Golden/Grammar/OptimizeGrammar/G1.expected.txt
test/Golden/Grammar/OptimizeGrammar/G10.expected.txt
test/Golden/Grammar/OptimizeGrammar/G11.expected.txt
test/Golden/Grammar/OptimizeGrammar/G12.expected.txt
test/Golden/Grammar/OptimizeGrammar/G13.expected.txt
test/Golden/Grammar/OptimizeGrammar/G14.expected.txt
test/Golden/Grammar/OptimizeGrammar/G15.expected.txt
test/Golden/Grammar/OptimizeGrammar/G16.expected.txt
test/Golden/Grammar/OptimizeGrammar/G2.expected.txt
test/Golden/Grammar/OptimizeGrammar/G3.expected.txt
test/Golden/Grammar/OptimizeGrammar/G4.expected.txt
test/Golden/Grammar/OptimizeGrammar/G5.expected.txt
test/Golden/Grammar/OptimizeGrammar/G6.expected.txt
test/Golden/Grammar/OptimizeGrammar/G7.expected.txt
test/Golden/Grammar/OptimizeGrammar/G8.expected.txt
test/Golden/Grammar/ViewGrammar/G1.expected.txt
test/Golden/Grammar/ViewGrammar/G10.expected.txt
test/Golden/Grammar/ViewGrammar/G11.expected.txt
test/Golden/Grammar/ViewGrammar/G12.expected.txt
test/Golden/Grammar/ViewGrammar/G13.expected.txt
test/Golden/Grammar/ViewGrammar/G14.expected.txt
test/Golden/Grammar/ViewGrammar/G15.expected.txt
test/Golden/Grammar/ViewGrammar/G16.expected.txt
test/Golden/Grammar/ViewGrammar/G2.expected.txt
test/Golden/Grammar/ViewGrammar/G3.expected.txt
test/Golden/Grammar/ViewGrammar/G4.expected.txt
test/Golden/Grammar/ViewGrammar/G5.expected.txt
test/Golden/Grammar/ViewGrammar/G6.expected.txt
test/Golden/Grammar/ViewGrammar/G7.expected.txt
test/Golden/Grammar/ViewGrammar/G8.expected.txt
test/Golden/Machine/G11.expected.txt
test/Golden/Machine/G12.expected.txt
test/Golden/Machine/G13.expected.txt
test/Golden/Machine/G14.expected.txt
test/Golden/Machine/G15.expected.txt
test/Golden/Machine/G16.expected.txt
test/Golden/Machine/G3.expected.txt
test/Golden/Machine/G4.expected.txt
test/Golden/Machine/G5.expected.txt
test/Golden/Machine/G8.expected.txt
test/Golden/Machine/G9.expected.txt
test/Golden/Parser.hs
test/Golden/Parser/G11/P1.expected.txt
test/Golden/Parser/G12/P1.expected.txt
test/Golden/Parser/G3/P1.expected.txt
test/Golden/Parser/G8/P1.expected.txt
test/Golden/Splice/G11.expected.txt
test/Golden/Splice/G12.expected.txt
test/Golden/Splice/G13.expected.txt
test/Golden/Splice/G14.expected.txt
test/Golden/Splice/G3.expected.txt
test/Golden/Splice/G8.expected.txt

index 6e2793221283595ee2f837c20ac22a6f6e0dc231..4340886f6a85c730c188771bbfaa1b92670edb16 100644 (file)
@@ -24,9 +24,7 @@ import Data.Ord (Ord)
 import Data.Function ((.))
 import Data.String (String)
 import Data.Typeable (Typeable)
-import System.IO (IO)
 import Text.Show (Show(..))
-import qualified Data.Functor as Functor
 import qualified Language.Haskell.TH.Syntax as TH
 
 -- * Type 'Grammar'
index 7a9329b63ea5fccf58f3814b781c4457230c2e7f..719a622f515b5887114a60cc1effd42931fc1496 100644 (file)
@@ -6,24 +6,18 @@ module Symantic.Parser.Grammar.ObserveSharing
   , module Symantic.Parser.Grammar.ObserveSharing
   ) where
 
-import Control.Monad (Monad(..), mapM)
-import Data.Function (($), (.), id)
+import Control.Monad (mapM)
+import Data.Function (($), (.))
 import Data.Hashable (Hashable, hashWithSalt)
-import System.IO (IO)
+import System.IO.Unsafe (unsafePerformIO) -- For 'new'
 import Text.Show (Show(..))
-import Data.Functor (Functor)
-import Data.Functor.Compose (Compose(..))
-import qualified Data.Functor as F
 import qualified Control.Applicative as F
-import System.IO.Unsafe (unsafePerformIO)
-import qualified Data.HashMap.Strict as HM
 
 import Symantic.Parser.Grammar.Combinators
 import Symantic.Derive
 import Symantic.ObserveSharing hiding (observeSharing)
 import qualified Symantic.ObserveSharing as ObserveSharing
 import qualified Language.Haskell.TH.Syntax as TH
-import Debug.Trace
 
 -- | Like 'Observable.observeSharing'
 -- but type-binding @(letName)@ to 'TH.Name'
index 7cc9392f282e61abc27c78f6d5efb3e937aad8f0..f4941fbb665c89980fb40abe27694027c64906ee 100644 (file)
@@ -268,7 +268,7 @@ pattern (:$>:) :: SimplComb repr a -> Production b -> Comb CombApplicable repr b
 pattern x :$>: t <- x :*>: Comb (Pure t)
 instance CombApplicable repr => Derivable (Comb CombApplicable repr) where
   derive = \case
-    Pure x -> pure (optimizeProduction x)
+    Pure x -> pure x
     f :<*>: x -> derive f <*> derive x
     x :<*: y -> derive x <* derive y
     x :*>: y -> derive x *> derive y
@@ -485,7 +485,7 @@ instance CombMatchable repr => Derivable (Comb CombMatchable repr) where
   derive = \case
     Conditional a bs def ->
       conditional (derive a)
-        ((\(p, b) -> (optimizeProduction p, derive b)) F.<$> bs)
+        ((\(p, b) -> (p, derive b)) F.<$> bs)
         (derive def)
 instance
   ( CombApplicable repr
@@ -552,7 +552,7 @@ instance
   CombSatisfiable tok repr =>
   Derivable (Comb (CombSatisfiable tok) repr) where
   derive = \case
-    SatisfyOrFail fs p -> satisfyOrFail fs (optimizeProduction p)
+    SatisfyOrFail fs p -> satisfyOrFail fs p
 instance
   (CombSatisfiable tok repr, Typeable tok) =>
   CombSatisfiable tok (SimplComb repr) where
index 2f14abb440c533826dd71bfc1be275930ba21f28..a0239aab1832eb53621cf710cdda9463b40d7dc7 100644 (file)
@@ -23,7 +23,6 @@ import qualified Language.Haskell.TH.Show as TH
 
 import Symantic.Data
 import Symantic.Lang
-import Symantic.Optimize
 import Symantic.Derive
 
 type Production = Product
@@ -118,9 +117,6 @@ instance Listable Production where
 instance Equalable Production where
   equal = Pair equal equal
 
-optimizeProduction :: Production a -> Production a
-optimizeProduction (Pair v c) = Pair (normalOrderReduction v) (normalOrderReduction c)
-
 -- Identity
 instance Anythingable Identity
 instance Abstractable Identity where
index 5c18593bce9d1be5ee2484f049340b17789bcb11..8894e178fed4485f7205577c639fe88ee7b5c93c 100644 (file)
@@ -7,7 +7,7 @@ import Data.Function (($), (.), id, on)
 import Data.Ord (Ord(..))
 import Data.Semigroup (Semigroup(..))
 import Data.String (String)
-import Data.Tuple (fst, snd)
+import Data.Tuple (fst)
 import Text.Show (Show(..))
 import qualified Data.Functor as Functor
 import qualified Data.HashMap.Strict as HM
@@ -15,6 +15,7 @@ import qualified Data.List as List
 import qualified Data.Tree as Tree
 
 import Symantic.ObserveSharing
+import Symantic.Optimize (normalOrderReduction)
 import Symantic.Parser.Grammar.Combinators
 import Symantic.Parser.Grammar.ObserveSharing
 import qualified Symantic.Parser.Grammar.Production as Prod
@@ -26,6 +27,9 @@ newtype ViewGrammar (showName::Bool) a = ViewGrammar { unViewGrammar ::
 viewGrammar :: ViewGrammar sN a -> ViewGrammar sN a
 viewGrammar = id
 
+showProduction :: Prod.Production a -> String
+showProduction p = showsPrec 10 (normalOrderReduction (Prod.prodCode p)) ""
+
 instance Show (ViewGrammar sN a) where
   show = List.unlines . draw . unViewGrammar
     where
@@ -48,7 +52,7 @@ instance CombAlternable (ViewGrammar sN) where
   try x = ViewGrammar $ Tree.Node ("try", "") [unViewGrammar x]
 instance CombApplicable (ViewGrammar sN) where
   _f <$> x = ViewGrammar $ Tree.Node ("<$>", "") [unViewGrammar x]
-  pure a = ViewGrammar $ Tree.Node ("pure " <> showsPrec 10 (Prod.prodCode a) "", "") []
+  pure a = ViewGrammar $ Tree.Node ("pure "<>showProduction a, "") []
   x <*> y = ViewGrammar $ Tree.Node ("<*>", "") [unViewGrammar x, unViewGrammar y]
   x <* y = ViewGrammar $ Tree.Node ("<*", "") [unViewGrammar x, unViewGrammar y]
   x *> y = ViewGrammar $ Tree.Node ("*>", "") [unViewGrammar x, unViewGrammar y]
@@ -79,13 +83,13 @@ instance CombLookable (ViewGrammar sN) where
   negLook x = ViewGrammar $ Tree.Node ("negLook", "") [unViewGrammar x]
   eof = ViewGrammar $ Tree.Node ("eof", "") []
 instance CombMatchable (ViewGrammar sN) where
-  conditional a bs b = ViewGrammar $ Tree.Node ("conditional", "")
-    [ unViewGrammar a
-    , Tree.Node ("branches", "") (unViewGrammar . snd Functor.<$> bs)
-    , unViewGrammar b
-    ]
+  conditional a bs d = ViewGrammar $ Tree.Node ("conditional", "")
+    $ Tree.Node ("condition", "") [unViewGrammar a]
+    : Tree.Node ("default", "") [unViewGrammar d]
+    : ((\(p,b) -> Tree.Node ("branch "<>showProduction p, "") [unViewGrammar b]) Functor.<$> bs)
 instance CombSatisfiable tok (ViewGrammar sN) where
-  satisfyOrFail _fs _p = ViewGrammar $ Tree.Node ("satisfy", "") []
+  satisfyOrFail _fs p = ViewGrammar $ Tree.Node
+    ("satisfy "<>showProduction p, "") []
 instance CombSelectable (ViewGrammar sN) where
   branch lr l r = ViewGrammar $ Tree.Node ("branch", "")
     [ unViewGrammar lr, unViewGrammar l, unViewGrammar r ]
index b016f7914b9ffe6fdda6719fe733800d6578f647..41adb07502e609326038d148eeb408917e5bbed2 100644 (file)
@@ -147,16 +147,16 @@ instance CombLookable (WriteGrammar sN) where
     where op = infixN 9
   eof = "eof"
 instance CombMatchable (WriteGrammar sN) where
-  conditional a bs def = WriteGrammar $ \inh ->
+  conditional a bs d = WriteGrammar $ \inh ->
     pairWriteGrammarInh inh op $
       Just "conditional " <>
       unWriteGrammar a inh <>
+      unWriteGrammar d inh <>
       Just " [" <>
       Just (mconcat (List.intersperse ", " $
       catMaybes $ (Functor.<$> bs) $ \(p{-TODO: print?-}, b) ->
         unWriteGrammar b inh{writeGrammarInh_op=(infixN 0, SideL)})) <>
-      Just "] " <>
-      unWriteGrammar def inh
+      Just "] "
     where
     op = infixN 9
 instance CombSatisfiable tok (WriteGrammar sN) where
index e4f502ec7eaef798f4d3c337b1798e46813e1a99..81c4f537f25d510213ce6b3d0be4f9bf53b5befb 100644 (file)
@@ -90,9 +90,9 @@ data instance Instr InstrValuable repr inp vs a where
     Instr InstrValuable repr inp (y ': x ': vs) a
 instance InstrValuable repr => Derivable (Instr InstrValuable repr inp vs) where
   derive = \case
-    PushValue x k -> pushValue x (derive k)
+    PushValue v k -> pushValue v (derive k)
     PopValue k -> popValue (derive k)
-    Lift2Value f k -> lift2Value f (derive k)
+    Lift2Value v k -> lift2Value v (derive k)
     SwapValue k -> swapValue (derive k)
 instance InstrValuable repr => InstrValuable (SomeInstr repr) where
   -- 'PopValue' after a 'PushValue' is a no-op.
@@ -144,7 +144,7 @@ data instance Instr InstrBranchable repr inp vs a where
 instance InstrBranchable repr => Derivable (Instr InstrBranchable repr inp vs) where
   derive = \case
     CaseBranch l r -> caseBranch (derive l) (derive r)
-    ChoicesBranch bs d -> choicesBranch ((derive Functor.<$>) Functor.<$> bs) (derive d)
+    ChoicesBranch bs d -> choicesBranch ((\(p,b) -> (p, derive b)) Functor.<$> bs) (derive d)
 instance InstrBranchable repr => InstrBranchable (SomeInstr repr) where
   caseBranch l = SomeInstr . CaseBranch l
   choicesBranch bs = SomeInstr . ChoicesBranch bs
index 443a2cc43cd08b41624184a862f1ddaa3a567669..ecbbd79ac26d7c210b090a6551ce4609d880e7e5 100644 (file)
@@ -265,8 +265,6 @@ instance
   , InstrReadable tok repr
   , Typeable tok
   ) => CombSatisfiable tok (Program repr inp) where
-  -- Note: 'read' is left with the responsability
-  -- to apply 'normalOrderReduction' if need be.
   satisfyOrFail fs p = Program $ return . read fs (prodCode p)
 instance
   ( InstrBranchable repr
index 0a77a56dc0513a6ac3999d1aef89e8c439c05061..817d6ee50733c5aa6b20d85f391ec86d7ef9db9a 100644 (file)
@@ -20,6 +20,7 @@ import qualified Data.Tree as Tree
 import qualified Language.Haskell.TH.Syntax as TH
 import Prelude (error)
 
+import Symantic.Optimize (normalOrderReduction)
 import Symantic.Parser.Grammar.Combinators (UnscopedRegister(..))
 import Symantic.Parser.Grammar.ObserveSharing
 import Symantic.Parser.Machine.Instructions
@@ -32,16 +33,17 @@ data ViewMachine (showName::Bool) inp (vs:: [Type]) a
     -- ^ Provide 'GenAnalysis', which is important for debugging
     -- and improving golden tests, see 'viewInstrCmd'.
   , unViewMachine ::
-      LetRecs TH.Name GenAnalysis -> -- Output of 'runOpenRecs'.
+      LetRecs TH.Name GenAnalysis -> -- Output of 'mutualFix'.
       Tree.Forest (String, String) ->
       Tree.Forest (String, String)
   }
 
-viewMachine ::
-  ViewMachine sN inp vs a ->
-  ViewMachine sN inp vs a
+viewMachine :: ViewMachine sN inp vs a -> ViewMachine sN inp vs a
 viewMachine = id
 
+showSplice :: Splice a -> String
+showSplice p = showsPrec 10 (normalOrderReduction p) ""
+
 -- | Helper to view a command.
 viewInstrCmd ::
   Either TH.Name (Gen inp vs a) ->
@@ -76,7 +78,7 @@ instance Show (ViewMachine sN inp vs a) where
 instance InstrValuable (ViewMachine sN) where
   pushValue a k = ViewMachine
     { unViewMachine = \lm next ->
-        viewInstrCmd (Right gen) lm ("pushValue "<>showsPrec 10 a "", "") [] :
+        viewInstrCmd (Right gen) lm ("pushValue "<>showSplice a, "") [] :
         unViewMachine k lm next
     , viewGen = gen
     } where gen = pushValue a (viewGen k)
@@ -88,7 +90,7 @@ instance InstrValuable (ViewMachine sN) where
     } where gen = popValue (viewGen k)
   lift2Value f k = ViewMachine
     { unViewMachine = \lm next ->
-        viewInstrCmd (Right gen) lm ("lift2Value "<>showsPrec 10 f "", "") [] :
+        viewInstrCmd (Right gen) lm ("lift2Value "<>showSplice f, "") [] :
         unViewMachine k lm next
     , viewGen = gen
     } where gen = lift2Value f (viewGen k)
@@ -135,7 +137,7 @@ instance InstrBranchable (ViewMachine sN) where
   choicesBranch bs d = ViewMachine
     { unViewMachine = \lm next ->
         viewInstrCmd (Right gen) lm ("choicesBranch", "") (
-          ((\(p, b) -> viewInstrArg ("branch "<>showsPrec 10 p "") $
+          ((\(p, b) -> viewInstrArg ("branch "<>showSplice p) $
             unViewMachine b lm []) <$> bs) <>
           [ viewInstrArg "default" (unViewMachine d lm []) ]
         ) : next
@@ -205,7 +207,7 @@ instance
   InstrReadable tok (ViewMachine sN) where
   read es p k = ViewMachine
     { unViewMachine = \lm next ->
-        viewInstrCmd (Right gen) lm ("read "<>showsPrec 10 p "", "") [] :
+        viewInstrCmd (Right gen) lm ("read "<>showSplice p, "") [] :
         unViewMachine k lm next
     , viewGen = gen
     } where gen = read es p (viewGen k)
index f39f8f00580ef88267e816f059f69e375e2bdee3..4a8ffe4c2391f7796e7471ee6abb7b5798b69c6a 100644 (file)
@@ -1,4 +1,4 @@
 lets
 ` <*>
   + pure (\x_0 -> GHC.Show.show 'a')
-  ` satisfy
+  ` satisfy ((GHC.Classes.==) 'a')
index 5cd784945240e15cc96cac8b770e5d3518ef2aa0..96ced6e8f51c75a452829fe2f4176560ef4e2d16 100644 (file)
@@ -4,7 +4,7 @@ lets
   ` <|>
     + <*>
     | + pure (\x_0 -> 'a')
-    | ` satisfy
+    | ` satisfy ((GHC.Classes.==) 'a')
     ` <*>
       + pure (\x_0 -> 'b')
-      ` satisfy
+      ` satisfy ((GHC.Classes.==) 'b')
index 0ea3f53ad95aee8d0ace3a554c94566ab1e2e7d8..0d85c53a995ed201dd45a107b2d88c7b8adc965e 100644 (file)
@@ -5,6 +5,6 @@ lets
   | ` chainPre
   |   + <*>
   |   | + pure (\x_0 -> (GHC.Types.:) 'a')
-  |   | ` satisfy
+  |   | ` satisfy ((GHC.Classes.==) 'a')
   |   ` pure GHC.Types.[]
-  ` satisfy
+  ` satisfy ((GHC.Classes.==) 'b')
index f4767b86645bea9c34640b076e09527922a56b03..c2393c2c8307cd2a6b405707d408a84f2676f3f7 100644 (file)
@@ -5,6 +5,6 @@ lets
   | ` chainPre
   |   + <*>
   |   | + pure (GHC.Types.:)
-  |   | ` satisfy
+  |   | ` satisfy (\t_0 -> ('a' GHC.Classes.== t_0) GHC.Classes.|| (('b' GHC.Classes.== t_0) GHC.Classes.|| (('c' GHC.Classes.== t_0) GHC.Classes.|| (('d' GHC.Classes.== t_0) GHC.Classes.|| GHC.Types.False))))
   |   ` pure GHC.Types.[]
   ` eof
index bd20e525c990e8befb7739a41b84c3d24af1fc8e..5dbad1dc036ee7a8c7d879cf4fc52476b0ac85ee 100644 (file)
@@ -6,44 +6,52 @@ lets
 |     + pure GHC.Tuple.()
 |     ` <*>
 |       + pure (\x_0 -> \x_1 -> x_1)
-|       ` satisfy
+|       ` satisfy (\c_0 -> GHC.Classes.not (('<' GHC.Classes.== c_0) GHC.Classes.|| (('>' GHC.Classes.== c_0) GHC.Classes.|| (('+' GHC.Classes.== c_0) GHC.Classes.|| (('-' GHC.Classes.== c_0) GHC.Classes.|| ((',' GHC.Classes.== c_0) GHC.Classes.|| (('.' GHC.Classes.== c_0) GHC.Classes.|| (('[' GHC.Classes.== c_0) GHC.Classes.|| ((']' GHC.Classes.== c_0) GHC.Classes.|| GHC.Types.False)))))))))
 + let <hidden>
 | ` chainPre
 |   + <*>
 |   | + <*>
 |   | | + pure (\x_0 -> \x_1 -> (GHC.Types.:) x_0)
 |   | | ` conditional
-|   | |   + look
-|   | |   | ` satisfy
-|   | |   + branches
-|   | |   | + <*>
-|   | |   | | + pure (\x_0 -> Parsers.Brainfuck.Types.Backward)
-|   | |   | | ` satisfy
-|   | |   | + <*>
-|   | |   | | + pure (\x_0 -> Parsers.Brainfuck.Types.Forward)
-|   | |   | | ` satisfy
-|   | |   | + <*>
-|   | |   | | + pure (\x_0 -> Parsers.Brainfuck.Types.Increment)
-|   | |   | | ` satisfy
-|   | |   | + <*>
-|   | |   | | + pure (\x_0 -> Parsers.Brainfuck.Types.Decrement)
-|   | |   | | ` satisfy
-|   | |   | + <*>
-|   | |   | | + pure (\x_0 -> Parsers.Brainfuck.Types.Input)
-|   | |   | | ` satisfy
-|   | |   | + <*>
-|   | |   | | + pure (\x_0 -> Parsers.Brainfuck.Types.Output)
-|   | |   | | ` satisfy
+|   | |   + condition
+|   | |   | ` look
+|   | |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   | |   + default
+|   | |   | ` failure
+|   | |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '<' x_0)
 |   | |   | ` <*>
-|   | |   |   + <*>
-|   | |   |   | + <*>
-|   | |   |   | | + <*>
-|   | |   |   | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> Parsers.Brainfuck.Types.Loop x_2)
-|   | |   |   | | | ` satisfy
-|   | |   |   | | ` ref <hidden>
-|   | |   |   | ` rec <hidden>
-|   | |   |   ` satisfy
-|   | |   ` failure
+|   | |   |   + pure (\x_0 -> Parsers.Brainfuck.Types.Backward)
+|   | |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   | |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '>' x_0)
+|   | |   | ` <*>
+|   | |   |   + pure (\x_0 -> Parsers.Brainfuck.Types.Forward)
+|   | |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   | |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '+' x_0)
+|   | |   | ` <*>
+|   | |   |   + pure (\x_0 -> Parsers.Brainfuck.Types.Increment)
+|   | |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   | |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '-' x_0)
+|   | |   | ` <*>
+|   | |   |   + pure (\x_0 -> Parsers.Brainfuck.Types.Decrement)
+|   | |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   | |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) ',' x_0)
+|   | |   | ` <*>
+|   | |   |   + pure (\x_0 -> Parsers.Brainfuck.Types.Input)
+|   | |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   | |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '.' x_0)
+|   | |   | ` <*>
+|   | |   |   + pure (\x_0 -> Parsers.Brainfuck.Types.Output)
+|   | |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   | |   ` branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '[' x_0)
+|   | |     ` <*>
+|   | |       + <*>
+|   | |       | + <*>
+|   | |       | | + <*>
+|   | |       | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> Parsers.Brainfuck.Types.Loop x_2)
+|   | |       | | | ` satisfy (\x_0 -> GHC.Types.True)
+|   | |       | | ` ref <hidden>
+|   | |       | ` rec <hidden>
+|   | |       ` satisfy ((GHC.Classes.==) ']')
 |   | ` ref <hidden>
 |   ` pure GHC.Types.[]
 ` <*>
index 6883757923d3ea0d9d7ae73bf324d69778a6153f..41dd1131cfa8d829a151e165ac0ee4f583167f66 100644 (file)
@@ -31,7 +31,7 @@ lets
 |   |     + <*>
 |   |     | + <*>
 |   |     | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
-|   |     | | ` satisfy
+|   |     | | ` satisfy ((GHC.Classes.==) '!')
 |   |     | ` ref <hidden>
 |   |     ` ref <hidden>
 |   ` ref <hidden>
@@ -43,7 +43,7 @@ lets
 |   | | | + <*>
 |   | | | | + <*>
 |   | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> GHC.Tuple.())
-|   | | | | | ` satisfy
+|   | | | | | ` satisfy ((GHC.Classes.==) '[')
 |   | | | | ` ref <hidden>
 |   | | | ` ref <hidden>
 |   | | ` chainPost
@@ -51,7 +51,7 @@ lets
 |   | |   ` <*>
 |   | |     + pure (\x_0 -> \x_1 -> x_1)
 |   | |     ` ref <hidden>
-|   | ` satisfy
+|   | ` satisfy ((GHC.Classes.==) ']')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
@@ -61,7 +61,7 @@ lets
 |   | | | + <*>
 |   | | | | + <*>
 |   | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> x_3)
-|   | | | | | ` satisfy
+|   | | | | | ` satisfy ((GHC.Classes.==) '{')
 |   | | | | ` ref <hidden>
 |   | | | ` chainPost
 |   | | |   + ref <hidden>
@@ -75,8 +75,8 @@ lets
 |   | | |       | |   ` <*>
 |   | | |       | |     + <*>
 |   | | |       | |     | + pure (\x_0 -> \x_1 -> (GHC.Types.:) 'i' ((GHC.Types.:) 'f' GHC.Types.[]))
-|   | | |       | |     | ` satisfy
-|   | | |       | |     ` satisfy
+|   | | |       | |     | ` satisfy ((GHC.Classes.==) 'i')
+|   | | |       | |     ` satisfy ((GHC.Classes.==) 'f')
 |   | | |       | ` ref <hidden>
 |   | | |       ` <|>
 |   | | |         + <*>
@@ -91,11 +91,11 @@ lets
 |   | | |         | | | |     | | + <*>
 |   | | |         | | | |     | | | + <*>
 |   | | |         | | | |     | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> (GHC.Types.:) 'w' ((GHC.Types.:) 'h' ((GHC.Types.:) 'i' ((GHC.Types.:) 'l' ((GHC.Types.:) 'e' GHC.Types.[])))))
-|   | | |         | | | |     | | | | ` satisfy
-|   | | |         | | | |     | | | ` satisfy
-|   | | |         | | | |     | | ` satisfy
-|   | | |         | | | |     | ` satisfy
-|   | | |         | | | |     ` satisfy
+|   | | |         | | | |     | | | | ` satisfy ((GHC.Classes.==) 'w')
+|   | | |         | | | |     | | | ` satisfy ((GHC.Classes.==) 'h')
+|   | | |         | | | |     | | ` satisfy ((GHC.Classes.==) 'i')
+|   | | |         | | | |     | ` satisfy ((GHC.Classes.==) 'l')
+|   | | |         | | | |     ` satisfy ((GHC.Classes.==) 'e')
 |   | | |         | | | ` ref <hidden>
 |   | | |         | | ` ref <hidden>
 |   | | |         | ` rec <hidden>
@@ -121,9 +121,9 @@ lets
 |   | | |           |   | | | | | | | | |   | |     + <*>
 |   | | |           |   | | | | | | | | |   | |     | + <*>
 |   | | |           |   | | | | | | | | |   | |     | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'v' ((GHC.Types.:) 'a' ((GHC.Types.:) 'r' GHC.Types.[])))
-|   | | |           |   | | | | | | | | |   | |     | | ` satisfy
-|   | | |           |   | | | | | | | | |   | |     | ` satisfy
-|   | | |           |   | | | | | | | | |   | |     ` satisfy
+|   | | |           |   | | | | | | | | |   | |     | | ` satisfy ((GHC.Classes.==) 'v')
+|   | | |           |   | | | | | | | | |   | |     | ` satisfy ((GHC.Classes.==) 'a')
+|   | | |           |   | | | | | | | | |   | |     ` satisfy ((GHC.Classes.==) 'r')
 |   | | |           |   | | | | | | | | |   | ` ref <hidden>
 |   | | |           |   | | | | | | | | |   ` ref <hidden>
 |   | | |           |   | | | | | | | | ` ref <hidden>
@@ -137,7 +137,7 @@ lets
 |   | | |           |   | | | | | | |     | ` ref <hidden>
 |   | | |           |   | | | | | | |     ` ref <hidden>
 |   | | |           |   | | | | | | ` ref <hidden>
-|   | | |           |   | | | | | ` satisfy
+|   | | |           |   | | | | | ` satisfy ((GHC.Classes.==) '=')
 |   | | |           |   | | | | ` ref <hidden>
 |   | | |           |   | | | ` ref <hidden>
 |   | | |           |   | | ` chainPost
@@ -157,37 +157,37 @@ lets
 |   | | |             | ` ref <hidden>
 |   | | |             ` ref <hidden>
 |   | | ` ref <hidden>
-|   | ` satisfy
+|   | ` satisfy ((GHC.Classes.==) '}')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
 |   + <*>
 |   | + pure (\x_0 -> \x_1 -> '(')
-|   | ` satisfy
+|   | ` satisfy ((GHC.Classes.==) '(')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
 |   + <*>
 |   | + pure (\x_0 -> \x_1 -> ')')
-|   | ` satisfy
+|   | ` satisfy ((GHC.Classes.==) ')')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
 |   + <*>
 |   | + pure (\x_0 -> \x_1 -> ',')
-|   | ` satisfy
+|   | ` satisfy ((GHC.Classes.==) ',')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
 |   + <*>
 |   | + pure (\x_0 -> \x_1 -> ';')
-|   | ` satisfy
+|   | ` satisfy ((GHC.Classes.==) ';')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
 |   + <*>
 |   | + pure (\x_0 -> \x_1 -> x_1)
-|   | ` satisfy
+|   | ` satisfy GHC.Unicode.isSpace
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
@@ -198,12 +198,12 @@ lets
 |   |     + <*>
 |   |     | + <*>
 |   |     | | + pure (\x_0 -> \x_1 -> \x_2 -> x_2)
-|   |     | | ` satisfy
+|   |     | | ` satisfy Parsers.Nandlang.nandIdentStart
 |   |     | ` chainPost
 |   |     |   + ref <hidden>
 |   |     |   ` <*>
 |   |     |     + pure (\x_0 -> \x_1 -> x_1)
-|   |     |     ` satisfy
+|   |     |     ` satisfy Parsers.Nandlang.nandIdentLetter
 |   |     ` ref <hidden>
 |   ` ref <hidden>
 + let <hidden>
@@ -214,10 +214,10 @@ lets
 |   | | ` <|>
 |   | |   + <*>
 |   | |   | + pure (\x_0 -> '0')
-|   | |   | ` satisfy
+|   | |   | ` satisfy ((GHC.Classes.==) '0')
 |   | |   ` <*>
 |   | |     + pure (\x_0 -> '1')
-|   | |     ` satisfy
+|   | |     ` satisfy ((GHC.Classes.==) '1')
 |   | ` ref <hidden>
 |   ` <|>
 |     + <*>
@@ -225,21 +225,21 @@ lets
 |     | | + <*>
 |     | | | + <*>
 |     | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_1)
-|     | | | | ` satisfy
+|     | | | | ` satisfy ((GHC.Classes.==) '\'')
 |     | | | ` <|>
 |     | | |   + <*>
 |     | | |   | + <*>
 |     | | |   | | + pure (\x_0 -> \x_1 -> x_1)
-|     | | |   | | ` satisfy
+|     | | |   | | ` satisfy Parsers.Nandlang.nandStringLetter
 |     | | |   | ` ref <hidden>
 |     | | |   ` <*>
 |     | | |     + <*>
 |     | | |     | + <*>
 |     | | |     | | + pure (\x_0 -> \x_1 -> \x_2 -> x_2)
-|     | | |     | | ` satisfy
-|     | | |     | ` satisfy
+|     | | |     | | ` satisfy ((GHC.Classes.==) '\\')
+|     | | |     | ` satisfy (\t_0 -> ('0' GHC.Classes.== t_0) GHC.Classes.|| (('t' GHC.Classes.== t_0) GHC.Classes.|| (('n' GHC.Classes.== t_0) GHC.Classes.|| (('v' GHC.Classes.== t_0) GHC.Classes.|| (('f' GHC.Classes.== t_0) GHC.Classes.|| (('r' GHC.Classes.== t_0) GHC.Classes.|| GHC.Types.False))))))
 |     | | |     ` ref <hidden>
-|     | | ` satisfy
+|     | | ` satisfy ((GHC.Classes.==) '\'')
 |     | ` ref <hidden>
 |     ` <*>
 |       + <*>
@@ -299,7 +299,7 @@ lets
 + let <hidden>
 | ` pure GHC.Tuple.()
 + let <hidden>
-| ` satisfy
+| ` satisfy (\t_0 -> ('0' GHC.Classes.== t_0) GHC.Classes.|| (('1' GHC.Classes.== t_0) GHC.Classes.|| (('2' GHC.Classes.== t_0) GHC.Classes.|| (('3' GHC.Classes.== t_0) GHC.Classes.|| (('4' GHC.Classes.== t_0) GHC.Classes.|| (('5' GHC.Classes.== t_0) GHC.Classes.|| (('6' GHC.Classes.== t_0) GHC.Classes.|| (('7' GHC.Classes.== t_0) GHC.Classes.|| (('8' GHC.Classes.== t_0) GHC.Classes.|| (('9' GHC.Classes.== t_0) GHC.Classes.|| GHC.Types.False))))))))))
 ` <*>
   + <*>
   | + <*>
@@ -327,14 +327,14 @@ lets
   | |     | | | | | | |     | | | | | + <*>
   | |     | | | | | | |     | | | | | | + <*>
   | |     | | | | | | |     | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> \x_7 -> (GHC.Types.:) 'f' ((GHC.Types.:) 'u' ((GHC.Types.:) 'n' ((GHC.Types.:) 'c' ((GHC.Types.:) 't' ((GHC.Types.:) 'i' ((GHC.Types.:) 'o' ((GHC.Types.:) 'n' GHC.Types.[]))))))))
-  | |     | | | | | | |     | | | | | | | ` satisfy
-  | |     | | | | | | |     | | | | | | ` satisfy
-  | |     | | | | | | |     | | | | | ` satisfy
-  | |     | | | | | | |     | | | | ` satisfy
-  | |     | | | | | | |     | | | ` satisfy
-  | |     | | | | | | |     | | ` satisfy
-  | |     | | | | | | |     | ` satisfy
-  | |     | | | | | | |     ` satisfy
+  | |     | | | | | | |     | | | | | | | ` satisfy ((GHC.Classes.==) 'f')
+  | |     | | | | | | |     | | | | | | ` satisfy ((GHC.Classes.==) 'u')
+  | |     | | | | | | |     | | | | | ` satisfy ((GHC.Classes.==) 'n')
+  | |     | | | | | | |     | | | | ` satisfy ((GHC.Classes.==) 'c')
+  | |     | | | | | | |     | | | ` satisfy ((GHC.Classes.==) 't')
+  | |     | | | | | | |     | | ` satisfy ((GHC.Classes.==) 'i')
+  | |     | | | | | | |     | ` satisfy ((GHC.Classes.==) 'o')
+  | |     | | | | | | |     ` satisfy ((GHC.Classes.==) 'n')
   | |     | | | | | | ` ref <hidden>
   | |     | | | | | ` ref <hidden>
   | |     | | | | ` ref <hidden>
@@ -344,7 +344,7 @@ lets
   | |     | |   | + <*>
   | |     | |   | | + <*>
   | |     | |   | | | + pure (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
-  | |     | |   | | | ` satisfy
+  | |     | |   | | | ` satisfy ((GHC.Classes.==) ':')
   | |     | |   | | ` ref <hidden>
   | |     | |   | ` ref <hidden>
   | |     | |   ` ref <hidden>
index fd178cc179b8501f76c25598c8cd68bdfb9a3e8f..79b24c9c162e9b946b0d017f35b8113b85b4e10c 100644 (file)
@@ -5,8 +5,8 @@ lets
   | ` <|>
   |   + <*>
   |   | + pure (\x_0 -> 'a')
-  |   | ` satisfy
+  |   | ` satisfy ((GHC.Classes.==) 'a')
   |   ` <*>
   |     + pure (\x_0 -> 'b')
-  |     ` satisfy
-  ` satisfy
+  |     ` satisfy ((GHC.Classes.==) 'b')
+  ` satisfy ((GHC.Classes.==) 'c')
index d1dc7d08fc1a568a999677da98c96c1d8c4324af..adf590eaa3d3eaeb1dbf9e88ee26c5883c980933 100644 (file)
@@ -5,12 +5,12 @@ lets
   | ` <|>
   |   + <*>
   |   | + pure (\x_0 -> 'a')
-  |   | ` satisfy
+  |   | ` satisfy ((GHC.Classes.==) 'a')
   |   ` <|>
   |     + <*>
   |     | + pure (\x_0 -> 'b')
-  |     | ` satisfy
+  |     | ` satisfy ((GHC.Classes.==) 'b')
   |     ` <*>
   |       + pure (\x_0 -> 'c')
-  |       ` satisfy
-  ` satisfy
+  |       ` satisfy ((GHC.Classes.==) 'c')
+  ` satisfy ((GHC.Classes.==) 'd')
index fc06d8b4d18051eb2936a4cbfbdb62e46c702100..9378ea6a86b4c7678caac5e5412f9faba4bc765b 100644 (file)
@@ -6,6 +6,6 @@ lets
       + <*>
       | + <*>
       | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' GHC.Types.[])))
-      | | ` satisfy
-      | ` satisfy
-      ` satisfy
+      | | ` satisfy ((GHC.Classes.==) 'a')
+      | ` satisfy ((GHC.Classes.==) 'b')
+      ` satisfy ((GHC.Classes.==) 'c')
index dfeb3083025ece65fff9ba5d5ee33fc59b5ed143..a9deb8de82a4e84e46bf6612a85db4a6c121f0e7 100644 (file)
@@ -4,5 +4,5 @@ lets
   ` chainPre
     + <*>
     | + pure (\x_0 -> (GHC.Types.:) 'a')
-    | ` satisfy
+    | ` satisfy ((GHC.Classes.==) 'a')
     ` pure GHC.Types.[]
index d0e5bed27c901eaea34ec17270752b9bf5338d1f..38410878ce160f31a8bbb5dcce7d8ba444970245 100644 (file)
@@ -6,10 +6,10 @@ lets
 |     | + <*>
 |     | | + <*>
 |     | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types.[]))))
-|     | | | ` satisfy
-|     | | ` satisfy
-|     | ` satisfy
-|     ` satisfy
+|     | | | ` satisfy ((GHC.Classes.==) 'a')
+|     | | ` satisfy ((GHC.Classes.==) 'b')
+|     | ` satisfy ((GHC.Classes.==) 'c')
+|     ` satisfy ((GHC.Classes.==) 'd')
 ` <*>
   + <*>
   | + pure (\x_0 -> \x_1 -> GHC.Show.show ((GHC.Types.:) x_0 x_1))
index 91450074eb343bdf4ec899bd9e554056040b6159..98545d0e604b95e12ba4f1a8b751a5911db0175d 100644 (file)
@@ -6,10 +6,10 @@ lets
 |     | + <*>
 |     | | + <*>
 |     | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types.[]))))
-|     | | | ` satisfy
-|     | | ` satisfy
-|     | ` satisfy
-|     ` satisfy
+|     | | | ` satisfy ((GHC.Classes.==) 'a')
+|     | | ` satisfy ((GHC.Classes.==) 'b')
+|     | ` satisfy ((GHC.Classes.==) 'c')
+|     ` satisfy ((GHC.Classes.==) 'd')
 ` <*>
   + <*>
   | + <*>
index e0fb9b3c00a20decbeaaea7e6069cdd224485b6f..78f07381675c28a2642e87bde3c95106fbe51470 100644 (file)
@@ -5,10 +5,10 @@ lets
     + <*>
     | + <*>
     | | + pure (\x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types.[]))
-    | | ` satisfy
-    | ` satisfy
+    | | ` satisfy ((GHC.Classes.==) 'a')
+    | ` satisfy ((GHC.Classes.==) 'a')
     ` <*>
       + <*>
       | + pure (\x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types.[]))
-      | ` satisfy
-      ` satisfy
+      | ` satisfy ((GHC.Classes.==) 'a')
+      ` satisfy ((GHC.Classes.==) 'b')
index ebeaf1aa9548dfd2772d632d5d824afb6e55d144..46f5eec9fd4b38e521254eadee6016cb8e23050a 100644 (file)
@@ -6,11 +6,11 @@ lets
     | ` <*>
     |   + <*>
     |   | + pure (\x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types.[]))
-    |   | ` satisfy
-    |   ` satisfy
+    |   | ` satisfy ((GHC.Classes.==) 'a')
+    |   ` satisfy ((GHC.Classes.==) 'a')
     ` try
       ` <*>
         + <*>
         | + pure (\x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types.[]))
-        | ` satisfy
-        ` satisfy
+        | ` satisfy ((GHC.Classes.==) 'a')
+        ` satisfy ((GHC.Classes.==) 'b')
index 291e1902648702ef8d69b6327138c9872c7fffa4..67f8530e2248ac8a9b407a346cbaf4e257b813d2 100644 (file)
@@ -5,6 +5,6 @@ lets
   | ` chainPre
   |   + <*>
   |   | + pure (\x_0 -> (GHC.Types.:) 'r')
-  |   | ` satisfy
+  |   | ` satisfy ((GHC.Classes.==) 'r')
   |   ` pure GHC.Types.[]
   ` eof
index fffecdd00edf0881700e3b26c8e310d0441858f2..5fa3749b96e0a6dd579f535b7de99698b3b3140e 100644 (file)
@@ -5,4 +5,4 @@ lets
     + <*>
     | + pure (\x_0 -> \x_1 -> x_0)
     | ` pure 'a'
-    ` satisfy
+    ` satisfy ((GHC.Classes.==) 'a')
index c29a057faff634e7ec3d23f99d584dc6c13c7b7a..584e5a5bc6c560d5d120c8d92bc5034386428538 100644 (file)
@@ -6,9 +6,9 @@ lets
     | + <*>
     | | + pure (\x_0 -> \x_1 -> x_0)
     | | ` pure 'a'
-    | ` satisfy
+    | ` satisfy ((GHC.Classes.==) 'a')
     ` <*>
       + <*>
       | + pure (\x_0 -> \x_1 -> x_0)
       | ` pure 'b'
-      ` satisfy
+      ` satisfy ((GHC.Classes.==) 'b')
index c1074f8028744174afe0fde42870265cd4ce7040..aabdebe1acb0cea5005c271cde721a315c70ff32 100644 (file)
@@ -11,10 +11,10 @@ lets
     |   |   + <*>
     |   |   | + pure (\x_0 -> \x_1 -> x_0)
     |   |   | ` pure 'a'
-    |   |   ` satisfy
+    |   |   ` satisfy ((GHC.Classes.==) 'a')
     |   ` pure GHC.Types.[]
     ` <*>
       + <*>
       | + pure (\x_0 -> \x_1 -> x_0)
       | ` pure 'b'
-      ` satisfy
+      ` satisfy ((GHC.Classes.==) 'b')
index fcc760e3e8c1ea86f3f7ba9aaca26f329f447d75..ec0d5c6c82efbac836ef767e5134e9e668b52d55 100644 (file)
@@ -7,6 +7,6 @@ lets
     | ` chainPre
     |   + <*>
     |   | + pure (GHC.Types.:)
-    |   | ` satisfy
+    |   | ` satisfy (\t_0 -> ('a' GHC.Classes.== t_0) GHC.Classes.|| (('b' GHC.Classes.== t_0) GHC.Classes.|| (('c' GHC.Classes.== t_0) GHC.Classes.|| (('d' GHC.Classes.== t_0) GHC.Classes.|| GHC.Types.False))))
     |   ` pure GHC.Types.[]
     ` eof
index 3ff8908f20ef819a6c14f1f0d36cacf1cb40a30a..adf4516a242c59587093a51ec429c65d738311fb 100644 (file)
@@ -11,7 +11,7 @@ lets
 |   |     + <*>
 |   |     | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
 |   |     | ` pure (\x_0 -> \x_1 -> x_0)
-|   |     ` satisfy
+|   |     ` satisfy (\c_0 -> GHC.Classes.not (('<' GHC.Classes.== c_0) GHC.Classes.|| (('>' GHC.Classes.== c_0) GHC.Classes.|| (('+' GHC.Classes.== c_0) GHC.Classes.|| (('-' GHC.Classes.== c_0) GHC.Classes.|| ((',' GHC.Classes.== c_0) GHC.Classes.|| (('.' GHC.Classes.== c_0) GHC.Classes.|| (('[' GHC.Classes.== c_0) GHC.Classes.|| ((']' GHC.Classes.== c_0) GHC.Classes.|| GHC.Types.False)))))))))
 |   ` pure GHC.Tuple.()
 + let <hidden>
 | ` chainPre
@@ -21,61 +21,69 @@ lets
 |   |   + <*>
 |   |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |   | ` conditional
-|   |   |   + look
-|   |   |   | ` satisfy
-|   |   |   + branches
-|   |   |   | + <*>
-|   |   |   | | + <*>
-|   |   |   | | | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   | | | ` pure Parsers.Brainfuck.Types.Backward
-|   |   |   | | ` satisfy
-|   |   |   | + <*>
-|   |   |   | | + <*>
-|   |   |   | | | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   | | | ` pure Parsers.Brainfuck.Types.Forward
-|   |   |   | | ` satisfy
-|   |   |   | + <*>
-|   |   |   | | + <*>
-|   |   |   | | | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   | | | ` pure Parsers.Brainfuck.Types.Increment
-|   |   |   | | ` satisfy
-|   |   |   | + <*>
-|   |   |   | | + <*>
-|   |   |   | | | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   | | | ` pure Parsers.Brainfuck.Types.Decrement
-|   |   |   | | ` satisfy
-|   |   |   | + <*>
-|   |   |   | | + <*>
-|   |   |   | | | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   | | | ` pure Parsers.Brainfuck.Types.Input
-|   |   |   | | ` satisfy
-|   |   |   | + <*>
-|   |   |   | | + <*>
-|   |   |   | | | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   | | | ` pure Parsers.Brainfuck.Types.Output
-|   |   |   | | ` satisfy
+|   |   |   + condition
+|   |   |   | ` look
+|   |   |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   |   |   + default
+|   |   |   | ` failure
+|   |   |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '<' x_0)
 |   |   |   | ` <*>
 |   |   |   |   + <*>
 |   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   |   | ` <*>
-|   |   |   |   |   + <*>
-|   |   |   |   |   | + <*>
-|   |   |   |   |   | | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   |   |   | | ` pure (\x_0 -> x_0)
-|   |   |   |   |   | ` <*>
-|   |   |   |   |   |   + <*>
-|   |   |   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   |   |   |   | ` satisfy
-|   |   |   |   |   |   ` ref <hidden>
-|   |   |   |   |   ` <*>
-|   |   |   |   |     + pure Parsers.Brainfuck.Types.Loop
-|   |   |   |   |     ` rec <hidden>
-|   |   |   |   ` <*>
-|   |   |   |     + <*>
-|   |   |   |     | + pure (\x_0 -> \x_1 -> x_0)
-|   |   |   |     | ` pure ']'
-|   |   |   |     ` satisfy
-|   |   |   ` failure
+|   |   |   |   | ` pure Parsers.Brainfuck.Types.Backward
+|   |   |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   |   |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '>' x_0)
+|   |   |   | ` <*>
+|   |   |   |   + <*>
+|   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
+|   |   |   |   | ` pure Parsers.Brainfuck.Types.Forward
+|   |   |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   |   |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '+' x_0)
+|   |   |   | ` <*>
+|   |   |   |   + <*>
+|   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
+|   |   |   |   | ` pure Parsers.Brainfuck.Types.Increment
+|   |   |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   |   |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '-' x_0)
+|   |   |   | ` <*>
+|   |   |   |   + <*>
+|   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
+|   |   |   |   | ` pure Parsers.Brainfuck.Types.Decrement
+|   |   |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   |   |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) ',' x_0)
+|   |   |   | ` <*>
+|   |   |   |   + <*>
+|   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
+|   |   |   |   | ` pure Parsers.Brainfuck.Types.Input
+|   |   |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   |   |   + branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '.' x_0)
+|   |   |   | ` <*>
+|   |   |   |   + <*>
+|   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
+|   |   |   |   | ` pure Parsers.Brainfuck.Types.Output
+|   |   |   |   ` satisfy (\x_0 -> GHC.Types.True)
+|   |   |   ` branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '[' x_0)
+|   |   |     ` <*>
+|   |   |       + <*>
+|   |   |       | + pure (\x_0 -> \x_1 -> x_0)
+|   |   |       | ` <*>
+|   |   |       |   + <*>
+|   |   |       |   | + <*>
+|   |   |       |   | | + pure (\x_0 -> \x_1 -> x_0)
+|   |   |       |   | | ` pure (\x_0 -> x_0)
+|   |   |       |   | ` <*>
+|   |   |       |   |   + <*>
+|   |   |       |   |   | + pure (\x_0 -> \x_1 -> x_0)
+|   |   |       |   |   | ` satisfy (\x_0 -> GHC.Types.True)
+|   |   |       |   |   ` ref <hidden>
+|   |   |       |   ` <*>
+|   |   |       |     + pure Parsers.Brainfuck.Types.Loop
+|   |   |       |     ` rec <hidden>
+|   |   |       ` <*>
+|   |   |         + <*>
+|   |   |         | + pure (\x_0 -> \x_1 -> x_0)
+|   |   |         | ` pure ']'
+|   |   |         ` satisfy ((GHC.Classes.==) ']')
 |   |   ` ref <hidden>
 |   ` pure GHC.Types.[]
 ` <*>
index 73f1996a3c17c23660b409707b043718f9ceb93f..8226cc064f3c870fd6f4cc77dc425b0e86c45741 100644 (file)
@@ -49,7 +49,7 @@ lets
 |     |       |   |   + <*>
 |     |       |   |   | + pure (\x_0 -> \x_1 -> x_0)
 |     |       |   |   | ` pure '!'
-|     |       |   |   ` satisfy
+|     |       |   |   ` satisfy ((GHC.Classes.==) '!')
 |     |       |   ` ref <hidden>
 |     |       ` ref <hidden>
 |     ` ref <hidden>
@@ -69,7 +69,7 @@ lets
 |   |   |   |   + <*>
 |   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |   |   |   | ` pure '['
-|   |   |   |   ` satisfy
+|   |   |   |   ` satisfy ((GHC.Classes.==) '[')
 |   |   |   ` ref <hidden>
 |   |   ` <*>
 |   |     + <*>
@@ -97,7 +97,7 @@ lets
 |     |   + <*>
 |     |   | + pure (\x_0 -> \x_1 -> x_0)
 |     |   | ` pure ']'
-|     |   ` satisfy
+|     |   ` satisfy ((GHC.Classes.==) ']')
 |     ` ref <hidden>
 + let <hidden>
 | ` <*>
@@ -115,7 +115,7 @@ lets
 |   |   |   |   + <*>
 |   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |   |   |   | ` pure '{'
-|   |   |   |   ` satisfy
+|   |   |   |   ` satisfy ((GHC.Classes.==) '{')
 |   |   |   ` ref <hidden>
 |   |   ` <*>
 |   |     + <*>
@@ -144,7 +144,7 @@ lets
 |   |     |       | | | |     |   + <*>
 |   |     |       | | | |     |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       | | | |     |   | ` pure 'i'
-|   |     |       | | | |     |   ` satisfy
+|   |     |       | | | |     |   ` satisfy ((GHC.Classes.==) 'i')
 |   |     |       | | | |     ` <*>
 |   |     |       | | | |       + <*>
 |   |     |       | | | |       | + pure (GHC.Types.:)
@@ -152,7 +152,7 @@ lets
 |   |     |       | | | |       |   + <*>
 |   |     |       | | | |       |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       | | | |       |   | ` pure 'f'
-|   |     |       | | | |       |   ` satisfy
+|   |     |       | | | |       |   ` satisfy ((GHC.Classes.==) 'f')
 |   |     |       | | | |       ` pure GHC.Types.[]
 |   |     |       | | | ` ref <hidden>
 |   |     |       | | ` <*>
@@ -178,7 +178,7 @@ lets
 |   |     |       | |   |   |   |     |   + <*>
 |   |     |       | |   |   |   |     |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       | |   |   |   |     |   | ` pure 'w'
-|   |     |       | |   |   |   |     |   ` satisfy
+|   |     |       | |   |   |   |     |   ` satisfy ((GHC.Classes.==) 'w')
 |   |     |       | |   |   |   |     ` <*>
 |   |     |       | |   |   |   |       + <*>
 |   |     |       | |   |   |   |       | + pure (GHC.Types.:)
@@ -186,7 +186,7 @@ lets
 |   |     |       | |   |   |   |       |   + <*>
 |   |     |       | |   |   |   |       |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       | |   |   |   |       |   | ` pure 'h'
-|   |     |       | |   |   |   |       |   ` satisfy
+|   |     |       | |   |   |   |       |   ` satisfy ((GHC.Classes.==) 'h')
 |   |     |       | |   |   |   |       ` <*>
 |   |     |       | |   |   |   |         + <*>
 |   |     |       | |   |   |   |         | + pure (GHC.Types.:)
@@ -194,7 +194,7 @@ lets
 |   |     |       | |   |   |   |         |   + <*>
 |   |     |       | |   |   |   |         |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       | |   |   |   |         |   | ` pure 'i'
-|   |     |       | |   |   |   |         |   ` satisfy
+|   |     |       | |   |   |   |         |   ` satisfy ((GHC.Classes.==) 'i')
 |   |     |       | |   |   |   |         ` <*>
 |   |     |       | |   |   |   |           + <*>
 |   |     |       | |   |   |   |           | + pure (GHC.Types.:)
@@ -202,7 +202,7 @@ lets
 |   |     |       | |   |   |   |           |   + <*>
 |   |     |       | |   |   |   |           |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       | |   |   |   |           |   | ` pure 'l'
-|   |     |       | |   |   |   |           |   ` satisfy
+|   |     |       | |   |   |   |           |   ` satisfy ((GHC.Classes.==) 'l')
 |   |     |       | |   |   |   |           ` <*>
 |   |     |       | |   |   |   |             + <*>
 |   |     |       | |   |   |   |             | + pure (GHC.Types.:)
@@ -210,7 +210,7 @@ lets
 |   |     |       | |   |   |   |             |   + <*>
 |   |     |       | |   |   |   |             |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       | |   |   |   |             |   | ` pure 'e'
-|   |     |       | |   |   |   |             |   ` satisfy
+|   |     |       | |   |   |   |             |   ` satisfy ((GHC.Classes.==) 'e')
 |   |     |       | |   |   |   |             ` pure GHC.Types.[]
 |   |     |       | |   |   |   ` ref <hidden>
 |   |     |       | |   |   ` ref <hidden>
@@ -252,7 +252,7 @@ lets
 |   |     |       |     |   |   |   |   |   |     |   + <*>
 |   |     |       |     |   |   |   |   |   |     |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       |     |   |   |   |   |   |     |   | ` pure 'v'
-|   |     |       |     |   |   |   |   |   |     |   ` satisfy
+|   |     |       |     |   |   |   |   |   |     |   ` satisfy ((GHC.Classes.==) 'v')
 |   |     |       |     |   |   |   |   |   |     ` <*>
 |   |     |       |     |   |   |   |   |   |       + <*>
 |   |     |       |     |   |   |   |   |   |       | + pure (GHC.Types.:)
@@ -260,7 +260,7 @@ lets
 |   |     |       |     |   |   |   |   |   |       |   + <*>
 |   |     |       |     |   |   |   |   |   |       |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       |     |   |   |   |   |   |       |   | ` pure 'a'
-|   |     |       |     |   |   |   |   |   |       |   ` satisfy
+|   |     |       |     |   |   |   |   |   |       |   ` satisfy ((GHC.Classes.==) 'a')
 |   |     |       |     |   |   |   |   |   |       ` <*>
 |   |     |       |     |   |   |   |   |   |         + <*>
 |   |     |       |     |   |   |   |   |   |         | + pure (GHC.Types.:)
@@ -268,7 +268,7 @@ lets
 |   |     |       |     |   |   |   |   |   |         |   + <*>
 |   |     |       |     |   |   |   |   |   |         |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       |     |   |   |   |   |   |         |   | ` pure 'r'
-|   |     |       |     |   |   |   |   |   |         |   ` satisfy
+|   |     |       |     |   |   |   |   |   |         |   ` satisfy ((GHC.Classes.==) 'r')
 |   |     |       |     |   |   |   |   |   |         ` pure GHC.Types.[]
 |   |     |       |     |   |   |   |   |   ` ref <hidden>
 |   |     |       |     |   |   |   |   ` ref <hidden>
@@ -302,7 +302,7 @@ lets
 |   |     |       |     |   |     |   + <*>
 |   |     |       |     |   |     |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |       |     |   |     |   | ` pure '='
-|   |     |       |     |   |     |   ` satisfy
+|   |     |       |     |   |     |   ` satisfy ((GHC.Classes.==) '=')
 |   |     |       |     |   |     ` ref <hidden>
 |   |     |       |     |   ` <*>
 |   |     |       |     |     + <*>
@@ -341,7 +341,7 @@ lets
 |     |   + <*>
 |     |   | + pure (\x_0 -> \x_1 -> x_0)
 |     |   | ` pure '}'
-|     |   ` satisfy
+|     |   ` satisfy ((GHC.Classes.==) '}')
 |     ` ref <hidden>
 + let <hidden>
 | ` <*>
@@ -363,7 +363,7 @@ lets
 |   | + <*>
 |   | | + pure (\x_0 -> \x_1 -> x_0)
 |   | | ` pure (\x_0 -> x_0)
-|   | ` satisfy
+|   | ` satisfy GHC.Unicode.isSpace
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
@@ -377,7 +377,7 @@ lets
 |   |     | + <*>
 |   |     | | + pure (\x_0 -> \x_1 -> x_0)
 |   |     | | ` pure (\x_0 -> x_0)
-|   |     | ` satisfy
+|   |     | ` satisfy Parsers.Nandlang.nandIdentStart
 |   |     ` <*>
 |   |       + <*>
 |   |       | + <*>
@@ -389,7 +389,7 @@ lets
 |   |       |     + <*>
 |   |       |     | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
 |   |       |     | ` pure (\x_0 -> \x_1 -> x_0)
-|   |       |     ` satisfy
+|   |       |     ` satisfy Parsers.Nandlang.nandIdentLetter
 |   |       ` ref <hidden>
 |   ` ref <hidden>
 + let <hidden>
@@ -400,7 +400,7 @@ lets
 |   |   + <*>
 |   |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |   | ` pure '('
-|   |   ` satisfy
+|   |   ` satisfy ((GHC.Classes.==) '(')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
@@ -410,7 +410,7 @@ lets
 |   |   + <*>
 |   |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |   | ` pure ')'
-|   |   ` satisfy
+|   |   ` satisfy ((GHC.Classes.==) ')')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
@@ -420,7 +420,7 @@ lets
 |   |   + <*>
 |   |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |   | ` pure ','
-|   |   ` satisfy
+|   |   ` satisfy ((GHC.Classes.==) ',')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
@@ -430,7 +430,7 @@ lets
 |   |   + <*>
 |   |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |   | ` pure ';'
-|   |   ` satisfy
+|   |   ` satisfy ((GHC.Classes.==) ';')
 |   ` ref <hidden>
 + let <hidden>
 | ` <*>
@@ -479,12 +479,12 @@ lets
 |   | | |   | + <*>
 |   | | |   | | + pure (\x_0 -> \x_1 -> x_0)
 |   | | |   | | ` pure '0'
-|   | | |   | ` satisfy
+|   | | |   | ` satisfy ((GHC.Classes.==) '0')
 |   | | |   ` <*>
 |   | | |     + <*>
 |   | | |     | + pure (\x_0 -> \x_1 -> x_0)
 |   | | |     | ` pure '1'
-|   | | |     ` satisfy
+|   | | |     ` satisfy ((GHC.Classes.==) '1')
 |   | | ` ref <hidden>
 |   | ` <*>
 |   |   + <*>
@@ -498,14 +498,14 @@ lets
 |   |   |   |   + <*>
 |   |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |   |   |   | ` pure '\''
-|   |   |   |   ` satisfy
+|   |   |   |   ` satisfy ((GHC.Classes.==) '\'')
 |   |   |   ` <|>
 |   |   |     + <*>
 |   |   |     | + <*>
 |   |   |     | | + <*>
 |   |   |     | | | + pure (\x_0 -> \x_1 -> x_0)
 |   |   |     | | | ` pure (\x_0 -> x_0)
-|   |   |     | | ` satisfy
+|   |   |     | | ` satisfy Parsers.Nandlang.nandStringLetter
 |   |   |     | ` ref <hidden>
 |   |   |     ` <*>
 |   |   |       + <*>
@@ -516,13 +516,13 @@ lets
 |   |   |       |   + <*>
 |   |   |       |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |   |       |   | ` pure '\\'
-|   |   |       |   ` satisfy
+|   |   |       |   ` satisfy ((GHC.Classes.==) '\\')
 |   |   |       ` <*>
 |   |   |         + <*>
 |   |   |         | + <*>
 |   |   |         | | + pure (\x_0 -> \x_1 -> x_0)
 |   |   |         | | ` pure (\x_0 -> x_0)
-|   |   |         | ` satisfy
+|   |   |         | ` satisfy (\t_0 -> ('0' GHC.Classes.== t_0) GHC.Classes.|| (('t' GHC.Classes.== t_0) GHC.Classes.|| (('n' GHC.Classes.== t_0) GHC.Classes.|| (('v' GHC.Classes.== t_0) GHC.Classes.|| (('f' GHC.Classes.== t_0) GHC.Classes.|| (('r' GHC.Classes.== t_0) GHC.Classes.|| GHC.Types.False))))))
 |   |   |         ` ref <hidden>
 |   |   ` <*>
 |   |     + <*>
@@ -531,7 +531,7 @@ lets
 |   |     |   + <*>
 |   |     |   | + pure (\x_0 -> \x_1 -> x_0)
 |   |     |   | ` pure '\''
-|   |     |   ` satisfy
+|   |     |   ` satisfy ((GHC.Classes.==) '\'')
 |   |     ` ref <hidden>
 |   ` <*>
 |     + <*>
@@ -591,7 +591,7 @@ lets
 + let <hidden>
 | ` pure GHC.Tuple.()
 + let <hidden>
-| ` satisfy
+| ` satisfy (\t_0 -> ('0' GHC.Classes.== t_0) GHC.Classes.|| (('1' GHC.Classes.== t_0) GHC.Classes.|| (('2' GHC.Classes.== t_0) GHC.Classes.|| (('3' GHC.Classes.== t_0) GHC.Classes.|| (('4' GHC.Classes.== t_0) GHC.Classes.|| (('5' GHC.Classes.== t_0) GHC.Classes.|| (('6' GHC.Classes.== t_0) GHC.Classes.|| (('7' GHC.Classes.== t_0) GHC.Classes.|| (('8' GHC.Classes.== t_0) GHC.Classes.|| (('9' GHC.Classes.== t_0) GHC.Classes.|| GHC.Types.False))))))))))
 ` <*>
   + pure GHC.Show.show
   ` <*>
@@ -642,7 +642,7 @@ lets
     |     |       |   |   |   |     |   + <*>
     |     |       |   |   |   |     |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |       |   |   |   |     |   | ` pure 'f'
-    |     |       |   |   |   |     |   ` satisfy
+    |     |       |   |   |   |     |   ` satisfy ((GHC.Classes.==) 'f')
     |     |       |   |   |   |     ` <*>
     |     |       |   |   |   |       + <*>
     |     |       |   |   |   |       | + pure (GHC.Types.:)
@@ -650,7 +650,7 @@ lets
     |     |       |   |   |   |       |   + <*>
     |     |       |   |   |   |       |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |       |   |   |   |       |   | ` pure 'u'
-    |     |       |   |   |   |       |   ` satisfy
+    |     |       |   |   |   |       |   ` satisfy ((GHC.Classes.==) 'u')
     |     |       |   |   |   |       ` <*>
     |     |       |   |   |   |         + <*>
     |     |       |   |   |   |         | + pure (GHC.Types.:)
@@ -658,7 +658,7 @@ lets
     |     |       |   |   |   |         |   + <*>
     |     |       |   |   |   |         |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |       |   |   |   |         |   | ` pure 'n'
-    |     |       |   |   |   |         |   ` satisfy
+    |     |       |   |   |   |         |   ` satisfy ((GHC.Classes.==) 'n')
     |     |       |   |   |   |         ` <*>
     |     |       |   |   |   |           + <*>
     |     |       |   |   |   |           | + pure (GHC.Types.:)
@@ -666,7 +666,7 @@ lets
     |     |       |   |   |   |           |   + <*>
     |     |       |   |   |   |           |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |       |   |   |   |           |   | ` pure 'c'
-    |     |       |   |   |   |           |   ` satisfy
+    |     |       |   |   |   |           |   ` satisfy ((GHC.Classes.==) 'c')
     |     |       |   |   |   |           ` <*>
     |     |       |   |   |   |             + <*>
     |     |       |   |   |   |             | + pure (GHC.Types.:)
@@ -674,7 +674,7 @@ lets
     |     |       |   |   |   |             |   + <*>
     |     |       |   |   |   |             |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |       |   |   |   |             |   | ` pure 't'
-    |     |       |   |   |   |             |   ` satisfy
+    |     |       |   |   |   |             |   ` satisfy ((GHC.Classes.==) 't')
     |     |       |   |   |   |             ` <*>
     |     |       |   |   |   |               + <*>
     |     |       |   |   |   |               | + pure (GHC.Types.:)
@@ -682,7 +682,7 @@ lets
     |     |       |   |   |   |               |   + <*>
     |     |       |   |   |   |               |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |       |   |   |   |               |   | ` pure 'i'
-    |     |       |   |   |   |               |   ` satisfy
+    |     |       |   |   |   |               |   ` satisfy ((GHC.Classes.==) 'i')
     |     |       |   |   |   |               ` <*>
     |     |       |   |   |   |                 + <*>
     |     |       |   |   |   |                 | + pure (GHC.Types.:)
@@ -690,7 +690,7 @@ lets
     |     |       |   |   |   |                 |   + <*>
     |     |       |   |   |   |                 |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |       |   |   |   |                 |   | ` pure 'o'
-    |     |       |   |   |   |                 |   ` satisfy
+    |     |       |   |   |   |                 |   ` satisfy ((GHC.Classes.==) 'o')
     |     |       |   |   |   |                 ` <*>
     |     |       |   |   |   |                   + <*>
     |     |       |   |   |   |                   | + pure (GHC.Types.:)
@@ -698,7 +698,7 @@ lets
     |     |       |   |   |   |                   |   + <*>
     |     |       |   |   |   |                   |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |       |   |   |   |                   |   | ` pure 'n'
-    |     |       |   |   |   |                   |   ` satisfy
+    |     |       |   |   |   |                   |   ` satisfy ((GHC.Classes.==) 'n')
     |     |       |   |   |   |                   ` pure GHC.Types.[]
     |     |       |   |   |   ` ref <hidden>
     |     |       |   |   ` ref <hidden>
@@ -734,7 +734,7 @@ lets
     |     |       |     |       |   |   |   + <*>
     |     |       |     |       |   |   |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |       |     |       |   |   |   | ` pure ':'
-    |     |       |     |       |   |   |   ` satisfy
+    |     |       |     |       |   |   |   ` satisfy ((GHC.Classes.==) ':')
     |     |       |     |       |   |   ` ref <hidden>
     |     |       |     |       |   ` ref <hidden>
     |     |       |     |       ` ref <hidden>
index cb67016804b9dc3be2dadae431253b60d9ee047f..2591890ffd4280f41916ef7b5bc672a276f1ec94 100644 (file)
@@ -9,14 +9,14 @@ lets
     |   | + <*>
     |   | | + pure (\x_0 -> \x_1 -> x_0)
     |   | | ` pure 'a'
-    |   | ` satisfy
+    |   | ` satisfy ((GHC.Classes.==) 'a')
     |   ` <*>
     |     + <*>
     |     | + pure (\x_0 -> \x_1 -> x_0)
     |     | ` pure 'b'
-    |     ` satisfy
+    |     ` satisfy ((GHC.Classes.==) 'b')
     ` <*>
       + <*>
       | + pure (\x_0 -> \x_1 -> x_0)
       | ` pure 'c'
-      ` satisfy
+      ` satisfy ((GHC.Classes.==) 'c')
index 3fe822e2cf2e9610503a13661b60c2df1c76deba..12a3fa890fc21d5f5039442efc4b357cc0f7b498 100644 (file)
@@ -10,19 +10,19 @@ lets
     |   | | + <*>
     |   | | | + pure (\x_0 -> \x_1 -> x_0)
     |   | | | ` pure 'a'
-    |   | | ` satisfy
+    |   | | ` satisfy ((GHC.Classes.==) 'a')
     |   | ` <*>
     |   |   + <*>
     |   |   | + pure (\x_0 -> \x_1 -> x_0)
     |   |   | ` pure 'b'
-    |   |   ` satisfy
+    |   |   ` satisfy ((GHC.Classes.==) 'b')
     |   ` <*>
     |     + <*>
     |     | + pure (\x_0 -> \x_1 -> x_0)
     |     | ` pure 'c'
-    |     ` satisfy
+    |     ` satisfy ((GHC.Classes.==) 'c')
     ` <*>
       + <*>
       | + pure (\x_0 -> \x_1 -> x_0)
       | ` pure 'd'
-      ` satisfy
+      ` satisfy ((GHC.Classes.==) 'd')
index 7fe342d67d23199dcd3bca9c7972ae5f214d2a7e..bf57c64b3b3326541450aa48cf9e5d8efe4a3b21 100644 (file)
@@ -9,7 +9,7 @@ lets
       |   + <*>
       |   | + pure (\x_0 -> \x_1 -> x_0)
       |   | ` pure 'a'
-      |   ` satisfy
+      |   ` satisfy ((GHC.Classes.==) 'a')
       ` <*>
         + <*>
         | + pure (GHC.Types.:)
@@ -17,7 +17,7 @@ lets
         |   + <*>
         |   | + pure (\x_0 -> \x_1 -> x_0)
         |   | ` pure 'b'
-        |   ` satisfy
+        |   ` satisfy ((GHC.Classes.==) 'b')
         ` <*>
           + <*>
           | + pure (GHC.Types.:)
@@ -25,5 +25,5 @@ lets
           |   + <*>
           |   | + pure (\x_0 -> \x_1 -> x_0)
           |   | ` pure 'c'
-          |   ` satisfy
+          |   ` satisfy ((GHC.Classes.==) 'c')
           ` pure GHC.Types.[]
index 3325cc0c9387c17d60c8a0c894a2314e3b7b0a62..9400e67a8cc2889e1a42244ea89155f7e6e45d5b 100644 (file)
@@ -8,5 +8,5 @@ lets
     |   + <*>
     |   | + pure (\x_0 -> \x_1 -> x_0)
     |   | ` pure 'a'
-    |   ` satisfy
+    |   ` satisfy ((GHC.Classes.==) 'a')
     ` pure GHC.Types.[]
index dd0720390772c7253323204d61ab092b5b0766f0..a53f4ba63bdb179833efb04f77d7750f9807491f 100644 (file)
@@ -8,7 +8,7 @@ lets
 |     |   + <*>
 |     |   | + pure (\x_0 -> \x_1 -> x_0)
 |     |   | ` pure 'a'
-|     |   ` satisfy
+|     |   ` satisfy ((GHC.Classes.==) 'a')
 |     ` <*>
 |       + <*>
 |       | + pure (GHC.Types.:)
@@ -16,7 +16,7 @@ lets
 |       |   + <*>
 |       |   | + pure (\x_0 -> \x_1 -> x_0)
 |       |   | ` pure 'b'
-|       |   ` satisfy
+|       |   ` satisfy ((GHC.Classes.==) 'b')
 |       ` <*>
 |         + <*>
 |         | + pure (GHC.Types.:)
@@ -24,7 +24,7 @@ lets
 |         |   + <*>
 |         |   | + pure (\x_0 -> \x_1 -> x_0)
 |         |   | ` pure 'c'
-|         |   ` satisfy
+|         |   ` satisfy ((GHC.Classes.==) 'c')
 |         ` <*>
 |           + <*>
 |           | + pure (GHC.Types.:)
@@ -32,7 +32,7 @@ lets
 |           |   + <*>
 |           |   | + pure (\x_0 -> \x_1 -> x_0)
 |           |   | ` pure 'd'
-|           |   ` satisfy
+|           |   ` satisfy ((GHC.Classes.==) 'd')
 |           ` pure GHC.Types.[]
 ` <*>
   + pure GHC.Show.show
index 78335fa84ba0bbe0c90f44c208ac0043ad9984f1..f47ad234f8287a3f587c95d06d801704343f776a 100644 (file)
@@ -8,7 +8,7 @@ lets
 |     |   + <*>
 |     |   | + pure (\x_0 -> \x_1 -> x_0)
 |     |   | ` pure 'a'
-|     |   ` satisfy
+|     |   ` satisfy ((GHC.Classes.==) 'a')
 |     ` <*>
 |       + <*>
 |       | + pure (GHC.Types.:)
@@ -16,7 +16,7 @@ lets
 |       |   + <*>
 |       |   | + pure (\x_0 -> \x_1 -> x_0)
 |       |   | ` pure 'b'
-|       |   ` satisfy
+|       |   ` satisfy ((GHC.Classes.==) 'b')
 |       ` <*>
 |         + <*>
 |         | + pure (GHC.Types.:)
@@ -24,7 +24,7 @@ lets
 |         |   + <*>
 |         |   | + pure (\x_0 -> \x_1 -> x_0)
 |         |   | ` pure 'c'
-|         |   ` satisfy
+|         |   ` satisfy ((GHC.Classes.==) 'c')
 |         ` <*>
 |           + <*>
 |           | + pure (GHC.Types.:)
@@ -32,7 +32,7 @@ lets
 |           |   + <*>
 |           |   | + pure (\x_0 -> \x_1 -> x_0)
 |           |   | ` pure 'd'
-|           |   ` satisfy
+|           |   ` satisfy ((GHC.Classes.==) 'd')
 |           ` pure GHC.Types.[]
 ` <*>
   + pure GHC.Show.show
index 838eaa883f3d779b67d31024ed365d96248a2541..3f393342a574da10e2c86c403d4c98d0440f5a84 100644 (file)
@@ -9,7 +9,7 @@ lets
     | |   + <*>
     | |   | + pure (\x_0 -> \x_1 -> x_0)
     | |   | ` pure 'a'
-    | |   ` satisfy
+    | |   ` satisfy ((GHC.Classes.==) 'a')
     | ` <*>
     |   + <*>
     |   | + pure (GHC.Types.:)
@@ -17,7 +17,7 @@ lets
     |   |   + <*>
     |   |   | + pure (\x_0 -> \x_1 -> x_0)
     |   |   | ` pure 'a'
-    |   |   ` satisfy
+    |   |   ` satisfy ((GHC.Classes.==) 'a')
     |   ` pure GHC.Types.[]
     ` <*>
       + <*>
@@ -26,7 +26,7 @@ lets
       |   + <*>
       |   | + pure (\x_0 -> \x_1 -> x_0)
       |   | ` pure 'a'
-      |   ` satisfy
+      |   ` satisfy ((GHC.Classes.==) 'a')
       ` <*>
         + <*>
         | + pure (GHC.Types.:)
@@ -34,5 +34,5 @@ lets
         |   + <*>
         |   | + pure (\x_0 -> \x_1 -> x_0)
         |   | ` pure 'b'
-        |   ` satisfy
+        |   ` satisfy ((GHC.Classes.==) 'b')
         ` pure GHC.Types.[]
index 61c9fe46b6b1561dced26c3e315355722892213a..b3c56d1a5fe86e1ce39dbb788dbaaa11b80d3cc8 100644 (file)
@@ -10,7 +10,7 @@ lets
     |   |   + <*>
     |   |   | + pure (\x_0 -> \x_1 -> x_0)
     |   |   | ` pure 'a'
-    |   |   ` satisfy
+    |   |   ` satisfy ((GHC.Classes.==) 'a')
     |   ` <*>
     |     + <*>
     |     | + pure (GHC.Types.:)
@@ -18,7 +18,7 @@ lets
     |     |   + <*>
     |     |   | + pure (\x_0 -> \x_1 -> x_0)
     |     |   | ` pure 'a'
-    |     |   ` satisfy
+    |     |   ` satisfy ((GHC.Classes.==) 'a')
     |     ` pure GHC.Types.[]
     ` try
       ` <*>
@@ -28,7 +28,7 @@ lets
         |   + <*>
         |   | + pure (\x_0 -> \x_1 -> x_0)
         |   | ` pure 'a'
-        |   ` satisfy
+        |   ` satisfy ((GHC.Classes.==) 'a')
         ` <*>
           + <*>
           | + pure (GHC.Types.:)
@@ -36,5 +36,5 @@ lets
           |   + <*>
           |   | + pure (\x_0 -> \x_1 -> x_0)
           |   | ` pure 'b'
-          |   ` satisfy
+          |   ` satisfy ((GHC.Classes.==) 'b')
           ` pure GHC.Types.[]
index c4b92cd4e279585148213d12bccc45fb2cf8d06e..78a0cf6505fa0115b588136ec7f20551a85c5617 100644 (file)
@@ -11,6 +11,6 @@ lets
     |   |   + <*>
     |   |   | + pure (\x_0 -> \x_1 -> x_0)
     |   |   | ` pure 'r'
-    |   |   ` satisfy
+    |   |   ` satisfy ((GHC.Classes.==) 'r')
     |   ` pure GHC.Types.[]
     ` eof
index 05d03a81c0f5977ecb0c36815bd6fa9210a0f0aa..09ae8002b7f129b7bbba7cafa6b1114e0833a08c 100644 (file)
@@ -12,32 +12,32 @@ iter <hidden>
   mayRaise=[ExceptionFailure]
 | <ok>
 | | pushValue (\x_0 -> (GHC.Types.:) 'a')
-| |   minReads=(Right 3)
+| |   minReads=(Right 1)
 | |   mayRaise=[ExceptionFailure]
 | | read ((GHC.Classes.==) 'a')
-| |   minReads=(Right 3)
+| |   minReads=(Right 1)
 | |   mayRaise=[ExceptionFailure]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
-| | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> \x_5 -> x_3 (x_4 x_5)))
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
-| | lift2Value ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | pushValue (\x_0 -> \x_1 -> \x_2 -> x_1 (x_0 x_2))
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | lift2Value (\x_0 -> \x_1 -> x_1 x_0)
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | readRegister <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | writeRegister <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | jump <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | <ko>
 | | pushInput
 | |   minReads=(Right 1)
index 70b2272fdadc7e67addf47743de85d3bebc4dff9..c380d73b3482fe5b71138a5393f9019c3a69ca61 100644 (file)
@@ -12,32 +12,32 @@ iter <hidden>
   mayRaise=[ExceptionFailure]
 | <ok>
 | | pushValue (GHC.Types.:)
-| |   minReads=(Right 3)
+| |   minReads=(Right 1)
 | |   mayRaise=[ExceptionFailure]
 | | read (\t_0 -> ('a' GHC.Classes.== t_0) GHC.Classes.|| (('b' GHC.Classes.== t_0) GHC.Classes.|| (('c' GHC.Classes.== t_0) GHC.Classes.|| (('d' GHC.Classes.== t_0) GHC.Classes.|| GHC.Types.False))))
-| |   minReads=(Right 3)
+| |   minReads=(Right 1)
 | |   mayRaise=[ExceptionFailure]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
-| | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> \x_5 -> x_3 (x_4 x_5)))
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
-| | lift2Value ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | pushValue (\x_0 -> \x_1 -> \x_2 -> x_1 (x_0 x_2))
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | lift2Value (\x_0 -> \x_1 -> x_1 x_0)
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | readRegister <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | writeRegister <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | jump <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | <ko>
 | | pushInput
 | |   minReads=(Right 0)
@@ -83,7 +83,7 @@ iter <hidden>
 | | | | | | | | pushInput
 | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | |   mayRaise=[ExceptionFailure]
-| | | | | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | | | | read (\x_0 -> GHC.Types.True)
 | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | popValue
index 7feb2e2c7878e4322717be80bb3a35ccb5efeb06..9d0b4c0ec145571189a56ac9529c04c99a945013 100644 (file)
@@ -15,26 +15,26 @@ let <hidden>
 |   mayRaise=[ExceptionFailure]
 | | <ok>
 | | | pushValue (\x_0 -> \x_1 -> x_1)
-| | |   minReads=(Right 3)
+| | |   minReads=(Right 1)
 | | |   mayRaise=[ExceptionFailure]
 | | | read (\c_0 -> GHC.Classes.not (('<' GHC.Classes.== c_0) GHC.Classes.|| (('>' GHC.Classes.== c_0) GHC.Classes.|| (('+' GHC.Classes.== c_0) GHC.Classes.|| (('-' GHC.Classes.== c_0) GHC.Classes.|| ((',' GHC.Classes.== c_0) GHC.Classes.|| (('.' GHC.Classes.== c_0) GHC.Classes.|| (('[' GHC.Classes.== c_0) GHC.Classes.|| ((']' GHC.Classes.== c_0) GHC.Classes.|| GHC.Types.False)))))))))
-| | |   minReads=(Right 3)
+| | |   minReads=(Right 1)
 | | |   mayRaise=[ExceptionFailure]
 | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | readRegister <hidden>
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | writeRegister <hidden>
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | jump <hidden>
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | <ko>
 | | | pushInput
 | | |   minReads=(Right 0)
@@ -84,35 +84,35 @@ let <hidden>
 | | |   minReads=(Right 1)
 | | |   mayRaise=[ExceptionFailure]
 | | | join <hidden>
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 0)
 | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 1)
+| | | |   minReads=(Right 0)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | call <hidden>
-| | | |   minReads=(Right 1)
+| | | |   minReads=(Right 0)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 1)
-| | | |   mayRaise=[ExceptionFailure]
-| | | | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> \x_5 -> x_3 (x_4 x_5)))
-| | | |   minReads=(Right 1)
-| | | |   mayRaise=[ExceptionFailure]
-| | | | lift2Value ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | |   minReads=(Right 1)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
+| | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_1 (x_0 x_2))
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
+| | | | lift2Value (\x_0 -> \x_1 -> x_1 x_0)
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | | readRegister <hidden>
-| | | |   minReads=(Right 1)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 1)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | | writeRegister <hidden>
-| | | |   minReads=(Right 1)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | | jump <hidden>
-| | | |   minReads=(Right 1)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | pushInput
 | | |   minReads=(Right 1)
 | | |   mayRaise=[ExceptionFailure]
@@ -137,10 +137,10 @@ let <hidden>
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | refJoin <hidden>
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | <branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '>' x_0)>
 | | | | | pushValue (\x_0 -> Parsers.Brainfuck.Types.Forward)
 | | | | |   minReads=(Right 1)
@@ -150,10 +150,10 @@ let <hidden>
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | refJoin <hidden>
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | <branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '+' x_0)>
 | | | | | pushValue (\x_0 -> Parsers.Brainfuck.Types.Increment)
 | | | | |   minReads=(Right 1)
@@ -163,10 +163,10 @@ let <hidden>
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | refJoin <hidden>
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | <branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '-' x_0)>
 | | | | | pushValue (\x_0 -> Parsers.Brainfuck.Types.Decrement)
 | | | | |   minReads=(Right 1)
@@ -176,10 +176,10 @@ let <hidden>
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | refJoin <hidden>
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | <branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) ',' x_0)>
 | | | | | pushValue (\x_0 -> Parsers.Brainfuck.Types.Input)
 | | | | |   minReads=(Right 1)
@@ -189,10 +189,10 @@ let <hidden>
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | refJoin <hidden>
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | <branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '.' x_0)>
 | | | | | pushValue (\x_0 -> Parsers.Brainfuck.Types.Output)
 | | | | |   minReads=(Right 1)
@@ -202,29 +202,29 @@ let <hidden>
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | refJoin <hidden>
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | <branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '[' x_0)>
 | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> Parsers.Brainfuck.Types.Loop x_2)
-| | | | |   minReads=(Right 2)
+| | | | |   minReads=(Right 1)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | read (\x_0 -> GHC.Types.True)
-| | | | |   minReads=(Right 2)
+| | | | |   minReads=(Right 1)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 0)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | call <hidden>
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 0)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 1)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | call <hidden>
-| | | | |   minReads=(Right 1)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 1)
 | | | | |   mayRaise=[ExceptionFailure]
@@ -233,10 +233,10 @@ let <hidden>
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | refJoin <hidden>
 | | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | <default>
 | | | | | fail [FailureEmpty]
 | | | | |   minReads=(Left ExceptionFailure)
index 4e5938ce1032df9c65407b406a5d0cd80b616070..e409bfe0826405720a3a563da2da375900ea1e3c 100644 (file)
@@ -25,10 +25,16 @@ let <hidden>
 | | |   mayRaise=[ExceptionFailure]
 | | | | <ok>
 | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
-| | | | |   minReads=(Right 2)
+| | | | |   minReads=(Right 4)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | call <hidden>
-| | | | |   minReads=(Right 2)
+| | | | |   minReads=(Right 4)
+| | | | |   mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | |   minReads=(Right 4)
+| | | | |   mayRaise=[ExceptionFailure]
+| | | | | call <hidden>
+| | | | |   minReads=(Right 4)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 2)
@@ -39,24 +45,18 @@ let <hidden>
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
 | | | | |   mayRaise=[]
-| | | | | call <hidden>
+| | | | | readRegister <hidden>
 | | | | |   minReads=(Right 0)
 | | | | |   mayRaise=[]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 8)
-| | | | |   mayRaise=[ExceptionFailure]
-| | | | | readRegister <hidden>
-| | | | |   minReads=(Right 8)
-| | | | |   mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 8)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | writeRegister <hidden>
-| | | | |   minReads=(Right 8)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | jump <hidden>
-| | | | |   minReads=(Right 8)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | <ko>
 | | | | | pushInput
 | | | | |   minReads=(Right 0)
@@ -168,26 +168,26 @@ let <hidden>
 |   mayRaise=[ExceptionFailure]
 | | <ok>
 | | | pushValue (\x_0 -> \x_1 -> x_1)
-| | |   minReads=(Right 0)
-| | |   mayRaise=[]
+| | |   minReads=(Right 1)
+| | |   mayRaise=[ExceptionFailure]
 | | | call <hidden>
+| | |   minReads=(Right 1)
+| | |   mayRaise=[ExceptionFailure]
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | |   minReads=(Right 0)
 | | |   mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
 | | | readRegister <hidden>
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | writeRegister <hidden>
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | jump <hidden>
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | <ko>
 | | | pushInput
 | | |   minReads=(Right 0)
@@ -279,49 +279,49 @@ let <hidden>
 | | | |   minReads=(Right 0)
 | | | |   mayRaise=[]
 | | | catch ExceptionFailure
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 2)
 | | |   mayRaise=[ExceptionFailure]
 | | | | <ok>
 | | | | | pushValue (\x_0 -> '0')
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | read ((GHC.Classes.==) '0')
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 1)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | commit ExceptionFailure
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 1)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | refJoin <hidden>
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 1)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | <ko>
 | | | | | pushInput
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | | | |                                                                j_1
 | | | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | choicesBranch
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | <branch (\x_0 -> x_0)>
 | | | | | | | pushValue (\x_0 -> '1')
-| | | | | | |   minReads=(Right 1)
+| | | | | | |   minReads=(Right 2)
 | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | read ((GHC.Classes.==) '1')
-| | | | | | |   minReads=(Right 1)
+| | | | | | |   minReads=(Right 2)
 | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | |   minReads=(Right 0)
-| | | | | | |   mayRaise=[]
+| | | | | | |   minReads=(Right 1)
+| | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | refJoin <hidden>
-| | | | | | |   minReads=(Right 0)
-| | | | | | |   mayRaise=[]
+| | | | | | |   minReads=(Right 1)
+| | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | <default>
 | | | | | | | fail []
 | | | | | | |   minReads=(Left ExceptionFailure)
@@ -377,67 +377,67 @@ let <hidden>
 | | | | | | | |   minReads=(Right 0)
 | | | | | | | |   mayRaise=[]
 | | | | | | | catch ExceptionFailure
-| | | | | | |   minReads=(Right 1)
+| | | | | | |   minReads=(Right 3)
 | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | <ok>
 | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_1)
-| | | | | | | | |   minReads=(Right 1)
+| | | | | | | | |   minReads=(Right 3)
 | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | read Parsers.Nandlang.nandStringLetter
-| | | | | | | | |   minReads=(Right 1)
+| | | | | | | | |   minReads=(Right 3)
 | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | |   minReads=(Right 0)
-| | | | | | | | |   mayRaise=[]
+| | | | | | | | |   minReads=(Right 2)
+| | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | call <hidden>
-| | | | | | | | |   minReads=(Right 0)
-| | | | | | | | |   mayRaise=[]
+| | | | | | | | |   minReads=(Right 2)
+| | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | |   minReads=(Right 0)
-| | | | | | | | |   mayRaise=[]
+| | | | | | | | |   minReads=(Right 2)
+| | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | commit ExceptionFailure
-| | | | | | | | |   minReads=(Right 0)
-| | | | | | | | |   mayRaise=[]
+| | | | | | | | |   minReads=(Right 2)
+| | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | refJoin <hidden>
-| | | | | | | | |   minReads=(Right 0)
-| | | | | | | | |   mayRaise=[]
+| | | | | | | | |   minReads=(Right 2)
+| | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | <ko>
 | | | | | | | | | pushInput
-| | | | | | | | |   minReads=(Right 2)
+| | | | | | | | |   minReads=(Right 4)
 | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | | | | | | | |                                                                j_1
 | | | | | | | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | | |   minReads=(Right 2)
+| | | | | | | | |   minReads=(Right 4)
 | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | choicesBranch
-| | | | | | | | |   minReads=(Right 2)
+| | | | | | | | |   minReads=(Right 4)
 | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | <branch (\x_0 -> x_0)>
 | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_2)
-| | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | read ((GHC.Classes.==) '\\')
-| | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | |   minReads=(Right 3)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | read (\t_0 -> ('0' GHC.Classes.== t_0) GHC.Classes.|| (('t' GHC.Classes.== t_0) GHC.Classes.|| (('n' GHC.Classes.== t_0) GHC.Classes.|| (('v' GHC.Classes.== t_0) GHC.Classes.|| (('f' GHC.Classes.== t_0) GHC.Classes.|| (('r' GHC.Classes.== t_0) GHC.Classes.|| GHC.Types.False))))))
-| | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | |   minReads=(Right 3)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | call <hidden>
-| | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | <default>
 | | | | | | | | | | | fail []
 | | | | | | | | | | |   minReads=(Left ExceptionFailure)
@@ -478,7 +478,7 @@ let <hidden>
 | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | <ok>
 | | | | | | | | | | | pushValue (\x_0 -> GHC.Tuple.())
-| | | | | | | | | | |   minReads=(Right 4)
+| | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | join <hidden>
 | | | | | | | | | | |   minReads=(Right 0)
@@ -493,17 +493,17 @@ let <hidden>
 | | | | | | | | | | | |   minReads=(Right 0)
 | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | catch ExceptionFailure
-| | | | | | | | | | |   minReads=(Right 4)
+| | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | <ok>
 | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_1)
-| | | | | | | | | | | | |   minReads=(Right 4)
+| | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | |   minReads=(Right 4)
+| | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | |   minReads=(Right 0)
 | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | join <hidden>
 | | | | | | | | | | | | |   minReads=(Right 2)
@@ -528,22 +528,22 @@ let <hidden>
 | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | <ok>
 | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
-| | | | | | | | | | | | | | |   minReads=(Right 2)
-| | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | |   minReads=(Right 2)
-| | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | newRegister <hidden>
-| | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | iter <hidden>
-| | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | <ok>
 | | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
@@ -565,80 +565,80 @@ let <hidden>
 | | | | | | | | | | | | | | | | |   minReads=(Right 0)
 | | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | readRegister <hidden>
-| | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | writeRegister <hidden>
-| | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | jump <hidden>
-| | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | <ko>
 | | | | | | | | | | | | | | | | | pushInput
-| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | | | | | | | | | | | | | | | |                                                                j_1
 | | | | | | | | | | | | | | | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | choicesBranch
-| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
 | | | | | | | | | | | | | | | | | | | readRegister <hidden>
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | <default>
 | | | | | | | | | | | | | | | | | | | fail []
 | | | | | | | | | | | | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | <ko>
 | | | | | | | | | | | | | | | pushInput
-| | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | | | | | | | | | | | | | |                                                                j_1
 | | | | | | | | | | | | | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | choicesBranch
-| | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
 | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | <default>
 | | | | | | | | | | | | | | | | | fail []
 | | | | | | | | | | | | | | | | |   minReads=(Left ExceptionFailure)
@@ -804,38 +804,38 @@ let <hidden>
 |   mayRaise=[ExceptionFailure]
 | | <ok>
 | | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
-| | |   minReads=(Right 2)
+| | |   minReads=(Right 4)
 | | |   mayRaise=[ExceptionFailure]
 | | | read ((GHC.Classes.==) '!')
-| | |   minReads=(Right 2)
+| | |   minReads=(Right 4)
 | | |   mayRaise=[ExceptionFailure]
 | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 3)
 | | |   mayRaise=[ExceptionFailure]
 | | | call <hidden>
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 3)
 | | |   mayRaise=[ExceptionFailure]
 | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 0)
-| | |   mayRaise=[]
+| | |   minReads=(Right 2)
+| | |   mayRaise=[ExceptionFailure]
 | | | call <hidden>
+| | |   minReads=(Right 2)
+| | |   mayRaise=[ExceptionFailure]
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | |   minReads=(Right 0)
 | | |   mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 8)
-| | |   mayRaise=[ExceptionFailure]
 | | | readRegister <hidden>
-| | |   minReads=(Right 8)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 8)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | writeRegister <hidden>
-| | |   minReads=(Right 8)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | jump <hidden>
-| | |   minReads=(Right 8)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | <ko>
 | | | pushInput
 | | |   minReads=(Right 0)
@@ -967,26 +967,26 @@ let <hidden>
 | | |   mayRaise=[ExceptionFailure]
 | | | | <ok>
 | | | | | pushValue (\x_0 -> \x_1 -> x_1)
-| | | | |   minReads=(Right 3)
+| | | | |   minReads=(Right 1)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | read Parsers.Nandlang.nandIdentLetter
-| | | | |   minReads=(Right 3)
+| | | | |   minReads=(Right 1)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 2)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | readRegister <hidden>
-| | | | |   minReads=(Right 2)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 2)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | writeRegister <hidden>
-| | | | |   minReads=(Right 2)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | jump <hidden>
-| | | | |   minReads=(Right 2)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | <ko>
 | | | | | pushInput
 | | | | |   minReads=(Right 1)
@@ -1007,14 +1007,14 @@ let <hidden>
 | | | | | | |   minReads=(Right 1)
 | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | |   minReads=(Right 0)
-| | | | | | |   mayRaise=[]
+| | | | | | |   minReads=(Right 1)
+| | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | |   minReads=(Right 0)
-| | | | | | |   mayRaise=[]
+| | | | | | |   minReads=(Right 1)
+| | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | call <hidden>
-| | | | | | |   minReads=(Right 0)
-| | | | | | |   mayRaise=[]
+| | | | | | |   minReads=(Right 1)
+| | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | | | |   minReads=(Right 1)
 | | | | | | |   mayRaise=[ExceptionFailure]
@@ -1060,39 +1060,39 @@ let <hidden>
 |   minReads=(Right 3)
 |   mayRaise=[ExceptionFailure]
 | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-|   minReads=(Right 1)
+|   minReads=(Right 2)
 |   mayRaise=[ExceptionFailure]
 | pushValue (\x_0 -> x_0)
-|   minReads=(Right 1)
+|   minReads=(Right 2)
 |   mayRaise=[ExceptionFailure]
 | newRegister <hidden>
-|   minReads=(Right 1)
+|   minReads=(Right 2)
 |   mayRaise=[ExceptionFailure]
 | iter <hidden>
-|   minReads=(Right 1)
+|   minReads=(Right 2)
 |   mayRaise=[ExceptionFailure]
 | | <ok>
 | | | pushValue (\x_0 -> \x_1 -> x_1)
-| | |   minReads=(Right 4)
-| | |   mayRaise=[ExceptionFailure]
-| | | join <hidden>
 | | |   minReads=(Right 2)
 | | |   mayRaise=[ExceptionFailure]
+| | | join <hidden>
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 4)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | | readRegister <hidden>
-| | | |   minReads=(Right 4)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 4)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | | writeRegister <hidden>
-| | | |   minReads=(Right 4)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | | jump <hidden>
-| | | |   minReads=(Right 4)
-| | | |   mayRaise=[ExceptionFailure]
+| | | |   minReads=(Right 0)
+| | | |   mayRaise=[]
 | | | catch ExceptionFailure
 | | |   minReads=(Right 2)
 | | |   mayRaise=[ExceptionFailure]
@@ -1162,66 +1162,66 @@ let <hidden>
 | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | <ok>
 | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
-| | | | | | | | |   minReads=(Right 11)
+| | | | | | | | |   minReads=(Right 7)
 | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | catch ExceptionFailure
-| | | | | | | | |   minReads=(Right 11)
+| | | | | | | | |   minReads=(Right 7)
 | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | <ok>
 | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> (GHC.Types.:) 'w' ((GHC.Types.:) 'h' ((GHC.Types.:) 'i' ((GHC.Types.:) 'l' ((GHC.Types.:) 'e' GHC.Types.[])))))
-| | | | | | | | | | |   minReads=(Right 11)
+| | | | | | | | | | |   minReads=(Right 7)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | read ((GHC.Classes.==) 'w')
-| | | | | | | | | | |   minReads=(Right 11)
+| | | | | | | | | | |   minReads=(Right 7)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 10)
+| | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | read ((GHC.Classes.==) 'h')
-| | | | | | | | | | |   minReads=(Right 10)
+| | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 9)
+| | | | | | | | | | |   minReads=(Right 5)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | read ((GHC.Classes.==) 'i')
-| | | | | | | | | | |   minReads=(Right 9)
+| | | | | | | | | | |   minReads=(Right 5)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | read ((GHC.Classes.==) 'l')
-| | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 7)
+| | | | | | | | | | |   minReads=(Right 3)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | read ((GHC.Classes.==) 'e')
-| | | | | | | | | | |   minReads=(Right 7)
+| | | | | | | | | | |   minReads=(Right 3)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 6)
+| | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | |   minReads=(Right 6)
+| | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 6)
+| | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | call <hidden>
-| | | | | | | | | | |   minReads=(Right 6)
+| | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 6)
+| | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | call <hidden>
-| | | | | | | | | | |   minReads=(Right 6)
+| | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | |   minReads=(Right 4)
-| | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | call <hidden>
-| | | | | | | | | | |   minReads=(Right 4)
-| | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | | | | | | | |   minReads=(Right 0)
 | | | | | | | | | | |   mayRaise=[]
@@ -1256,39 +1256,45 @@ let <hidden>
 | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | <ok>
 | | | | | | | | | | | | | catch ExceptionFailure
-| | | | | | | | | | | | |   minReads=(Right 10)
+| | | | | | | | | | | | |   minReads=(Right 8)
 | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | <ok>
 | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> \x_7 -> \x_8 -> \x_9 -> x_8)
-| | | | | | | | | | | | | | |   minReads=(Right 10)
+| | | | | | | | | | | | | | |   minReads=(Right 8)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | join <hidden>
-| | | | | | | | | | | | | | |   minReads=(Right 10)
+| | | | | | | | | | | | | | |   minReads=(Right 8)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | |   minReads=(Right 3)
+| | | | | | | | | | | | | | | |   minReads=(Right 8)
 | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | |   minReads=(Right 3)
+| | | | | | | | | | | | | | | |   minReads=(Right 8)
 | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | newRegister <hidden>
-| | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | iter <hidden>
-| | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | <ok>
 | | | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
-| | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | |   minReads=(Right 4)
+| | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | |   minReads=(Right 4)
+| | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
@@ -1299,88 +1305,88 @@ let <hidden>
 | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
 | | | | | | | | | | | | | | | | | |   mayRaise=[]
-| | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | readRegister <hidden>
 | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
 | | | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | | | | readRegister <hidden>
-| | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | | writeRegister <hidden>
-| | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | | jump <hidden>
-| | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | <ko>
 | | | | | | | | | | | | | | | | | | pushInput
-| | | | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | | | | | | | | | | | | | | | | |                                                                j_1
 | | | | | | | | | | | | | | | | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | choicesBranch
-| | | | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
 | | | | | | | | | | | | | | | | | | | | readRegister <hidden>
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 6)
+| | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 6)
+| | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 6)
+| | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | read ((GHC.Classes.==) '=')
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 6)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 5)
+| | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 5)
+| | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | newRegister <hidden>
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | iter <hidden>
-| | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | <ok>
 | | | | | | | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 4)
+| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 4)
+| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 4)
 | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
@@ -1391,52 +1397,46 @@ let <hidden>
 | | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
 | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
-| | | | | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | | | | readRegister <hidden>
 | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
 | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | | | | | | | | readRegister <hidden>
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | | | | | | writeRegister <hidden>
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | | | | | | jump <hidden>
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
-| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
 | | | | | | | | | | | | | | | | | | | | | <ko>
 | | | | | | | | | | | | | | | | | | | | | | pushInput
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | | | | | | | | | | | | | | | | | | | | |                                                                j_1
 | | | | | | | | | | | | | | | | | | | | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | choicesBranch
-| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
 | | | | | | | | | | | | | | | | | | | | | | | | readRegister <hidden>
-| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | | | | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
 | | | | | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
@@ -1464,55 +1464,55 @@ let <hidden>
 | | | | | | | | | | | | | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | catch ExceptionFailure
-| | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | |   minReads=(Right 8)
 | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | <ok>
 | | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> GHC.Tuple.())
-| | | | | | | | | | | | | | | | |   minReads=(Right 3)
+| | | | | | | | | | | | | | | | |   minReads=(Right 11)
 | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | catch ExceptionFailure
-| | | | | | | | | | | | | | | | |   minReads=(Right 3)
+| | | | | | | | | | | | | | | | |   minReads=(Right 11)
 | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | <ok>
 | | | | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'v' ((GHC.Types.:) 'a' ((GHC.Types.:) 'r' GHC.Types.[])))
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 3)
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 11)
 | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | read ((GHC.Classes.==) 'v')
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 3)
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 11)
 | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 10)
 | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | read ((GHC.Classes.==) 'a')
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 10)
 | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 9)
 | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | read ((GHC.Classes.==) 'r')
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 9)
 | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | <ko>
 | | | | | | | | | | | | | | | | | | | loadInput
 | | | | | | | | | | | | | | | | | | |   minReads=(Left ExceptionFailure)
@@ -1522,23 +1522,23 @@ let <hidden>
 | | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | <ko>
 | | | | | | | | | | | | | | | | | pushInput
-| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   minReads=(Right 8)
 | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | | | | | | | | | | | | | | | |                                                                j_1
 | | | | | | | | | | | | | | | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   minReads=(Right 8)
 | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | choicesBranch
-| | | | | | | | | | | | | | | | |   minReads=(Right 0)
+| | | | | | | | | | | | | | | | |   minReads=(Right 8)
 | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
 | | | | | | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | | | | | | | | |   minReads=(Right 0)
-| | | | | | | | | | | | | | | | | | |   mayRaise=[]
+| | | | | | | | | | | | | | | | | | |   minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | | | | | | | | | | | <default>
 | | | | | | | | | | | | | | | | | | | fail []
 | | | | | | | | | | | | | | | | | | |   minReads=(Left ExceptionFailure)
@@ -1595,44 +1595,44 @@ let <hidden>
 | | | | | | |   mayRaise=[ExceptionFailure]
 | | <ko>
 | | | pushInput
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 2)
 | | |   mayRaise=[ExceptionFailure]
 | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | |                                                                j_1
 | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 2)
 | | |   mayRaise=[ExceptionFailure]
 | | | choicesBranch
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 2)
 | | |   mayRaise=[ExceptionFailure]
 | | | | <branch (\x_0 -> x_0)>
 | | | | | readRegister <hidden>
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | call <hidden>
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 2)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 2)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | call <hidden>
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 2)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | read ((GHC.Classes.==) '}')
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 1)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | call <hidden>
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 1)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
 | | | | |   mayRaise=[]
@@ -1659,79 +1659,79 @@ let <hidden>
 |   minReads=(Right 4)
 |   mayRaise=[ExceptionFailure]
 | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-|   minReads=(Right 2)
+|   minReads=(Right 3)
 |   mayRaise=[ExceptionFailure]
 | call <hidden>
-|   minReads=(Right 2)
+|   minReads=(Right 3)
 |   mayRaise=[ExceptionFailure]
 | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-|   minReads=(Right 1)
+|   minReads=(Right 2)
 |   mayRaise=[ExceptionFailure]
 | pushValue (\x_0 -> x_0)
-|   minReads=(Right 1)
+|   minReads=(Right 2)
 |   mayRaise=[ExceptionFailure]
 | newRegister <hidden>
-|   minReads=(Right 1)
+|   minReads=(Right 2)
 |   mayRaise=[ExceptionFailure]
 | iter <hidden>
-|   minReads=(Right 1)
+|   minReads=(Right 2)
 |   mayRaise=[ExceptionFailure]
 | | <ok>
 | | | pushValue (\x_0 -> \x_1 -> x_1)
-| | |   minReads=(Right 0)
-| | |   mayRaise=[]
+| | |   minReads=(Right 1)
+| | |   mayRaise=[ExceptionFailure]
 | | | call <hidden>
+| | |   minReads=(Right 1)
+| | |   mayRaise=[ExceptionFailure]
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | |   minReads=(Right 0)
 | | |   mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
 | | | readRegister <hidden>
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | writeRegister <hidden>
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | | jump <hidden>
-| | |   minReads=(Right 2)
-| | |   mayRaise=[ExceptionFailure]
+| | |   minReads=(Right 0)
+| | |   mayRaise=[]
 | | <ko>
 | | | pushInput
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 2)
 | | |   mayRaise=[ExceptionFailure]
 | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | |                                                                j_1
 | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 2)
 | | |   mayRaise=[ExceptionFailure]
 | | | choicesBranch
-| | |   minReads=(Right 1)
+| | |   minReads=(Right 2)
 | | |   mayRaise=[ExceptionFailure]
 | | | | <branch (\x_0 -> x_0)>
 | | | | | readRegister <hidden>
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | pushValue GHC.Tuple.()
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | read ((GHC.Classes.==) ']')
-| | | | |   minReads=(Right 1)
+| | | | |   minReads=(Right 2)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 1)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | call <hidden>
-| | | | |   minReads=(Right 0)
-| | | | |   mayRaise=[]
+| | | | |   minReads=(Right 1)
+| | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | | |   minReads=(Right 0)
 | | | | |   mayRaise=[]
@@ -1762,173 +1762,173 @@ iter <hidden>
   mayRaise=[ExceptionFailure]
 | <ok>
 | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> \x_7 -> \x_8 -> x_8)
-| |   minReads=(Right 13)
+| |   minReads=(Right 18)
 | |   mayRaise=[ExceptionFailure]
 | | catch ExceptionFailure
-| |   minReads=(Right 13)
+| |   minReads=(Right 18)
 | |   mayRaise=[ExceptionFailure]
 | | | <ok>
 | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> \x_7 -> (GHC.Types.:) 'f' ((GHC.Types.:) 'u' ((GHC.Types.:) 'n' ((GHC.Types.:) 'c' ((GHC.Types.:) 't' ((GHC.Types.:) 'i' ((GHC.Types.:) 'o' ((GHC.Types.:) 'n' GHC.Types.[]))))))))
-| | | |   minReads=(Right 13)
+| | | |   minReads=(Right 18)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | read ((GHC.Classes.==) 'f')
-| | | |   minReads=(Right 13)
+| | | |   minReads=(Right 18)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 12)
+| | | |   minReads=(Right 17)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | read ((GHC.Classes.==) 'u')
-| | | |   minReads=(Right 12)
+| | | |   minReads=(Right 17)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 11)
+| | | |   minReads=(Right 16)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | read ((GHC.Classes.==) 'n')
-| | | |   minReads=(Right 11)
+| | | |   minReads=(Right 16)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 10)
+| | | |   minReads=(Right 15)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | read ((GHC.Classes.==) 'c')
-| | | |   minReads=(Right 10)
+| | | |   minReads=(Right 15)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 9)
+| | | |   minReads=(Right 14)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | read ((GHC.Classes.==) 't')
-| | | |   minReads=(Right 9)
+| | | |   minReads=(Right 14)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 8)
+| | | |   minReads=(Right 13)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | read ((GHC.Classes.==) 'i')
-| | | |   minReads=(Right 8)
+| | | |   minReads=(Right 13)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 7)
+| | | |   minReads=(Right 12)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | read ((GHC.Classes.==) 'o')
-| | | |   minReads=(Right 7)
+| | | |   minReads=(Right 12)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 6)
+| | | |   minReads=(Right 11)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | read ((GHC.Classes.==) 'n')
-| | | |   minReads=(Right 6)
+| | | |   minReads=(Right 11)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 5)
+| | | |   minReads=(Right 10)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | commit ExceptionFailure
-| | | |   minReads=(Right 5)
+| | | |   minReads=(Right 10)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 5)
+| | | |   minReads=(Right 10)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | call <hidden>
-| | | |   minReads=(Right 5)
+| | | |   minReads=(Right 10)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 5)
+| | | |   minReads=(Right 10)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | call <hidden>
-| | | |   minReads=(Right 5)
+| | | |   minReads=(Right 10)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 3)
+| | | |   minReads=(Right 8)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | call <hidden>
-| | | |   minReads=(Right 3)
+| | | |   minReads=(Right 8)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 1)
+| | | |   minReads=(Right 6)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | call <hidden>
-| | | |   minReads=(Right 1)
+| | | |   minReads=(Right 6)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 1)
+| | | |   minReads=(Right 6)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | join <hidden>
-| | | |   minReads=(Right 24)
+| | | |   minReads=(Right 6)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 36)
+| | | | |   minReads=(Right 6)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | call <hidden>
-| | | | |   minReads=(Right 36)
+| | | | |   minReads=(Right 6)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 34)
+| | | | |   minReads=(Right 4)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | call <hidden>
-| | | | |   minReads=(Right 34)
+| | | | |   minReads=(Right 4)
 | | | | |   mayRaise=[ExceptionFailure]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 30)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | readRegister <hidden>
-| | | | |   minReads=(Right 30)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | |   minReads=(Right 30)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | writeRegister <hidden>
-| | | | |   minReads=(Right 30)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | | jump <hidden>
-| | | | |   minReads=(Right 30)
-| | | | |   mayRaise=[ExceptionFailure]
+| | | | |   minReads=(Right 0)
+| | | | |   mayRaise=[]
 | | | | catch ExceptionFailure
-| | | |   minReads=(Right 0)
+| | | |   minReads=(Right 6)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | | <ok>
 | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
-| | | | | |   minReads=(Right 1)
+| | | | | |   minReads=(Right 8)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | read ((GHC.Classes.==) ':')
-| | | | | |   minReads=(Right 1)
+| | | | | |   minReads=(Right 8)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 7)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | call <hidden>
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 7)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 6)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | call <hidden>
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 6)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 6)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | commit ExceptionFailure
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 6)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | refJoin <hidden>
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 6)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | <ko>
 | | | | | | pushInput
-| | | | | |   minReads=(Right 0)
+| | | | | |   minReads=(Right 6)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | | | | |                                                                j_1
 | | | | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | | | | |   minReads=(Right 0)
+| | | | | |   minReads=(Right 6)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | choicesBranch
-| | | | | |   minReads=(Right 0)
+| | | | | |   minReads=(Right 6)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | <branch (\x_0 -> x_0)>
 | | | | | | | | call <hidden>
-| | | | | | | |   minReads=(Right 0)
-| | | | | | | |   mayRaise=[]
+| | | | | | | |   minReads=(Right 6)
+| | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | refJoin <hidden>
-| | | | | | | |   minReads=(Right 0)
-| | | | | | | |   mayRaise=[]
+| | | | | | | |   minReads=(Right 6)
+| | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | <default>
 | | | | | | | | fail []
 | | | | | | | |   minReads=(Left ExceptionFailure)
@@ -1961,13 +1961,13 @@ iter <hidden>
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | |   minReads=(Right 0)
-| | | |   mayRaise=[]
+| | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | |   minReads=(Right 0)
-| | | |   mayRaise=[]
+| | | |   mayRaise=[ExceptionFailure]
 | | | | call <hidden>
 | | | |   minReads=(Right 0)
-| | | |   mayRaise=[]
+| | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | | | |   minReads=(Right 0)
 | | | |   mayRaise=[ExceptionFailure]
@@ -1991,7 +1991,7 @@ iter <hidden>
 | | | | | | | | pushInput
 | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | |   mayRaise=[ExceptionFailure]
-| | | | | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | | | | read (\x_0 -> GHC.Types.True)
 | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | popValue
index 494ef7fc7e70309d934f02f32f64458d9dd269f2..895a7001476383389c3e8862ecd6e5cfeafd98fc 100644 (file)
@@ -17,49 +17,49 @@ join <hidden>
 |   minReads=(Right 0)
 |   mayRaise=[]
 catch ExceptionFailure
-  minReads=(Right 1)
+  minReads=(Right 2)
   mayRaise=[ExceptionFailure]
 | <ok>
 | | pushValue (\x_0 -> 'a')
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | read ((GHC.Classes.==) 'a')
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 0)
-| |   mayRaise=[]
+| |   minReads=(Right 1)
+| |   mayRaise=[ExceptionFailure]
 | | commit ExceptionFailure
-| |   minReads=(Right 0)
-| |   mayRaise=[]
+| |   minReads=(Right 1)
+| |   mayRaise=[ExceptionFailure]
 | | refJoin <hidden>
-| |   minReads=(Right 0)
-| |   mayRaise=[]
+| |   minReads=(Right 1)
+| |   mayRaise=[ExceptionFailure]
 | <ko>
 | | pushInput
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | |                                                                j_1
 | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | choicesBranch
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | | <branch (\x_0 -> x_0)>
 | | | | pushValue (\x_0 -> 'b')
-| | | |   minReads=(Right 1)
+| | | |   minReads=(Right 2)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | read ((GHC.Classes.==) 'b')
-| | | |   minReads=(Right 1)
+| | | |   minReads=(Right 2)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | |   minReads=(Right 0)
-| | | |   mayRaise=[]
+| | | |   minReads=(Right 1)
+| | | |   mayRaise=[ExceptionFailure]
 | | | | refJoin <hidden>
-| | | |   minReads=(Right 0)
-| | | |   mayRaise=[]
+| | | |   minReads=(Right 1)
+| | | |   mayRaise=[ExceptionFailure]
 | | | <default>
 | | | | fail []
 | | | |   minReads=(Left ExceptionFailure)
index 0135953ceb66119711cdce85ee328d98ffec71e2..31d39c42b45f761a5052221d7656fbde168b61a5 100644 (file)
@@ -17,81 +17,81 @@ join <hidden>
 |   minReads=(Right 0)
 |   mayRaise=[]
 catch ExceptionFailure
-  minReads=(Right 1)
+  minReads=(Right 2)
   mayRaise=[ExceptionFailure]
 | <ok>
 | | pushValue (\x_0 -> 'a')
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | read ((GHC.Classes.==) 'a')
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 0)
-| |   mayRaise=[]
+| |   minReads=(Right 1)
+| |   mayRaise=[ExceptionFailure]
 | | commit ExceptionFailure
-| |   minReads=(Right 0)
-| |   mayRaise=[]
+| |   minReads=(Right 1)
+| |   mayRaise=[ExceptionFailure]
 | | refJoin <hidden>
-| |   minReads=(Right 0)
-| |   mayRaise=[]
+| |   minReads=(Right 1)
+| |   mayRaise=[ExceptionFailure]
 | <ko>
 | | pushInput
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | |                                                                j_1
 | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | choicesBranch
-| |   minReads=(Right 1)
+| |   minReads=(Right 2)
 | |   mayRaise=[ExceptionFailure]
 | | | <branch (\x_0 -> x_0)>
 | | | | catch ExceptionFailure
-| | | |   minReads=(Right 1)
+| | | |   minReads=(Right 2)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | | <ok>
 | | | | | | pushValue (\x_0 -> 'b')
-| | | | | |   minReads=(Right 1)
+| | | | | |   minReads=(Right 2)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | read ((GHC.Classes.==) 'b')
-| | | | | |   minReads=(Right 1)
+| | | | | |   minReads=(Right 2)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 1)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | commit ExceptionFailure
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 1)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | refJoin <hidden>
-| | | | | |   minReads=(Right 0)
-| | | | | |   mayRaise=[]
+| | | | | |   minReads=(Right 1)
+| | | | | |   mayRaise=[ExceptionFailure]
 | | | | | <ko>
 | | | | | | pushInput
-| | | | | |   minReads=(Right 1)
+| | | | | |   minReads=(Right 2)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
 | | | | | |                                                                j_1
 | | | | | |                                                                _) -> i_0 GHC.Classes.== j_1)
-| | | | | |   minReads=(Right 1)
+| | | | | |   minReads=(Right 2)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | choicesBranch
-| | | | | |   minReads=(Right 1)
+| | | | | |   minReads=(Right 2)
 | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | <branch (\x_0 -> x_0)>
 | | | | | | | | pushValue (\x_0 -> 'c')
-| | | | | | | |   minReads=(Right 1)
+| | | | | | | |   minReads=(Right 2)
 | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | read ((GHC.Classes.==) 'c')
-| | | | | | | |   minReads=(Right 1)
+| | | | | | | |   minReads=(Right 2)
 | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | |   minReads=(Right 0)
-| | | | | | | |   mayRaise=[]
+| | | | | | | |   minReads=(Right 1)
+| | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | refJoin <hidden>
-| | | | | | | |   minReads=(Right 0)
-| | | | | | | |   mayRaise=[]
+| | | | | | | |   minReads=(Right 1)
+| | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | <default>
 | | | | | | | | fail []
 | | | | | | | |   minReads=(Left ExceptionFailure)
index 001636b346fcd23b6f41cc3dcf5e96e024c5b823..9ee0f022098fdc8f10b8bb0f5f1c48f51d6f5750 100644 (file)
@@ -12,32 +12,32 @@ iter <hidden>
   mayRaise=[ExceptionFailure]
 | <ok>
 | | pushValue (\x_0 -> (GHC.Types.:) 'a')
-| |   minReads=(Right 3)
+| |   minReads=(Right 1)
 | |   mayRaise=[ExceptionFailure]
 | | read ((GHC.Classes.==) 'a')
-| |   minReads=(Right 3)
+| |   minReads=(Right 1)
 | |   mayRaise=[ExceptionFailure]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
-| | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> \x_5 -> x_3 (x_4 x_5)))
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
-| | lift2Value ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | pushValue (\x_0 -> \x_1 -> \x_2 -> x_1 (x_0 x_2))
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | lift2Value (\x_0 -> \x_1 -> x_1 x_0)
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | readRegister <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | writeRegister <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | jump <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | <ko>
 | | pushInput
 | |   minReads=(Right 0)
index 4f46da465426529251aa9c88d1eee26bffde931f..6a4b7022ab7d07e433d3bd5c4df48d5882f0aeee 100644 (file)
@@ -65,32 +65,32 @@ iter <hidden>
   mayRaise=[ExceptionFailure]
 | <ok>
 | | pushValue (GHC.Types.:)
+| |   minReads=(Right 4)
+| |   mayRaise=[ExceptionFailure]
+| | call <hidden>
+| |   minReads=(Right 4)
+| |   mayRaise=[ExceptionFailure]
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | |   minReads=(Right 0)
 | |   mayRaise=[]
-| | call <hidden>
+| | pushValue (\x_0 -> \x_1 -> \x_2 -> x_1 (x_0 x_2))
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | lift2Value (\x_0 -> \x_1 -> x_1 x_0)
 | |   minReads=(Right 0)
 | |   mayRaise=[]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
-| | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> \x_5 -> x_3 (x_4 x_5)))
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
-| | lift2Value ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
 | | readRegister <hidden>
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | writeRegister <hidden>
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | jump <hidden>
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | <ko>
 | | pushInput
 | |   minReads=(Right 0)
index 304b77c85cff78532a16afaf1f2b86810e4b69a3..b543197db797da15862fba7ab3d9c39e032c2065 100644 (file)
@@ -65,32 +65,32 @@ iter <hidden>
   mayRaise=[ExceptionFailure]
 | <ok>
 | | pushValue (GHC.Types.:)
+| |   minReads=(Right 4)
+| |   mayRaise=[ExceptionFailure]
+| | call <hidden>
+| |   minReads=(Right 4)
+| |   mayRaise=[ExceptionFailure]
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
 | |   minReads=(Right 0)
 | |   mayRaise=[]
-| | call <hidden>
+| | pushValue (\x_0 -> \x_1 -> \x_2 -> x_1 (x_0 x_2))
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | lift2Value (\x_0 -> \x_1 -> x_1 x_0)
 | |   minReads=(Right 0)
 | |   mayRaise=[]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
-| | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> \x_5 -> x_3 (x_4 x_5)))
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
-| | lift2Value ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
 | | readRegister <hidden>
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | writeRegister <hidden>
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | jump <hidden>
-| |   minReads=(Right 8)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | <ko>
 | | pushInput
 | |   minReads=(Right 0)
@@ -136,7 +136,7 @@ iter <hidden>
 | | | | | | | | pushInput
 | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | |   mayRaise=[ExceptionFailure]
-| | | | | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | | | | read (\x_0 -> GHC.Types.True)
 | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | popValue
index 803c9cb7ac0e01e15ce1b34c7bc23d4e65ed8085..919b53538496728755787f9a425dfa51fc119dc2 100644 (file)
@@ -12,32 +12,32 @@ iter <hidden>
   mayRaise=[ExceptionFailure]
 | <ok>
 | | pushValue (\x_0 -> (GHC.Types.:) 'r')
-| |   minReads=(Right 3)
+| |   minReads=(Right 1)
 | |   mayRaise=[ExceptionFailure]
 | | read ((GHC.Classes.==) 'r')
-| |   minReads=(Right 3)
+| |   minReads=(Right 1)
 | |   mayRaise=[ExceptionFailure]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
-| | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> \x_5 -> x_3 (x_4 x_5)))
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
-| | lift2Value ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | pushValue (\x_0 -> \x_1 -> \x_2 -> x_1 (x_0 x_2))
+| |   minReads=(Right 0)
+| |   mayRaise=[]
+| | lift2Value (\x_0 -> \x_1 -> x_1 x_0)
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | readRegister <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | writeRegister <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | | jump <hidden>
-| |   minReads=(Right 2)
-| |   mayRaise=[ExceptionFailure]
+| |   minReads=(Right 0)
+| |   mayRaise=[]
 | <ko>
 | | pushInput
 | |   minReads=(Right 0)
@@ -83,7 +83,7 @@ iter <hidden>
 | | | | | | | | pushInput
 | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | |   mayRaise=[ExceptionFailure]
-| | | | | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | | | | read (\x_0 -> GHC.Types.True)
 | | | | | | | |   minReads=(Left ExceptionFailure)
 | | | | | | | |   mayRaise=[ExceptionFailure]
 | | | | | | | | popValue
index ed7e46a85aa28291c9d899bf1e497cba2beca538..ec8902c371cdd8444027c141e8fc17a340064885 100644 (file)
@@ -21,7 +21,7 @@ catch ExceptionFailure
 | | | | pushInput
 | | | |   minReads=(Left ExceptionFailure)
 | | | |   mayRaise=[ExceptionFailure]
-| | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | read (\x_0 -> GHC.Types.True)
 | | | |   minReads=(Left ExceptionFailure)
 | | | |   mayRaise=[ExceptionFailure]
 | | | | popValue
index fd33d15269bcfa467c2315ea55e1e6d2c0ee9593..62c6a31b8d88a7816777e3c43c4f5cb90d03cd9d 100644 (file)
@@ -65,7 +65,7 @@ goldens = testGroup "Parser" $
 parsers :: [Text -> Either (P.ParsingError Text) String]
 parsers =
   [ p1, p2, p3, p4, p5, p6, p7, p8, p9
-  , p10, p11, p12, p13, p14, p15, p16--, p17
+  , p10, p11, p12, p13, p14, p15, p16, p17
   ]
 
 p1 = $$(TH.Code $ TH.runIO s1)
@@ -84,4 +84,4 @@ p13 = $$(TH.Code $ TH.runIO s13)
 p14 = $$(TH.Code $ TH.runIO s14)
 p15 = $$(TH.Code $ TH.runIO s15)
 p16 = $$(TH.Code $ TH.runIO s16)
---p17 = $$(TH.Code $ TH.runIO s17)
+p17 = $$(TH.Code $ TH.runIO s17)
index da38e420291d1ffa71fa96fb2bc7780138ef2885..c146dbaa2409c157b28ac34eb766e15d21fa2c2a 100644 (file)
@@ -1 +1 @@
-ParsingErrorStandard {parsingErrorOffset = 3, parsingErrorException = ExceptionFailure, parsingErrorUnexpected = Just 'a', parsingErrorExpecting = fromList [FailureHorizon 3,FailureToken 'b']}
\ No newline at end of file
+ParsingErrorStandard {parsingErrorOffset = 4, parsingErrorException = ExceptionFailure, parsingErrorUnexpected = Just 'c', parsingErrorExpecting = fromList [FailureToken 'a',FailureToken 'b']}
\ No newline at end of file
index c45d36c4a510ec341549eb4fcd6a3ec7d9308799..5ec0128ef7755bf3d7116aab6573afef3631b526 100644 (file)
@@ -1 +1 @@
-ParsingErrorStandard {parsingErrorOffset = 8, parsingErrorException = ExceptionFailure, parsingErrorUnexpected = Just 'a', parsingErrorExpecting = fromList [FailureEnd,FailureHorizon 3]}
\ No newline at end of file
+"baacbccbaa"
\ No newline at end of file
index a9cf1d4397c4c0419d629812520feb4ea2a84326..92302fa3507235d5f56ef88161319ac0fd424e79 100644 (file)
@@ -1 +1 @@
-"aaa"
\ No newline at end of file
+"aaaaa"
\ No newline at end of file
index 97ab6ee9a7dec1aa0a693fca76423a99be59a12e..584cd86c4298fc22e9af326d421140ce5326bd6c 100644 (file)
@@ -1 +1 @@
-ParsingErrorStandard {parsingErrorOffset = 2, parsingErrorException = ExceptionFailure, parsingErrorUnexpected = Just 'r', parsingErrorExpecting = fromList [FailureEnd,FailureHorizon 3]}
\ No newline at end of file
+ParsingErrorStandard {parsingErrorOffset = 3, parsingErrorException = ExceptionFailure, parsingErrorUnexpected = Just 'a', parsingErrorExpecting = fromList [FailureEnd,FailureToken 'r']}
\ No newline at end of file
index 42b7c742ec7a5de87a887e5e580421121fc8e32e..c9b6836885cd09314e06b08b22d08d31ff94a790 100644 (file)
                                    in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                             loop = \_callReturn callInput callCatchStackByLabel ->
                               let readFail = catchHandler callInput
-                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 callInput)
+                               in if readMore callInput
                                     then
                                       let !(#
                                              c,
                                                   1
                                                   ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                       ( case inputToken of
-                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                       )
                                                   )
                                                   Data.Set.Internal.Tip
index e38aaac7c93c423feb9f8de5a255462bf53ecc66..20ab97a68d59b8229862da3153626b87e7e2bd29 100644 (file)
                                    in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                             loop = \_callReturn callInput callCatchStackByLabel ->
                               let readFail = catchHandler callInput
-                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 callInput)
+                               in if readMore callInput
                                     then
                                       let !(#
                                              c,
                                                   1
                                                   ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                       ( case inputToken of
-                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                       )
                                                   )
                                                   Data.Set.Internal.Tip
index aa0b547ef2d2734c24ad7dba8f6f4e65437d7618..27fcc83604edb1d2d0e3f5168e377fc5ccfd3a9a 100644 (file)
@@ -89,7 +89,7 @@
                                    in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                             loop = \_callReturn callInput callCatchStackByLabel ->
                               let readFail = catchHandler callInput
-                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 callInput)
+                               in if readMore callInput
                                     then
                                       let !(#
                                              c,
                                                   1
                                                   ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                       ( case inputToken of
-                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                       )
                                                   )
                                                   Data.Set.Internal.Tip
                                                 then
                                                   let _ = "choicesBranch.then"
                                                    in let readFail = readFail
-                                                       in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+                                                       in if readMore callInput
                                                             then
                                                               let !(#
                                                                      c,
                                                                           1
                                                                           ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                               ( case inputToken of
-                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                                               )
                                                                           )
                                                                           Data.Set.Internal.Tip
                                                         then
                                                           let _ = "choicesBranch.then"
                                                            in let readFail = readFail
-                                                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+                                                               in if readMore callInput
                                                                     then
                                                                       let !(#
                                                                              c,
                                                                                   1
                                                                                   ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                       ( case inputToken of
-                                                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+                                                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                                                       )
                                                                                   )
                                                                                   Data.Set.Internal.Tip
                                                                 then
                                                                   let _ = "choicesBranch.then"
                                                                    in let readFail = readFail
-                                                                       in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+                                                                       in if readMore callInput
                                                                             then
                                                                               let !(#
                                                                                      c,
                                                                                           1
                                                                                           ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                               ( case inputToken of
-                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                                                               )
                                                                                           )
                                                                                           Data.Set.Internal.Tip
                                                                         then
                                                                           let _ = "choicesBranch.then"
                                                                            in let readFail = readFail
-                                                                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+                                                                               in if readMore callInput
                                                                                     then
                                                                                       let !(#
                                                                                              c,
                                                                                                   1
                                                                                                   ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                       ( case inputToken of
-                                                                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+                                                                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                                                                       )
                                                                                                   )
                                                                                                   Data.Set.Internal.Tip
                                                                                 then
                                                                                   let _ = "choicesBranch.then"
                                                                                    in let readFail = readFail
-                                                                                       in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+                                                                                       in if readMore callInput
                                                                                             then
                                                                                               let !(#
                                                                                                      c,
                                                                                                           1
                                                                                                           ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                               ( case inputToken of
-                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                                                                               )
                                                                                                           )
                                                                                                           Data.Set.Internal.Tip
                                                                                         then
                                                                                           let _ = "choicesBranch.then"
                                                                                            in let readFail = readFail
-                                                                                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+                                                                                               in if readMore callInput
                                                                                                     then
                                                                                                       let !(#
                                                                                                              c,
                                                                                                                   1
                                                                                                                   ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                                       ( case inputToken of
-                                                                                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+                                                                                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                                                                                       )
                                                                                                                   )
                                                                                                                   Data.Set.Internal.Tip
                                                                                                 then
                                                                                                   let _ = "choicesBranch.then"
                                                                                                    in let readFail = readFail
-                                                                                                       in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 callInput)
+                                                                                                       in if readMore callInput
                                                                                                             then
                                                                                                               let !(#
                                                                                                                      c,
                                                                                                                               ( let _ = "suspend"
                                                                                                                                  in \farInp farExp v (!inp) ->
                                                                                                                                       let readFail = readFail
-                                                                                                                                       in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
+                                                                                                                                       in if readMore inp
                                                                                                                                             then
                                                                                                                                               let !(#
                                                                                                                                                      c,
                                                                                                                                                           1
                                                                                                                                                           ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                                                                               ( case inputToken of
-                                                                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+                                                                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                                                                                                                               )
                                                                                                                                                           )
                                                                                                                                                           Data.Set.Internal.Tip
                                                                                                                           1
                                                                                                                           ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                                               ( case inputToken of
-                                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+                                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                                                                                               )
                                                                                                                           )
                                                                                                                           Data.Set.Internal.Tip
index e44a20b62c6a710ffa7b80fa40614c41c1607b97..d28f8f2284f9462add9c0161788773b87ac3a182 100644 (file)
                                              in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                                       loop = \_callReturn callInput callCatchStackByLabel ->
                                         let readFail = catchHandler callInput
-                                         in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+                                         in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 callInput)
                                               then
                                                 let !(#
                                                        c,
                                                             1
                                                             ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                 ( case inputToken of
-                                                                    (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+                                                                    (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
                                                                 )
                                                             )
                                                             Data.Set.Internal.Tip
                                                                               ( let _ = "suspend"
                                                                                  in \farInp farExp v (!inp) ->
                                                                                       let readFail = readFail
-                                                                                       in if readMore inp
+                                                                                       in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
                                                                                             then
                                                                                               let !(#
                                                                                                      c,
                                                                                                           1
                                                                                                           ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                               ( case inputToken of
-                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
                                                                                                               )
                                                                                                           )
                                                                                                           Data.Set.Internal.Tip
                                                                                                                                                                         ( let _ = "suspend"
                                                                                                                                                                            in \farInp farExp v (!inp) ->
                                                                                                                                                                                 let readFail = catchHandler
-                                                                                                                                                                                 in if readMore inp
+                                                                                                                                                                                 in if readMore (Symantic.Parser.Machine.Input.shiftRightText 5 inp)
                                                                                                                                                                                       then
                                                                                                                                                                                         let !(#
                                                                                                                                                                                                c,
                                                                                                                                                                                                     1
                                                                                                                                                                                                     ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                                                                                                                         ( case inputToken of
-                                                                                                                                                                                                            (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+                                                                                                                                                                                                            (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 6
                                                                                                                                                                                                         )
                                                                                                                                                                                                     )
                                                                                                                                                                                                     Data.Set.Internal.Tip
                                                                                                                                               let _ = "catch.ko ExceptionFailure"
                                                                                                                                                in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                                                                                                                                          in let readFail = catchHandler
-                                                                                                                                             in if readMore (Symantic.Parser.Machine.Input.shiftRightText 12 failInp)
+                                                                                                                                             in if readMore (Symantic.Parser.Machine.Input.shiftRightText 10 failInp)
                                                                                                                                                   then
                                                                                                                                                     let !(#
                                                                                                                                                            c,
                                                                                                                                                                 1
                                                                                                                                                                 ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                                                                                     ( case inputToken of
-                                                                                                                                                                        (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 13
+                                                                                                                                                                        (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 11
                                                                                                                                                                     )
                                                                                                                                                                 )
                                                                                                                                                                 Data.Set.Internal.Tip
                                                                                                     let _ = "catch.ko ExceptionFailure"
                                                                                                      in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                                                                                                in let readFail = catchHandler
-                                                                                                   in if readMore (Symantic.Parser.Machine.Input.shiftRightText 12 failInp)
+                                                                                                   in if readMore (Symantic.Parser.Machine.Input.shiftRightText 6 failInp)
                                                                                                         then
                                                                                                           let !(#
                                                                                                                  c,
                                                                                                                       1
                                                                                                                       ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                                           ( case inputToken of
-                                                                                                                              (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 13
+                                                                                                                              (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 7
                                                                                                                           )
                                                                                                                       )
                                                                                                                       Data.Set.Internal.Tip
                                                                               let _ = "catch.ko ExceptionFailure"
                                                                                in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
                                                                          in let readFail = catchHandler
-                                                                             in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 callInput)
+                                                                             in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
                                                                                   then
                                                                                     let !(#
                                                                                            c,
                                                                                                 1
                                                                                                 ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                     ( case inputToken of
-                                                                                                        (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
+                                                                                                        (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
                                                                                                     )
                                                                                                 )
                                                                                                 Data.Set.Internal.Tip
                                                                        in do
                                                                             sr <- GHC.STRef.readSTRef reg
                                                                             let readFail = readFail
-                                                                             in if readMore failInp
+                                                                             in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
                                                                                   then
                                                                                     let !(#
                                                                                            c,
                                                                                                 1
                                                                                                 ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                     ( case inputToken of
-                                                                                                        (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+                                                                                                        (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
                                                                                                     )
                                                                                                 )
                                                                                                 Data.Set.Internal.Tip
                                                            in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                                                     loop = \_callReturn callInput callCatchStackByLabel ->
                                                       let readFail = catchHandler callInput
-                                                       in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 callInput)
+                                                       in if readMore callInput
                                                             then
                                                               let !(#
                                                                      c,
                                                                           1
                                                                           ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                               ( case inputToken of
-                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                                               )
                                                                           )
                                                                           Data.Set.Internal.Tip
                                                 let _ = "catch.ko ExceptionFailure"
                                                  in catchHandler callInput Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
                                            in let readFail = catchHandler
-                                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 12 callInput)
+                                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 17 callInput)
                                                     then
                                                       let !(#
                                                              c,
                                                                                                                                                                                                                 let _ = "choicesBranch.else"
                                                                                                                                                                                                                  in catchHandler callInput Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                                                                                                                                                                                                    in let readFail = catchHandler
-                                                                                                                                                                                                       in if readMore inp
+                                                                                                                                                                                                       in if readMore (Symantic.Parser.Machine.Input.shiftRightText 7 inp)
                                                                                                                                                                                                             then
                                                                                                                                                                                                               let !(#
                                                                                                                                                                                                                      c,
                                                                                                                                                                                                                           1
                                                                                                                                                                                                                           ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                                                                                                                                                                               ( case inputToken of
-                                                                                                                                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+                                                                                                                                                                                                                                  (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 8
                                                                                                                                                                                                                               )
                                                                                                                                                                                                                           )
                                                                                                                                                                                                                           Data.Set.Internal.Tip
                                                                   1
                                                                   ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                                       ( case inputToken of
-                                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 13
+                                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 18
                                                                       )
                                                                   )
                                                                   Data.Set.Internal.Tip
index 872b1ab62f01d30668fe5f75ca0f831ed99f3a50..6d337fe8fa2d82a6217955f3112586597a65e3d6 100644 (file)
@@ -90,7 +90,7 @@
                                    in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                             loop = \_callReturn callInput callCatchStackByLabel ->
                               let readFail = catchHandler callInput
-                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 callInput)
+                               in if readMore callInput
                                     then
                                       let !(#
                                              c,
                                                   1
                                                   ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                       ( case inputToken of
-                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                       )
                                                   )
                                                   Data.Set.Internal.Tip
index 8dde8fad530d9ab64679af5174d0205d002c4870..dd8ddcf35291f3b580ca9d2ffe0cc8c88468c9a0 100644 (file)
                                    in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
                             loop = \_callReturn callInput callCatchStackByLabel ->
                               let readFail = catchHandler callInput
-                               in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 callInput)
+                               in if readMore callInput
                                     then
                                       let !(#
                                              c,
                                                   1
                                                   ( Symantic.Parser.Grammar.Combinators.SomeFailure
                                                       ( case inputToken of
-                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+                                                          (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
                                                       )
                                                   )
                                                   Data.Set.Internal.Tip