make benchmarks/repl
```
+```bash
+make ghcid
+make parsers/ghcid
+make tests/ghcid
+make benchmarks/ghcid
+```
+
## Testing
```bash
make tests
## Benchmarking
-### Profiling
+```bash
+make benchmarks b=Brainfuck/ByteString/hanoi/'*' BENCHMARK_OPTIONS=-n1
+```
+
+## Profiling
#### Time
```bash
override BENCHMARK_OPTIONS += --output benchmarks/html/$(version).html --match glob $b
-override GHCID_OPTIONS += --no-height-limit --reverse-errors
-override GHC_PROF_OPTIONS += -eventlog -fprof-auto -fprof-auto-calls
+override GHCID_OPTIONS += --no-height-limit --reverse-errors --warnings
+override GHC_PROF_OPTIONS += -eventlog -fprof-auto -fprof-cafs
+#-fprof-auto-calls
override REPL_OPTIONS += -ignore-dot-ghci
override RTS_OPTIONS += -L100
override TEST_OPTIONS += --color always --size-cutoff 1000000 $(addprefix -p ,$t)
+override CABAL_TEST_FLAGS += -j
cabal := $(wildcard *.cabal)
package := $(notdir ./$(cabal:.cabal=))
repl:
cabal repl $(CABAL_REPL_FLAGS) $(project)
ghcid:
- ghcid $(GHCID_OPTIONS) -c 'cabal repl $(CABAL_REPL_FLAGS) $(project) $(addprefix --repl-options ,$(REPL_OPTIONS))'
+ ghcid $(GHCID_OPTIONS) --command 'cabal repl -fno-code $(CABAL_REPL_FLAGS) $(project) $(addprefix --repl-options ,$(REPL_OPTIONS))'
.PHONY: parsers
parsers:
cabal build $(CABAL_BUILD_FLAGS) $(project):parsers
parsers/repl:
cabal repl $(CABAL_REPL_FLAGS) $(project):parsers
parsers/ghcid:
- ghcid $(GHCID_OPTIONS) -c 'cabal repl $(CABAL_REPL_FLAGS) $(project):parsers $(addprefix --repl-options ,$(REPL_OPTIONS))'
+ ghcid $(GHCID_OPTIONS) --command 'cabal repl -fno-code $(CABAL_REPL_FLAGS) $(project):parsers $(addprefix --repl-options ,$(REPL_OPTIONS))'
parsers/prof-th:
- cabal v2-build lib:$(project) --enable-profiling $(GHC_PROF_OPTIONS) --write-ghc-environment-files=always
+ cabal v2-build lib:$(project) --enable-profiling $(addprefix --ghc-options ,$(GHC_PROF_OPTIONS)) --write-ghc-environment-files=always
cabal build $(CABAL_BUILD_FLAGS) $(project):parsers \
- --enable-profiling $(GHC_PROF_OPTIONS) \
+ --enable-profiling $(addprefix --ghc-options ,$(GHC_PROF_OPTIONS)) \
--ghc-options "$(addprefix -opti,+RTS $(RTS_OPTIONS))"
.PHONY: tests
$(project)-test.eventlog $(project)-test.prof:
cabal test $(CABAL_TEST_FLAGS) \
--test-show-details always --test-options "$(TEST_OPTIONS) +RTS $(RTS_OPTIONS)" \
- --enable-profiling $(GHC_PROF_OPTIONS) || true
+ --enable-profiling $(addprefix --ghc-options ,$(GHC_PROF_OPTIONS)) || true
tests/prof-th:
- cabal v2-build lib:$(project) --enable-profiling $(GHC_PROF_OPTIONS) --write-ghc-environment-files=always
+ cabal v2-build lib:$(project) --enable-profiling $(addprefix --ghc-options ,$(GHC_PROF_OPTIONS)) --write-ghc-environment-files=always
cabal test $(CABAL_TEST_FLAGS) \
--test-show-details always --test-options "$(TEST_OPTIONS) +RTS $(RTS_OPTIONS)" \
- --enable-profiling $(GHC_PROF_OPTIONS) \
+ --enable-profiling $(addprefix --ghc-options ,$(GHC_PROF_OPTIONS)) \
--ghc-options "$(addprefix -opti,+RTS $(RTS_OPTIONS))"
-tests/repl:
- cabal repl $(CABAL_REPL_FLAGS) --enable-tests $(project)-test
-tests/ghcid:
- ghcid $(GHCID_OPTIONS) -c 'cabal repl $(CABAL_REPL_FLAGS) $(project):tests --test-options "$(TEST_OPTIONS)"'
+t/repl tests/repl:
+ cabal repl $(CABAL_REPL_FLAGS) $(CABAL_TEST_FLAGS) --enable-tests $(project)-test
+t/ghcid tests/ghcid:
+ ghcid $(GHCID_OPTIONS) --command 'cabal repl $(CABAL_REPL_FLAGS) $(CABAL_TEST_FLAGS) $(project):tests' --test ":main $(TEST_OPTIONS)"
%/accept: TEST_OPTIONS += --accept
%/accept: %
benchmark :: Benchmark
benchmark = bgroup "Brainfuck" $ List.concat
- [ benchBrainfuck "helloworld"
- , benchBrainfuck "compiler"
+ [ benchBrainfuck "compiler"
, benchBrainfuck "hanoi"
]
},
"nixpkgs": {
"locked": {
- "narHash": "sha256-JenJ8F1xebz8VhfSxUcod1DsR9hRCYG5A+KNSsK5yWs=",
- "path": "/nix/store/fcf9j9allbj8d4qlhq5sr6h8098aa78k-nixpkgs-patched",
+ "narHash": "sha256-r3EoB5BEXlDDDm6zZ571l3GQQTV+ENxis3QQF33WzrQ=",
+ "path": "/nix/store/95j1q84ajdn4ry10rywngn2jhasjjzlz-nixpkgs-patched",
"type": "path"
},
"original": {
]
},
"locked": {
- "lastModified": 1626241645,
- "narHash": "sha256-BYpVYkzNuPmKSLYp9UEqbzTWEDX/Ffd6e4ORhHCI42Y=",
+ "lastModified": 1627373745,
+ "narHash": "sha256-8uWfvRlMdpFdgNS+qVlemxB483rE3SHqIq/umngcWt8=",
"ref": "master",
- "rev": "768058451dc46a32c54e542c1dbbad4983d4a509",
- "revCount": 15,
+ "rev": "23387cfe09e217cc68c2ce2dcaa1436352694739",
+ "revCount": 16,
"type": "git",
"url": "git://git.sourcephile.fr/haskell/symantic-base"
},
lexeme p = p SP.<* whitespace
bf :: repr [Instruction]
bf = SP.many (lexeme (SP.match (SP.look (SP.item @tok))
- (SP.prod . coerceEnum Prelude.<$> "<>+-,.[")
- op SP.empty))
+ (SP.prod . coerceEnum Prelude.<$> "<>+-,.[")
+ op SP.empty))
op :: SP.Production tok -> repr Instruction
op prod = case coerceEnum (SP.runValue prod) of
'<' -> SP.item @tok SP.$> SP.prod Backward
+++ /dev/null
-[Taken from https://esolangs.org/wiki/Brainfuck]
-+++++ +++++ initialize counter (cell #0) to 10
-[ use loop to set the next four cells to 70/100/30/10
- > +++++ ++ add 7 to cell #1
- > +++++ +++++ add 10 to cell #2
- > +++ add 3 to cell #3
- > + add 1 to cell #4
- <<<< - decrement counter (cell #0)
-]
-> ++ . print 'H'
-> + . print 'e'
-+++++ ++ . print 'l'
-. print 'l'
-+++ . print 'o'
-> ++ . print ' '
-<< +++++ +++++ +++++ . print 'W'
-> . print 'o'
-+++ . print 'r'
------ - . print 'l'
------ --- . print 'd'
-> + . print '!'
-> . print '\n'
+++ /dev/null
-++++++++++[>+++++++>++++++++++>+++>+<<<<-]>++.>+.+++++++..+++.>++.<<+++++++++++++++.>.+++.------.--------.>+.>.
, module Symantic.Parser.Grammar.Production
, module Symantic.Parser.Grammar.Write
, module Symantic.Parser.Grammar.View
- , Letable(..)
+ , Referenceable(..)
, Letsable(..)
) where
import Symantic.Parser.Grammar.Combinators
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
--- * Class 'Grammarable'
+-- * Type 'Grammar'
+type Grammar repr = ObserveSharing TH.Name (OptimizeGrammar repr)
+
+-- ** Class 'Grammarable'
type Grammarable tok repr =
( CombAlternable repr
, CombApplicable repr
, CombFoldable repr
- , Letable TH.Name repr
+ , Referenceable TH.Name repr
, Letsable TH.Name repr
, CombLookable repr
, CombMatchable repr
, CombSatisfiable tok repr
, CombSelectable repr
+ --, CombRegisterable repr
+ , CombRegisterableUnscoped repr
, Eq tok
, Ord tok
, TH.Lift tok
-- | A usual pipeline to interpret 'Comb'inators:
-- 'observeSharing' then 'optimizeGrammar' then a polymorphic @(repr)@.
-grammar ::
- Grammarable tok repr =>
- ObserveSharing TH.Name
- (OptimizeGrammar repr) a ->
- repr a
+grammar :: Grammarable tok repr => Grammar repr a -> repr a
grammar = optimizeGrammar . observeSharing
-- | An usual pipeline to show 'Comb'inators:
-- 'observeSharing' then 'optimizeGrammar' then 'viewGrammar' then 'show'.
-showGrammar :: forall showName a tok repr.
- repr ~ ObserveSharing TH.Name (OptimizeGrammar (ViewGrammar showName)) =>
+showGrammar :: forall showName a tok.
ShowLetName showName TH.Name =>
- Grammarable tok repr =>
- repr a -> String
+ Grammarable tok (Grammar (ViewGrammar showName)) =>
+ Grammar (ViewGrammar showName) a -> String
showGrammar = show . viewGrammar . grammar @tok
{-# LANGUAGE DeriveGeneric #-} -- For NFData instances
{-# LANGUAGE DeriveAnyClass #-} -- For NFData instances
{-# LANGUAGE DeriveLift #-} -- For TH.Lift (Exception tok)
+{-# LANGUAGE DerivingStrategies #-} -- For UnscopedRegister
{-# LANGUAGE PatternSynonyms #-} -- For Failure
{-# LANGUAGE StandaloneDeriving #-} -- For Show (Exception (InputToken inp))
{-# LANGUAGE InstanceSigs #-}
import Data.Either (Either(..))
import Data.Eq (Eq(..))
import Data.Ord (Ord(..), Ordering(..))
-import Data.Function ((.), flip, const)
+import Data.Function ((.), flip, const, fix)
import Data.Int (Int)
import Data.Kind (Type, Constraint)
import Data.Maybe (Maybe(..))
-- * Class 'CombFoldable'
class CombFoldable repr where
- chainPre :: repr (a -> a) -> repr a -> repr a
+ chainPre :: repr (a -> a) -> repr a -> repr a
chainPost :: repr a -> repr (a -> a) -> repr a
- {-
+ chainPre = liftDerived2 chainPre
+ chainPost = liftDerived2 chainPost
default chainPre ::
FromDerived2 CombFoldable repr =>
repr (a -> a) -> repr a -> repr a
default chainPost ::
FromDerived2 CombFoldable repr =>
repr a -> repr (a -> a) -> repr a
- chainPre = liftDerived2 chainPre
- chainPost = liftDerived2 chainPost
- -}
+ {-
default chainPre ::
CombApplicable repr =>
CombAlternable repr =>
repr a -> repr (a -> a) -> repr a
chainPre op p = go <*> p where go = (Prod..) <$> op <*> go <|> pure Prod.id
chainPost p op = p <**> go where go = (Prod..) <$> op <*> go <|> pure Prod.id
+ -}
{-
chainPre op p = flip (foldr ($)) <$> many op <*> p
chainPost p op = foldl' (flip ($)) <$> p <*> many op
-- * Class 'CombMatchable'
class CombMatchable repr where
conditional ::
- Eq a => repr a -> [Production (a -> Bool)] -> [repr b] -> repr b -> repr b
+ repr a -> [(Production (a -> Bool), repr b)] -> repr b -> repr b
+ conditional a bs = liftDerived1
+ (conditional (derive a) ((\(p,b) -> (p, derive b)) Functor.<$> bs))
default conditional ::
FromDerived1 CombMatchable repr => Derivable repr =>
- Eq a => repr a -> [Production (a -> Bool)] -> [repr b] -> repr b -> repr b
- conditional a ps bs = liftDerived1 (conditional (derive a) ps (derive Functor.<$> bs))
-
- match :: Eq a => repr a -> [Production a] -> (Production a -> repr b) -> repr b -> repr b
- match a as a2b = conditional a ((Prod.equal Prod..@) Functor.<$> as) (a2b Functor.<$> as)
- -- match a as a2b = conditional a (((Prod.eq Prod..@ Prod.qual) Prod..@) Functor.<$> as) (a2b Functor.<$> as)
+ repr a -> [(Production (a -> Bool), repr b)] -> repr b -> repr b
data instance Failure CombMatchable
+match ::
+ CombMatchable repr =>
+ Eq a => TH.Lift a =>
+ repr a -> [Production a] -> (Production a -> repr b) -> repr b -> repr b
+match a as p = conditional a
+ ((\v ->
+ ( Prod.lam (\x -> (Prod.==) Prod..@ v Prod..@ x)
+ , p v
+ )
+ ) Functor.<$> as)
+
+predicate ::
+ CombMatchable repr =>
+ Production (a -> Bool) -> repr a -> repr b -> repr b -> repr b
+predicate p a b d = conditional a [(p, b)] d
+
+infixl 4 <?:>
+(<?:>) ::
+ CombMatchable repr =>
+ repr Bool -> (repr a, repr a) -> repr a
+cond <?:> (p, q) = predicate Prod.id cond p q
+
-- * Class 'CombSatisfiable'
class CombSatisfiable tok repr where
-- | Like 'satisfyOrFail' but with no custom failure.
branch = liftDerived3 branch
data instance Failure CombSelectable
+when ::
+ CombMatchable repr =>
+ CombSelectable repr =>
+ Prod.Constantable () repr =>
+ repr Bool -> repr () -> repr ()
+when p q = p <?:> (q, Prod.unit)
+
+while ::
+ CombMatchable repr =>
+ CombSelectable repr =>
+ Prod.Constantable () repr =>
+ repr Bool -> repr ()
+while x = fix (when x)
+
-- * Class 'CombLookable'
class CombLookable repr where
look :: repr a -> repr a
instance CombLookable repr => CombLookable (Sym.Any repr)
instance CombFoldable repr => CombFoldable (Sym.Any repr)
-}
+
+-- * Type 'Register'
+newtype Register r a = Register { unRegister :: UnscopedRegister a }
+ deriving (Eq, Show)
+
+-- ** Type 'UnscopedRegister'
+newtype UnscopedRegister r = UnscopedRegister { unUnscopedRegister :: TH.Name }
+ deriving (Eq)
+ deriving newtype Show
+
+
+{-
+put_ :: ParserOps rep => Register r a -> rep a -> Parser ()
+put_ r = put r . pure
+
+gets_ :: ParserOps rep => Register r a -> rep (a -> b) -> Parser b
+gets_ r = gets r . pure
+
+modify_ :: ParserOps rep => Register r a -> rep (a -> a) -> Parser ()
+modify_ r = modify r . pure
+-}
+
+gets ::
+ CombApplicable repr =>
+ CombRegisterable repr =>
+ Register r a -> repr (a -> b) -> repr b
+gets r p = p <*> get r
+
+modify ::
+ CombApplicable repr =>
+ CombRegisterable repr =>
+ Register r a -> repr (a -> a) -> repr ()
+modify r p = put r (gets r p)
+
+move ::
+ CombRegisterable repr =>
+ Register r1 a -> Register r2 a -> repr ()
+move dst src = put dst (get src)
+
+bind ::
+ CombRegisterable repr =>
+ repr a -> (repr a -> repr b) -> repr b
+bind p f = new p (f . get)
+
+local ::
+ CombApplicable repr =>
+ CombRegisterable repr =>
+ Register r a -> repr a -> repr b -> repr b
+local r p q = bind (get r) (\x -> put r p *> q <* put r x)
+
+swap ::
+ CombApplicable repr =>
+ CombRegisterable repr =>
+ Register r1 a -> Register r2 a -> repr ()
+swap r1 r2 = bind (get r1) (\x -> move r1 r2 *> put r2 x)
+
+rollback ::
+ CombAlternable repr =>
+ CombApplicable repr =>
+ CombRegisterable repr =>
+ Register r a -> repr b -> repr b
+rollback r p = bind (get r) (\x -> p <|> put r x *> empty)
+
+for ::
+ CombApplicable repr =>
+ CombMatchable repr =>
+ CombSelectable repr =>
+ CombRegisterable repr =>
+ Prod.Constantable () repr =>
+ repr a -> repr (a -> Bool) -> repr (a -> a) -> repr () -> repr ()
+for init cond step body =
+ new init (\i ->
+ let cond' = gets i cond in
+ when cond' (while (body *> modify i step *> cond'))
+ )
+
+
+-- ** Class 'CombRegisterable'
+class CombRegisterable (repr::ReprComb) where
+ new :: repr a -> (forall r. Register r a -> repr b) -> repr b
+ get :: Register r a -> repr a
+ put :: Register r a -> repr a -> repr ()
+ default new ::
+ FromDerived CombRegisterable repr => Derivable repr =>
+ repr a -> (forall r. Register r a -> repr b) -> repr b
+ default get ::
+ FromDerived CombRegisterable repr =>
+ Register r a -> repr a
+ default put ::
+ FromDerived1 CombRegisterable repr =>
+ Register r a -> repr a -> repr ()
+ new ini f = liftDerived (new (derive ini) (derive . f))
+ get = liftDerived . get
+ put = liftDerived1 . put
+{-# LANGUAGE DefaultSignatures #-}
+{-# LANGUAGE TupleSections #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Symantic.Parser.Grammar.ObserveSharing
( module Symantic.ObserveSharing
, module Symantic.Parser.Grammar.ObserveSharing
) where
-import Control.Monad (mapM)
-import Data.Function (($), (.))
+import Control.Monad (Monad(..), mapM)
+import Data.Function (($), (.), id)
import Data.Hashable (Hashable, hashWithSalt)
+import System.IO (IO)
import Text.Show (Show(..))
-import qualified Control.Applicative as Functor
+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'
makeLetName _ = TH.qNewName "name"
-- Combinators semantics for the 'ObserveSharing' interpreter.
-instance (Letable TH.Name repr, CombAlternable repr) =>
- CombAlternable (ObserveSharing TH.Name repr)
-instance (Letable TH.Name repr, CombApplicable repr) =>
- CombApplicable (ObserveSharing TH.Name repr)
instance
- ( Letable TH.Name repr
- , CombFoldable repr
- {- TODO: the following constraints are for the current CombFoldable,
- - they will have to be removed when CombFoldable will have 'liftDerived2' as defaults
- -}
- , CombApplicable repr
+ ( Referenceable TH.Name repr
, CombAlternable repr
+ ) => CombAlternable (ObserveSharing TH.Name repr)
+instance
+ ( Referenceable TH.Name repr
+ , CombApplicable repr
+ ) => CombApplicable (ObserveSharing TH.Name repr)
+instance
+ ( Referenceable TH.Name repr
+ , CombFoldable repr
) => CombFoldable (ObserveSharing TH.Name repr)
-instance (Letable TH.Name repr, CombLookable repr) =>
- CombLookable (ObserveSharing TH.Name repr)
-instance (Letable TH.Name repr, CombMatchable repr) =>
- CombMatchable (ObserveSharing TH.Name repr) where
+instance
+ ( Referenceable TH.Name repr
+ , CombLookable repr
+ ) => CombLookable (ObserveSharing TH.Name repr)
+instance
+ ( Referenceable TH.Name repr
+ , CombMatchable repr
+ ) => CombMatchable (ObserveSharing TH.Name repr) where
-- Here the default definition does not fit
-- since there is no liftDerived* for the type of 'conditional'
-- and its default definition does not handles 'bs'
-- as needed by the 'ObserveSharing' interpreter.
- conditional a cs bs b = observeSharingNode $ ObserveSharing $
- conditional
- Functor.<$> unObserveSharing a
- Functor.<*> Functor.pure cs
- Functor.<*> mapM unObserveSharing bs
- Functor.<*> unObserveSharing b
-instance (Letable TH.Name repr, CombSelectable repr) =>
- CombSelectable (ObserveSharing TH.Name repr)
-instance (Letable TH.Name repr, CombSatisfiable tok repr) =>
- CombSatisfiable tok (ObserveSharing TH.Name repr)
+ conditional a bs d = observeSharingNode $ ObserveSharing $ conditional
+ F.<$> unObserveSharing a
+ F.<*> mapM (\(p, b) -> (p,) F.<$> unObserveSharing b) bs
+ F.<*> unObserveSharing d
+instance
+ ( Referenceable TH.Name repr
+ , CombSelectable repr
+ ) => CombSelectable (ObserveSharing TH.Name repr)
+instance
+ ( Referenceable TH.Name repr
+ , CombSatisfiable tok repr
+ ) => CombSatisfiable tok (ObserveSharing TH.Name repr)
+instance
+ ( Referenceable TH.Name repr
+ , CombRegisterableUnscoped repr
+ ) => CombRegisterable (ObserveSharing TH.Name repr) where
+ new ini f =
+ -- 'unsafePerformIO' is used here because propagating 'IO'
+ -- would prevent 'observeSharing' to recognize recursive let,
+ -- causing an infinite loop on them.
+ let !regName = unsafePerformIO $ TH.newName "reg" in
+ let reg = UnscopedRegister regName in
+ newUnscoped reg ini (f (Register reg))
+ get = getUnscoped . unRegister
+ put reg x = putUnscoped (unRegister reg) x
+instance
+ ( Referenceable TH.Name repr
+ , CombRegisterableUnscoped repr
+ ) => CombRegisterableUnscoped (ObserveSharing TH.Name repr)
+
+-- * Class 'CombRegisterableUnscoped'
+-- | These combinators are used to remove the @Rank2Types@ from 'CombRegisterable'
+-- in order to be able to 'observeSharing'.
+class CombRegisterableUnscoped (repr::ReprComb) where
+ newUnscoped :: UnscopedRegister a -> repr a -> repr b -> repr b
+ getUnscoped :: UnscopedRegister a -> repr a
+ putUnscoped :: UnscopedRegister a -> repr a -> repr ()
+ default newUnscoped ::
+ FromDerived2 CombRegisterableUnscoped repr =>
+ UnscopedRegister a -> repr a -> repr b -> repr b
+ default getUnscoped ::
+ FromDerived CombRegisterableUnscoped repr =>
+ UnscopedRegister a -> repr a
+ default putUnscoped ::
+ FromDerived1 CombRegisterableUnscoped repr =>
+ UnscopedRegister a -> repr a -> repr ()
+ newUnscoped = liftDerived2 . newUnscoped
+ getUnscoped = liftDerived . getUnscoped
+ putUnscoped = liftDerived1 . putUnscoped
-- Combinators semantics for the 'FinalizeSharing' interpreter.
-instance CombApplicable repr => CombApplicable (FinalizeSharing TH.Name repr)
-instance CombAlternable repr => CombAlternable (FinalizeSharing TH.Name repr)
-instance CombFoldable repr => CombFoldable (FinalizeSharing TH.Name repr) where
- chainPre = liftDerived2 chainPre
- chainPost = liftDerived2 chainPost
-instance CombLookable repr => CombLookable (FinalizeSharing TH.Name repr)
-instance CombMatchable repr => CombMatchable (FinalizeSharing TH.Name repr) where
- conditional a cs bs b = FinalizeSharing $
- conditional
- Functor.<$> unFinalizeSharing a
- Functor.<*> Functor.pure cs
- Functor.<*> mapM unFinalizeSharing bs
- Functor.<*> unFinalizeSharing b
-instance CombSatisfiable tok repr => CombSatisfiable tok (FinalizeSharing TH.Name repr)
-instance CombSelectable repr => CombSelectable (FinalizeSharing TH.Name repr)
+instance
+ ( CombApplicable repr
+ ) => CombApplicable (FinalizeSharing TH.Name repr)
+instance
+ ( CombAlternable repr
+ ) => CombAlternable (FinalizeSharing TH.Name repr)
+instance
+ ( CombFoldable repr
+ ) => CombFoldable (FinalizeSharing TH.Name repr)
+instance
+ ( CombLookable repr
+ ) => CombLookable (FinalizeSharing TH.Name repr)
+instance
+ ( CombMatchable repr
+ ) => CombMatchable (FinalizeSharing TH.Name repr) where
+ conditional a bs d = FinalizeSharing $ conditional
+ F.<$> unFinalizeSharing a
+ F.<*> mapM (\(p, b) -> (p,) F.<$> unFinalizeSharing b) bs
+ F.<*> unFinalizeSharing d
+instance
+ ( CombSatisfiable tok repr
+ ) => CombSatisfiable tok (FinalizeSharing TH.Name repr)
+instance
+ ( CombSelectable repr
+ ) => CombSelectable (FinalizeSharing TH.Name repr)
+instance
+ ( CombRegisterableUnscoped repr
+ ) => CombRegisterableUnscoped (FinalizeSharing TH.Name repr)
+
+-- | Ties the knot between mutually recursive 'TH.Name's
+-- introduced by 'defLet' and 'defJoin'.
+-- and provide the empty initial 'CallTrace' stack
+runOpenRecs :: OpenRecs letName (CallTrace -> a) -> LetRecs letName a
+runOpenRecs ga = (($ []) F.<$>) (mutualFix ga)
+
+-- | Call trace stack updated by 'call' and 'refJoin'.
+-- Used to avoid infinite loops when tying the knot with 'polyfix'.
+type CallTrace = [TH.Name]
{-# LANGUAGE PatternSynonyms #-} -- For Comb
{-# LANGUAGE TemplateHaskell #-} -- For branch
-{-# LANGUAGE ViewPatterns #-} -- For unSomeComb
+{-# LANGUAGE ViewPatterns #-} -- For unSimplComb
{-# OPTIONS_GHC -fno-warn-orphans #-} -- For MakeLetName TH.Name
-- | Bottom-up optimization of 'Comb'inators,
-- reexamining downward as needed after each optimization.
module Symantic.Parser.Grammar.Optimize where
-import Data.Bool (Bool(..))
+import Data.Bool (Bool(..), (&&), not)
import Data.Either (Either(..), either)
import Data.Eq (Eq(..))
import Data.Function (($), (.))
import Data.Set (Set)
import Data.Functor.Identity (Identity(..))
import Data.Functor.Product (Product(..))
+import Unsafe.Coerce (unsafeCoerce)
import Type.Reflection (Typeable, typeRep, eqTypeRep, (:~~:)(..))
+import Data.Semigroup (Semigroup(..))
import qualified Data.Foldable as Foldable
-import qualified Data.Functor as Functor
-import qualified Data.List as List
+import qualified Data.Functor as F
+import qualified Data.HashMap.Strict as HM
+import qualified Data.HashSet as HS
+import Data.Hashable (Hashable)
+import qualified Language.Haskell.TH as TH
import Symantic.Parser.Grammar.Combinators
import Symantic.Parser.Grammar.Production
+import Symantic.Parser.Grammar.ObserveSharing hiding (def)
import Symantic.Derive
-import Symantic.ObserveSharing
import qualified Symantic.Data as Prod
import qualified Symantic.Lang as Prod
(&) = flip ($)
infix 0 &
-}
+type OptimizeGrammar = KnotComb TH.Name
--- * Type 'OptimizeGrammar'
-type OptimizeGrammar = SomeComb
+-- | TODO: remove useless wrapping?
+newtype TiedComb repr a = TiedComb
+ { combSimpl :: SimplComb repr a
+ --, combRefs :: HS.HashSet letName
+ }
+
+-- * Type 'KnotComb'
+data KnotComb letName repr a = KnotComb
+ { knotCombOpens :: OpenRecs letName (SomeLet (TiedComb repr))
+ -- ^ 'TiedComb' for all 'letName' in 'lets'.
+ , knotCombOpen ::
+ LetRecs letName (SomeLet (TiedComb repr)) ->
+ TiedComb repr a
+ -- ^ 'TiedComb' of the current combinator,
+ -- with access to the final 'knotCombOpens'.
+ }
optimizeGrammar ::
- Derivable (SomeComb repr) =>
- SomeComb repr a -> repr a
-optimizeGrammar = derive
+ Derivable (SimplComb repr) =>
+ KnotComb TH.Name repr a -> repr a
+optimizeGrammar = derive . derive
+
+type instance Derived (KnotComb letName repr) = SimplComb repr
+instance Derivable (KnotComb letName repr) where
+ derive opt = combSimpl $
+ knotCombOpen opt (mutualFix (knotCombOpens opt))
+instance LiftDerived (KnotComb letName repr) where
+ liftDerived x = KnotComb
+ { knotCombOpens = HM.empty
+ , knotCombOpen = \finals -> TiedComb
+ { combSimpl = x
+ }
+ }
+instance LiftDerived1 (KnotComb letName repr) where
+ liftDerived1 f a = a
+ { knotCombOpen = \finals -> TiedComb
+ { combSimpl = f (combSimpl (knotCombOpen a finals))
+ }
+ }
+instance (Eq letName, Hashable letName) => LiftDerived2 (KnotComb letName repr) where
+ liftDerived2 f a b = KnotComb
+ { knotCombOpens = knotCombOpens a <> knotCombOpens b
+ , knotCombOpen = \finals -> TiedComb
+ { combSimpl = f
+ (combSimpl (knotCombOpen a finals))
+ (combSimpl (knotCombOpen b finals))
+ }
+ }
+instance (Eq letName, Hashable letName) => LiftDerived3 (KnotComb letName repr) where
+ liftDerived3 f a b c = KnotComb
+ { knotCombOpens = HM.unions
+ [ knotCombOpens a
+ , knotCombOpens b
+ , knotCombOpens c
+ ]
+ , knotCombOpen = \finals -> TiedComb
+ { combSimpl = f
+ (combSimpl (knotCombOpen a finals))
+ (combSimpl (knotCombOpen b finals))
+ (combSimpl (knotCombOpen c finals))
+ }
+ }
+instance (Eq letName, Hashable letName) => LiftDerived4 (KnotComb letName repr) where
+ liftDerived4 f a b c d = KnotComb
+ { knotCombOpens = HM.unions
+ [ knotCombOpens a
+ , knotCombOpens b
+ , knotCombOpens c
+ , knotCombOpens d
+ ]
+ , knotCombOpen = \finals -> TiedComb
+ { combSimpl = f
+ (combSimpl (knotCombOpen a finals))
+ (combSimpl (knotCombOpen b finals))
+ (combSimpl (knotCombOpen c finals))
+ (combSimpl (knotCombOpen d finals))
+ }
+ }
-- * Data family 'Comb'
-- | 'Comb'inators of the 'Grammar'.
:: ReprComb -> ReprComb
type instance Derived (Comb comb repr) = repr
--- | Convenient utility to pattern-match a 'SomeComb'.
-pattern Comb :: Typeable comb => Comb comb repr a -> SomeComb repr a
-pattern Comb x <- (unSomeComb -> Just x)
+-- | 'unsafeCoerce' restrained to 'SimplComb'.
+-- Useful to avoid dependant-map when inlining.
+unsafeSimplComb :: SimplComb repr a -> SimplComb repr b
+unsafeSimplComb = unsafeCoerce
--- ** Type 'SomeComb'
--- | Some 'Comb'inator existentialized over the actual combinator symantic class.
+-- | Convenient utility to pattern-match a 'SimplComb'.
+pattern Comb :: Typeable comb => Comb comb repr a -> SimplComb repr a
+pattern Comb x <- (unSimplComb -> Just x)
+
+-- ** Type 'SimplComb'
+-- | Interpreter simplifying combinators.
-- Useful to handle a list of 'Comb'inators
-- without requiring impredicative quantification.
-- Must be used by pattern-matching
--- on the 'SomeComb' data-constructor,
+-- on the 'SimplComb' data-constructor,
-- to bring the constraints in scope.
--
-- The optimizations are directly applied within it,
-- to avoid introducing an extra newtype,
-- this also give a more understandable code.
-data SomeComb repr a =
+data SimplComb repr a =
forall comb.
(Derivable (Comb comb repr), Typeable comb) =>
- SomeComb (Comb comb repr a)
+ SimplComb
+ { combData :: Comb comb repr a
+ -- ^ Some 'Comb'inator existentialized
+ -- over the actual combinator symantic class.
+ , combInline :: Bool
+ -- ^ Whether this combinator must be inlined
+ -- in place of a 'ref'erence pointing to it
+ -- (instead of generating a 'call').
+ , combRefs :: HS.HashSet TH.Name
+ -- ^ 'ref''s names reacheable from combinator
+ -- (including those behind 'ref's).
+ }
-type instance Derived (SomeComb repr) = repr
-instance Derivable (SomeComb repr) where
- derive (SomeComb x) = derive x
+type instance Derived (SimplComb repr) = repr
+instance Derivable (SimplComb repr) where
+ derive SimplComb{..} = derive combData
--- | @(unSomeComb c :: 'Maybe' ('Comb' comb repr a))@
--- extract the data-constructor from the given 'SomeComb'
+-- | @(unSimplComb c :: 'Maybe' ('Comb' comb repr a))@
+-- extract the data-constructor from the given 'SimplComb'
-- iif. it belongs to the @('Comb' comb repr a)@ data-instance.
-unSomeComb ::
+unSimplComb ::
forall comb repr a.
Typeable comb =>
- SomeComb repr a -> Maybe (Comb comb repr a)
-unSomeComb (SomeComb (c::Comb c repr a)) =
+ SimplComb repr a -> Maybe (Comb comb repr a)
+unSimplComb SimplComb{ combData = c :: Comb c repr a } =
case typeRep @comb `eqTypeRep` typeRep @c of
Just HRefl -> Just c
Nothing -> Nothing
-- CombAlternable
data instance Comb CombAlternable repr a where
- Alt :: Exception -> SomeComb repr a -> SomeComb repr a -> Comb CombAlternable repr a
+ Alt :: Exception -> SimplComb repr a -> SimplComb repr a -> Comb CombAlternable repr a
Empty :: Comb CombAlternable repr a
Failure :: SomeFailure -> Comb CombAlternable repr a
Throw :: ExceptionLabel -> Comb CombAlternable repr a
- Try :: SomeComb repr a -> Comb CombAlternable repr a
+ Try :: SimplComb repr a -> Comb CombAlternable repr a
instance CombAlternable repr => Derivable (Comb CombAlternable repr) where
derive = \case
Alt exn x y -> alt exn (derive x) (derive y)
, CombLookable repr
, CombMatchable repr
, CombSelectable repr
- ) => CombAlternable (SomeComb repr) where
- empty = SomeComb Empty
- failure sf = SomeComb (Failure sf)
+ ) => CombAlternable (SimplComb repr) where
+ empty = SimplComb
+ { combData = Empty
+ , combInline = True
+ , combRefs = HS.empty
+ }
+ failure sf = SimplComb
+ { combData = Failure sf
+ , combInline = True
+ , combRefs = HS.empty
+ }
alt _exn p@(Comb Pure{}) _ = p
-- & trace "Left Catch Law"
-- & trace "Associativity Law"
alt exn (Comb (Look p)) (Comb (Look q)) = look (alt exn (try p) q)
-- & trace "Distributivity Law"
- alt exn x y = SomeComb (Alt exn x y)
+ alt exn x y = SimplComb
+ { combData = Alt exn x y
+ , combInline = False
+ , combRefs = combRefs x <> combRefs y
+ }
- throw exn = SomeComb (Throw exn)
+ throw exn = SimplComb
+ { combData = Throw exn
+ , combInline = True
+ , combRefs = HS.empty
+ }
try (Comb (p :$>: x)) = try p $> x
-- & trace "Try Interchange Law"
try (Comb (f :<$>: p)) = f <$> try p
-- & trace "Try Interchange Law"
- try x = SomeComb (Try x)
+ try x = SimplComb
+ { combData = Try x
+ , combInline = False
+ , combRefs = combRefs x
+ }
+instance
+ ( CombApplicable repr
+ , CombAlternable repr
+ , CombLookable repr
+ , CombMatchable repr
+ , CombSelectable repr
+ , Eq letName
+ , Hashable letName
+ ) => CombAlternable (KnotComb letName repr)
-- CombApplicable
data instance Comb CombApplicable repr a where
Pure :: Production a -> Comb CombApplicable repr a
- (:<*>:) :: SomeComb repr (a -> b) -> SomeComb repr a -> Comb CombApplicable repr b
- (:<*:) :: SomeComb repr a -> SomeComb repr b -> Comb CombApplicable repr a
- (:*>:) :: SomeComb repr a -> SomeComb repr b -> Comb CombApplicable repr b
+ (:<*>:) :: SimplComb repr (a -> b) -> SimplComb repr a -> Comb CombApplicable repr b
+ (:<*:) :: SimplComb repr a -> SimplComb repr b -> Comb CombApplicable repr a
+ (:*>:) :: SimplComb repr a -> SimplComb repr b -> Comb CombApplicable repr b
infixl 4 :<*>:, :<*:, :*>:
-pattern (:<$>:) :: Production (a -> b) -> SomeComb repr a -> Comb CombApplicable repr b
+pattern (:<$>:) :: Production (a -> b) -> SimplComb repr a -> Comb CombApplicable repr b
pattern t :<$>: x <- Comb (Pure t) :<*>: x
-pattern (:$>:) :: SomeComb repr a -> Production b -> Comb CombApplicable repr b
+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
, CombLookable repr
, CombMatchable repr
, CombSelectable repr
- ) => CombApplicable (SomeComb repr) where
- pure = SomeComb . Pure
+ ) => CombApplicable (SimplComb repr) where
+ pure a = SimplComb
+ { combData = Pure a
+ , combInline = False -- TODO: maybe True?
+ , combRefs = HS.empty
+ }
f <$> Comb (Branch b l r) =
branch b
((Prod..) Prod..@ f <$> l)
((Prod..) Prod..@ f <$> r)
-- & trace "Branch Distributivity Law"
- f <$> Comb (Conditional a ps bs d) =
- conditional a ps
- ((f <$>) Functor.<$> bs)
- (f <$> d)
+ f <$> Comb (Conditional a bs def) =
+ conditional a
+ ((\(p, b) -> (p, f <$> b)) F.<$> bs)
+ (f <$> def)
-- & trace "Conditional Distributivity Law"
-- Being careful here to use (<*>),
- -- instead of SomeComb (f <$> unOptComb x),
+ -- instead of SimplComb { combData = f <$> combData x },
-- in order to apply the optimizations of (<*>).
f <$> x = pure f <*> x
p <*> Comb (NegLook q) =
(p <*> pure Prod.unit) <* negLook q
-- & trace "Absorption Law"
- x <*> y = SomeComb (x :<*>: y)
+ x <*> y = SimplComb
+ { combData = x :<*>: y
+ , combInline = False
+ , combRefs = combRefs x <> combRefs y
+ }
Comb Empty *> _ = empty
-- & trace "App Right Absorption Law"
-- & trace "Identity Law"
u *> Comb (v :*>: w) = (u *> v) *> w
-- & trace "Associativity Law"
- x *> y = SomeComb (x :*>: y)
+ x *> y = SimplComb
+ { combData = x :*>: y
+ , combInline = False
+ , combRefs = combRefs x <> combRefs y
+ }
Comb Empty <* _ = empty
-- & trace "App Right Absorption Law"
-- & trace "Identity Law"
Comb (u :<*: v) <* w = u <* (v <* w)
-- & trace "Associativity Law"
- x <* y = SomeComb (x :<*: y)
+ x <* y = SimplComb
+ { combData = x :<*: y
+ , combInline = False
+ , combRefs = combRefs x <> combRefs y
+ }
+instance
+ ( CombApplicable repr
+ , CombAlternable repr
+ , CombLookable repr
+ , CombMatchable repr
+ , CombSelectable repr
+ , Eq letName
+ , Hashable letName
+ ) => CombApplicable (KnotComb letName repr)
-- CombFoldable
data instance Comb CombFoldable repr a where
- ChainPreC :: SomeComb repr (a -> a) -> SomeComb repr a -> Comb CombFoldable repr a
- ChainPostC :: SomeComb repr a -> SomeComb repr (a -> a) -> Comb CombFoldable repr a
+ ChainPre :: SimplComb repr (a -> a) -> SimplComb repr a -> Comb CombFoldable repr a
+ ChainPost :: SimplComb repr a -> SimplComb repr (a -> a) -> Comb CombFoldable repr a
instance CombFoldable repr => Derivable (Comb CombFoldable repr) where
derive = \case
- ChainPreC x y -> chainPre (derive x) (derive y)
- ChainPostC x y -> chainPost (derive x) (derive y)
-instance CombFoldable repr => CombFoldable (SomeComb repr) where
- chainPre x = SomeComb . ChainPreC x
- chainPost x = SomeComb . ChainPostC x
-
--- Letable
-data instance Comb (Letable letName) repr a where
- Shareable :: letName -> SomeComb repr a -> Comb (Letable letName) repr a
- Ref :: Bool -> letName -> Comb (Letable letName) repr a
+ ChainPre op p -> chainPre (derive op) (derive p)
+ ChainPost p op -> chainPost (derive p) (derive op)
+instance CombFoldable repr => CombFoldable (SimplComb repr) where
+ chainPre op p = SimplComb
+ { combData = ChainPre op p
+ , combInline = False
+ , combRefs = combRefs op <> combRefs p
+ }
+ chainPost p op = SimplComb
+ { combData = ChainPost p op
+ , combInline = False
+ , combRefs = combRefs p <> combRefs op
+ }
instance
- Letable letName repr =>
- Derivable (Comb (Letable letName) repr) where
- derive = \case
- Shareable n x -> shareable n (derive x)
- Ref isRec n -> ref isRec n
-instance
- (Letable letName repr, Typeable letName) =>
- Letable letName (SomeComb repr) where
- shareable n = SomeComb . Shareable n
- ref isRec = SomeComb . Ref isRec
-
--- Letsable
-data instance Comb (Letsable letName) repr a where
- Lets :: LetBindings letName (SomeComb repr) ->
- SomeComb repr a -> Comb (Letsable letName) repr a
-instance
- Letsable letName repr =>
- Derivable (Comb (Letsable letName) repr) where
- derive = \case
- Lets defs x -> lets ((\(SomeLet sub) -> SomeLet (derive sub)) Functor.<$> defs) (derive x)
-instance
- (Letsable letName repr, Typeable letName) =>
- Letsable letName (SomeComb repr) where
- lets defs = SomeComb . Lets defs
+ ( CombFoldable repr
+ , Eq letName
+ , Hashable letName
+ ) => CombFoldable (KnotComb letName repr)
-- CombLookable
data instance Comb CombLookable repr a where
- Look :: SomeComb repr a -> Comb CombLookable repr a
- NegLook :: SomeComb repr a -> Comb CombLookable repr ()
+ Look :: SimplComb repr a -> Comb CombLookable repr a
+ NegLook :: SimplComb repr a -> Comb CombLookable repr ()
Eof :: Comb CombLookable repr ()
instance CombLookable repr => Derivable (Comb CombLookable repr) where
derive = \case
, CombLookable repr
, CombSelectable repr
, CombMatchable repr
- ) => CombLookable (SomeComb repr) where
+ ) => CombLookable (SimplComb repr) where
look p@(Comb Pure{}) = p
-- & trace "Pure Look Law"
look p@(Comb Empty) = p
-- & trace "Interchange Law"
look (Comb (f :<$>: p)) = f <$> look p
-- & trace "Interchange Law"
- look x = SomeComb (Look x)
+ look x = SimplComb
+ { combData = Look x
+ , combInline = False
+ , combRefs = combRefs x
+ }
negLook (Comb Pure{}) = empty
-- & trace "Pure Negative-Look"
-- & trace "Transparency Law"
negLook (Comb (p :$>: _)) = negLook p
-- & trace "NegLook Idempotence Law"
- negLook x = SomeComb (NegLook x)
+ negLook x = SimplComb
+ { combData = NegLook x
+ , combInline = False
+ , combRefs = combRefs x
+ }
- eof = SomeComb Eof
+ eof = SimplComb
+ { combData = Eof
+ , combInline = True
+ , combRefs = HS.empty
+ }
+instance
+ ( CombLookable repr
+ , CombAlternable repr
+ , CombApplicable repr
+ , CombSelectable repr
+ , CombMatchable repr
+ , Eq letName
+ , Hashable letName
+ ) => CombLookable (KnotComb letName repr)
-- CombMatchable
data instance Comb CombMatchable repr a where
- Conditional :: Eq a =>
- SomeComb repr a ->
- [Production (a -> Bool)] ->
- [SomeComb repr b] ->
- SomeComb repr b ->
+ Conditional ::
+ SimplComb repr a ->
+ [(Production (a -> Bool), SimplComb repr b)] ->
+ SimplComb repr b ->
Comb CombMatchable repr b
instance CombMatchable repr => Derivable (Comb CombMatchable repr) where
derive = \case
- Conditional a ps bs b ->
+ Conditional a bs def ->
conditional (derive a)
- (optimizeProduction Functor.<$> ps)
- (derive Functor.<$> bs) (derive b)
+ ((\(p, b) -> (optimizeProduction p, derive b)) F.<$> bs)
+ (derive def)
instance
( CombApplicable repr
, CombAlternable repr
, CombLookable repr
, CombSelectable repr
, CombMatchable repr
- ) => CombMatchable (SomeComb repr) where
- conditional (Comb Empty) _ _ d = d
+ ) => CombMatchable (SimplComb repr) where
+ conditional (Comb Empty) _ def = def
-- & trace "Conditional Absorption Law"
- conditional p _ qs (Comb Empty)
- | Foldable.all (\case { Comb Empty -> True; _ -> False }) qs = p *> empty
+ conditional a bs (Comb Empty)
+ | Foldable.all (\case { (_, Comb Empty) -> True; _ -> False }) bs = a *> empty
-- & trace "Conditional Weakening Law"
- conditional a _ps bs (Comb Empty)
- | Foldable.all (\case { Comb Empty -> True; _ -> False }) bs = a *> empty
- -- & trace "Conditional Weakening Law"
- conditional (Comb (Pure a)) ps bs d =
- Foldable.foldr (\(p, b) next ->
- if runValue (p Prod..@ a) then b else next
- ) d (List.zip ps bs)
+ conditional (Comb (Pure a)) bs def =
+ Foldable.foldr (\(p, b) acc ->
+ if runValue (p Prod..@ a) then b else acc
+ ) def bs
-- & trace "Conditional Pure Law"
- conditional a ps bs d = SomeComb (Conditional a ps bs d)
+ conditional a bs d = SimplComb
+ { combData = Conditional a bs d
+ , combInline = False
+ , combRefs = HS.unions
+ $ combRefs a
+ : combRefs d
+ : ((\(_p, b) -> combRefs b) F.<$> bs)
+ }
+instance
+ ( CombMatchable repr
+ , CombAlternable repr
+ , CombApplicable repr
+ , CombLookable repr
+ , CombSelectable repr
+ , Eq letName
+ , Hashable letName
+ ) => CombMatchable (KnotComb letName repr) where
+ conditional a bs d = KnotComb
+ { knotCombOpens = HM.unions
+ $ knotCombOpens a
+ : knotCombOpens d
+ : ((\(_p, b) -> knotCombOpens b) F.<$> bs)
+ , knotCombOpen = \finals -> TiedComb
+ { combSimpl = conditional
+ (combSimpl (knotCombOpen a finals))
+ ((\(p, b) -> (p, combSimpl (knotCombOpen b finals))) F.<$> bs)
+ (combSimpl (knotCombOpen d finals))
+ }
+ }
-- CombSatisfiable
data instance Comb (CombSatisfiable tok) repr a where
SatisfyOrFail fs p -> satisfyOrFail fs (optimizeProduction p)
instance
(CombSatisfiable tok repr, Typeable tok) =>
- CombSatisfiable tok (SomeComb repr) where
- satisfyOrFail fs = SomeComb . SatisfyOrFail fs
+ CombSatisfiable tok (SimplComb repr) where
+ satisfyOrFail fs p = SimplComb
+ { combData = SatisfyOrFail fs p
+ , combInline = False -- TODO: True? depending on p?
+ , combRefs = HS.empty
+ }
+instance
+ ( CombSatisfiable tok repr
+ , Typeable tok
+ , Eq letName
+ , Hashable letName
+ ) => CombSatisfiable tok (KnotComb letName repr)
-- CombSelectable
data instance Comb CombSelectable repr a where
Branch ::
- SomeComb repr (Either a b) ->
- SomeComb repr (a -> c) ->
- SomeComb repr (b -> c) ->
+ SimplComb repr (Either a b) ->
+ SimplComb repr (a -> c) ->
+ SimplComb repr (b -> c) ->
Comb CombSelectable repr c
instance CombSelectable repr => Derivable (Comb CombSelectable repr) where
derive = \case
, CombLookable repr
, CombSelectable repr
, CombMatchable repr
- ) => CombSelectable (SomeComb repr) where
+ ) => CombSelectable (SimplComb repr) where
branch (Comb Empty) _ _ = empty
-- & trace "Branch Absorption Law"
branch b (Comb Empty) (Comb Empty) = b *> empty
Right r -> case $$(runCode lr) r of
Left{} -> Left ()
Right rr -> Right rr ||]
- branch b l r = SomeComb (Branch b l r)
+ branch b l r = SimplComb
+ { combData = Branch b l r
+ , combInline = False
+ , combRefs = HS.unions [ combRefs b, combRefs l, combRefs r ]
+ }
+instance
+ ( CombSelectable repr
+ , CombAlternable repr
+ , CombApplicable repr
+ , CombLookable repr
+ , CombMatchable repr
+ , Eq letName
+ , Hashable letName
+ ) => CombSelectable (KnotComb letName repr)
+
+-- CombRegisterableUnscoped
+data instance Comb CombRegisterableUnscoped repr a where
+ NewUnscoped :: UnscopedRegister a -> SimplComb repr a -> SimplComb repr b -> Comb CombRegisterableUnscoped repr b
+ GetUnscoped :: UnscopedRegister a -> Comb CombRegisterableUnscoped repr a
+ PutUnscoped :: UnscopedRegister a -> SimplComb repr a -> Comb CombRegisterableUnscoped repr ()
+instance CombRegisterableUnscoped repr => Derivable (Comb CombRegisterableUnscoped repr) where
+ derive = \case
+ NewUnscoped r ini x -> newUnscoped r (derive ini) (derive x)
+ GetUnscoped r -> getUnscoped r
+ PutUnscoped r x -> putUnscoped r (derive x)
+instance -- TODO: optimizations
+ ( CombRegisterableUnscoped repr
+ ) => CombRegisterableUnscoped (SimplComb repr) where
+ newUnscoped r ini x = SimplComb
+ { combData = NewUnscoped r ini x
+ , combInline = combInline ini && combInline x
+ , combRefs = combRefs ini <> combRefs x
+ }
+ getUnscoped r = SimplComb
+ { combData = GetUnscoped r
+ , combInline = True
+ , combRefs = HS.empty
+ }
+ putUnscoped r x = SimplComb
+ { combData = PutUnscoped r x
+ , combInline = combInline x
+ , combRefs = combRefs x
+ }
+instance
+ ( CombRegisterableUnscoped repr
+ , Eq letName
+ , Hashable letName
+ ) => CombRegisterableUnscoped (KnotComb letName repr) where
+
+-- Letsable
+data instance Comb (Letsable letName) repr a where
+ Lets ::
+ LetBindings letName (SimplComb repr) ->
+ SimplComb repr a ->
+ Comb (Letsable letName) repr a
+instance
+ Letsable letName repr =>
+ Derivable (Comb (Letsable letName) repr) where
+ derive = \case
+ Lets defs x -> lets
+ ((\(SomeLet sub) -> SomeLet (derive sub)) F.<$> defs)
+ (derive x)
+instance
+ (Letsable letName repr, Typeable letName) =>
+ Letsable letName (SimplComb repr) where
+ lets defs body = SimplComb
+ { combData = Lets defs body
+ , combInline = False
+ , combRefs = HS.unions
+ $ combRefs body
+ : ((\(SomeLet sub) -> combRefs sub) F.<$> HM.elems defs)
+ }
+instance
+ Letsable TH.Name repr =>
+ Letsable TH.Name (KnotComb TH.Name repr) where
+ lets defs body = KnotComb
+ { knotCombOpens =
+ HM.unions
+ $ knotCombOpens body
+ : ((\(SomeLet sub) -> SomeLet . knotCombOpen sub) F.<$> defs)
+ -- Not really necessary to include 'knotCombOpens' of 'defs' here
+ -- since there is only a single 'lets' at the top of the AST,
+ -- but well.
+ : ((\(SomeLet sub) -> knotCombOpens sub) F.<$> HM.elems defs)
+ , knotCombOpen = \finals -> TiedComb
+ { combSimpl =
+ let bodySimpl = combSimpl $ knotCombOpen body finals in
+ let defsSimpl = (\(SomeLet sub) -> SomeLet $ combSimpl $ knotCombOpen sub finals) F.<$> defs in
+ let defsUsed = HS.unions
+ $ combRefs bodySimpl
+ : ((\(SomeLet sub) -> combRefs sub) F.<$> HM.elems defsSimpl) in
+ lets (HM.intersection defsSimpl (HS.toMap defsUsed)) bodySimpl
+ }
+ }
+
+-- Referenceable
+data instance Comb (Referenceable letName) repr a where
+ Ref :: Bool -> letName -> Comb (Referenceable letName) repr a
+instance
+ Referenceable letName repr =>
+ Derivable (Comb (Referenceable letName) repr) where
+ derive = \case
+ Ref isRec name -> ref isRec name
+instance
+ Referenceable TH.Name repr =>
+ Referenceable TH.Name (SimplComb repr) where
+ ref isRec name = SimplComb
+ { combData = Ref isRec name
+ , combInline = not isRec
+ , combRefs = HS.singleton name
+ }
+instance
+ Referenceable TH.Name repr =>
+ Referenceable TH.Name (KnotComb TH.Name repr) where
+ ref isRec name = KnotComb
+ { knotCombOpens = HM.empty
+ , knotCombOpen = \finals ->
+ if isRec
+ then TiedComb
+ { combSimpl = ref isRec name
+ }
+ else case finals HM.! name of
+ SomeLet a@TiedComb
+ { combSimpl = p@SimplComb{ combInline = True }
+ } -> a{combSimpl = unsafeSimplComb p}
+ SomeLet TiedComb
+ { combSimpl = SimplComb{ combRefs = refs }
+ } -> TiedComb
+ { combSimpl = (ref isRec name)
+ { combRefs = HS.insert name refs }
+ }
+ }
import Data.Ord (Ord(..))
import Data.Semigroup (Semigroup(..))
import Data.String (String)
-import Data.Tuple (fst)
+import Data.Tuple (fst, snd)
import Text.Show (Show(..))
import qualified Data.Functor as Functor
import qualified Data.HashMap.Strict as HM
import Symantic.ObserveSharing
import Symantic.Parser.Grammar.Combinators
+import Symantic.Parser.Grammar.ObserveSharing
import qualified Symantic.Parser.Grammar.Production as Prod
-- * Type 'ViewGrammar'
chainPost x f = ViewGrammar $ Tree.Node ("chainPost", "") [unViewGrammar x, unViewGrammar f]
instance
ShowLetName sN letName =>
- Letable letName (ViewGrammar sN) where
- shareable name x = ViewGrammar $
- Tree.Node ("shareable", " "<>showLetName @sN name) [unViewGrammar x]
+ Referenceable letName (ViewGrammar sN) where
ref isRec name = ViewGrammar $
Tree.Node
( if isRec then "rec" else "ref"
negLook x = ViewGrammar $ Tree.Node ("negLook", "") [unViewGrammar x]
eof = ViewGrammar $ Tree.Node ("eof", "") []
instance CombMatchable (ViewGrammar sN) where
- conditional a _ps bs b = ViewGrammar $ Tree.Node ("conditional", "")
+ conditional a bs b = ViewGrammar $ Tree.Node ("conditional", "")
[ unViewGrammar a
- , Tree.Node ("branches", "") (unViewGrammar Functor.<$> bs)
+ , Tree.Node ("branches", "") (unViewGrammar . snd Functor.<$> bs)
, unViewGrammar b
]
instance CombSatisfiable tok (ViewGrammar sN) where
instance CombSelectable (ViewGrammar sN) where
branch lr l r = ViewGrammar $ Tree.Node ("branch", "")
[ unViewGrammar lr, unViewGrammar l, unViewGrammar r ]
+instance CombRegisterableUnscoped (ViewGrammar sN) where
+ newUnscoped r x y = ViewGrammar $ Tree.Node ("new "<>show r, "") [ unViewGrammar x, unViewGrammar y ]
+ getUnscoped r = ViewGrammar $ Tree.Node ("get "<>show r, "") [ ]
+ putUnscoped r x = ViewGrammar $ Tree.Node ("put "<>show r, "") [ unViewGrammar x ]
where
op = infixN 9
instance CombApplicable (WriteGrammar sN) where
- pure _ = WriteGrammar $ return Nothing
+ pure _ = WriteGrammar $ return Nothing{-TODO: print?-}
-- pure _ = "pure"
WriteGrammar x <*> WriteGrammar y = WriteGrammar $ \inh ->
let inh' side = inh
where op = infixN 9
instance
ShowLetName sN letName =>
- Letable letName (WriteGrammar sN) where
- shareable name x = WriteGrammar $ \inh ->
+ Referenceable letName (WriteGrammar sN) where
+ ref isRec name = WriteGrammar $ \inh ->
pairWriteGrammarInh inh op $
- Just "shareable "
- <> Just (fromString (showLetName @sN name))
- <> unWriteGrammar x inh
- where
- op = infixN 9
- ref rec name = WriteGrammar $ \inh ->
- pairWriteGrammarInh inh op $
- Just (if rec then "rec " else "ref ") <>
+ Just (if isRec then "rec " else "ref ") <>
Just (fromString (showLetName @sN name))
where
op = infixN 9
where op = infixN 9
eof = "eof"
instance CombMatchable (WriteGrammar sN) where
- conditional a _ps bs d = WriteGrammar $ \inh ->
+ conditional a bs def = WriteGrammar $ \inh ->
pairWriteGrammarInh inh op $
Just "conditional " <>
unWriteGrammar a inh <>
Just " [" <>
Just (mconcat (List.intersperse ", " $
- catMaybes $ (Functor.<$> bs) $ \x ->
- unWriteGrammar x inh{writeGrammarInh_op=(infixN 0, SideL)})) <>
+ catMaybes $ (Functor.<$> bs) $ \(p{-TODO: print?-}, b) ->
+ unWriteGrammar b inh{writeGrammarInh_op=(infixN 0, SideL)})) <>
Just "] " <>
- unWriteGrammar d inh
+ unWriteGrammar def inh
where
op = infixN 9
instance CombSatisfiable tok (WriteGrammar sN) where
, module Symantic.Parser.Machine.Program
, module Symantic.Parser.Machine.View
) where
-import Data.Function ((.))
+
import System.IO (IO)
-import qualified Language.Haskell.TH.Syntax as TH
+import Data.Function ((.))
import Symantic.Parser.Grammar
import Symantic.Parser.Machine.Generate
import Symantic.Parser.Machine.View
-- * Type 'Machine'
-type Machine repr inp =
- ObserveSharing TH.Name
- (OptimizeGrammar (Program repr inp))
+type Machine repr inp = Grammar (Program repr inp)
-- | Build a 'Machine' able to 'generateCode' for the given 'Parser'.
machine :: forall inp repr a.
{-# LANGUAGE ConstraintKinds #-} -- For Dict
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-} -- For nextInput
{-# LANGUAGE UndecidableInstances #-} -- For Show (ParsingError inp)
{-# OPTIONS_GHC -fno-warn-orphans #-}
import Control.DeepSeq (NFData(..))
import Control.Monad (Monad(..))
+import Control.Monad.ST (ST, runST)
import Data.Bool (Bool)
import Data.Char (Char)
import Data.Either (Either(..), either)
-import Data.Foldable (foldMap', toList, null)
-import Data.Function (($), (.), id, const, on)
+import Data.Foldable (toList, null)
+import Data.Function (($), (.), id, on)
import Data.Functor (Functor, (<$>), (<$))
import Data.Int (Int)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Set (Set)
import Data.String (String)
import Data.Traversable (Traversable(..))
+import Data.Tuple (snd)
import Data.Typeable (Typeable)
import Data.Word (Word8)
import GHC.Generics (Generic)
import Symantic.Derive
import Symantic.ObserveSharing
-import Symantic.Parser.Grammar.Combinators (Exception(..), Failure(..), SomeFailure(..), inputTokenProxy)
+import Symantic.Parser.Grammar.ObserveSharing
+import Symantic.Parser.Grammar.Combinators
+ ( UnscopedRegister(..)
+ , Exception(..)
+ , Failure(..)
+ , SomeFailure(..)
+ , inputTokenProxy
+ )
import Symantic.Parser.Machine.Input
import Symantic.Parser.Machine.Instructions
import qualified Language.Haskell.TH.HideName as TH
-- * Type 'Gen'
-- | Generate the 'CodeQ' parsing the input.
data Gen inp vs a = Gen
- { genAnalysisByLet :: LetMapFix (CallTrace -> GenAnalysis)
+ { genAnalysisByLet :: OpenRecs TH.Name (CallTrace -> GenAnalysis)
-- ^ 'genAnalysis' for each 'defLet' and 'defJoin' of the 'Machine'.
- , genAnalysis :: LetMapTo (CallTrace -> GenAnalysis)
+ , genAnalysis :: OpenRec TH.Name (CallTrace -> GenAnalysis)
-- ^ Synthetized (bottom-up) static genAnalysis of the 'Machine'.
- , unGen ::
- GenCtx inp vs a ->
- CodeQ (Either (ParsingError inp) a)
+ , unGen :: forall st.
+ GenCtx st inp vs a ->
+ CodeQ (ST st (Either (ParsingError inp) a))
}
+{-# INLINE returnST #-}
+returnST :: forall s a. a -> ST s a
+returnST = return @(ST s)
+
-- | @('generateCode' input mach)@ generates @TemplateHaskell@ code
-- parsing the given 'input' according to the given 'Machine'.
generateCode ::
TH.Lift (InputToken inp) =>
-}
-- InputToken inp ~ Char =>
+ --forall inp a.
Inputable inp =>
Show (Cursor inp) =>
Gen inp '[] a ->
CodeQ (inp -> Either (ParsingError inp) a)
-generateCode k = [|| \(input :: inp) ->
+generateCode Gen{unGen=k, ..} = [|| \(input :: inp) ->
-- Pattern bindings containing unlifted types
-- should use an outermost bang pattern.
let !(# init, readMore, readNext #) = $$(cursorOf [||input||])
- finalRet = \_farInp _farExp v _inp -> Right v
- finalRaise :: forall b. (Catcher inp b)
+ finalRet = \_farInp _farExp v _inp -> returnST $ Right v
+ finalRaise :: forall st b. (Catcher st inp b)
= \ !exn _failInp !farInp !farExp ->
- Left ParsingError
+ returnST $ Left ParsingError
{ parsingErrorOffset = offset farInp
, parsingErrorException = exn
, parsingErrorUnexpected =
else Nothing
, parsingErrorExpecting = farExp
}
- in
- $$(
- let defInputTokenProxy exprCode =
- TH.unsafeCodeCoerce $ do
- value <- TH.unTypeQ $ TH.examineCode [||Proxy :: Proxy (InputToken inp)||]
- expr <- TH.unTypeQ (TH.examineCode exprCode)
- return $ TH.LetE [
- TH.FunD inputTokenProxy [TH.Clause [] (TH.NormalB value) []]
- ] expr
- in defInputTokenProxy $
- unGen k GenCtx
+ in runST $$(
+ let
+ -- | Defines 'inputTokenProxy' so that the TemplateHaskell code
+ -- can refer to @(InputToken inp)@ through it.
+ defInputTokenProxy :: TH.CodeQ a -> TH.CodeQ a
+ defInputTokenProxy exprCode =
+ TH.unsafeCodeCoerce [|
+ let $(return (TH.VarP inputTokenProxy)) = Proxy :: Proxy (InputToken inp) in
+ $(TH.unTypeQ (TH.examineCode exprCode))
+ |]
+ in
+ defInputTokenProxy $
+ k GenCtx
{ valueStack = ValueStackEmpty
- , catchStackByLabel = Map.empty
+ , catchStackByLabel = Map.empty :: Map Exception (NonEmpty (TH.CodeQ (Catcher s inp a)))
, defaultCatch = [||finalRaise||]
- , callStack = []
- , retCode = [||finalRet||]
+ , analysisCallStack = []
+ , returnCall = [||finalRet||] :: CodeQ (Return s inp a a)
, input = [||init||]
, nextInput = [||readNext||]
, moreInput = [||readMore||]
, farthestExpecting = [||Set.empty||]
, checkedHorizon = 0
, horizonStack = []
- , finalGenAnalysisByLet = runGenAnalysis (genAnalysisByLet k)
+ , finalGenAnalysisByLet = runOpenRecs genAnalysisByLet
}
)
||]
, mayRaise :: Map Exception ()
} deriving (Show)
--- | Tie the knot between mutually recursive 'TH.Name's
--- introduced by 'defLet' and 'defJoin'.
--- and provide the empty initial 'CallTrace' stack
-runGenAnalysis ::
- LetMapFix (CallTrace -> GenAnalysis) ->
- LetMap GenAnalysis
-runGenAnalysis ga = (($ []) <$>) $ polyfix ga
-
--- | Poly-variadic fixpoint combinator.
--- Used to express mutual recursion and to transparently introduce memoization,
--- more precisely to "tie the knot"
--- between observed sharing ('defLet', 'call', 'jump')
--- and also between join points ('defJoin', 'refJoin').
--- Because it's enough for its usage here,
--- all mutually dependent functions are restricted to the same polymorphic type @(a)@.
--- See http://okmij.org/ftp/Computation/fixed-point-combinators.html#Poly-variadic
-polyfix :: Functor f => f (f a -> a) -> f a
-polyfix fs = fix $ \finals -> ($ finals) <$> fs
-
-fix :: (a -> a) -> a
-fix f = final where final = f final
-
-type LetMap = HM.HashMap TH.Name
-type LetMapTo a = LetMap a -> a
-type LetMapFix a = LetMap (LetMap a -> a)
-
--- | Call trace stack updated by 'call' and 'refJoin'.
--- Used to avoid infinite loops when tying the knot with 'polyfix'.
-type CallTrace = [TH.Name]
-
-- ** Type 'Offset'
type Offset = Int
-- ** Type 'Horizon'
altGenAnalysis :: NonEmpty GenAnalysis -> GenAnalysis
altGenAnalysis aas@(a:|as) = GenAnalysis
{ minReads = List.foldl' (\acc x ->
- either
- (\l -> either (const (Left l)) Right)
- (\r -> either (const (Right r)) (Right . min r))
- acc (minReads x)
+ case acc of
+ Left l ->
+ case minReads x of
+ Left{} -> Left l
+ Right r -> Right r
+ Right r ->
+ case minReads x of
+ Left{} -> Right r
+ Right r' -> Right (min r r')
) (minReads a) as
, mayRaise = sconcat (mayRaise <$> aas)
}
-- ** Type 'GenCtx'
-- | This is an inherited (top-down) context
-- only present at compile-time, to build TemplateHaskell splices.
-data GenCtx inp vs a =
+data GenCtx st inp vs a =
( Cursorable (Cursor inp)
{-
, TH.Lift (InputToken inp)
-}
) => GenCtx
{ valueStack :: ValueStack vs
- , catchStackByLabel :: Map Exception (NonEmpty (CodeQ (Catcher inp a)))
+ , catchStackByLabel :: Map Exception (NonEmpty (CodeQ (Catcher st inp a)))
-- | Default 'Catcher' defined at the begining of the generated 'CodeQ',
-- hence a constant within the 'Gen'eration.
- , defaultCatch :: forall b. CodeQ (Catcher inp b)
+ , defaultCatch :: forall b. CodeQ (Catcher st inp b)
-- | Used by 'checkToken' to get 'GenAnalysis' from 'genAnalysis'.
- , callStack :: [TH.Name]
- , retCode :: CodeQ (Cont inp a a)
+ , analysisCallStack :: [TH.Name]
+ , returnCall :: CodeQ (Return st inp a a)
, input :: CodeQ (Cursor inp)
, moreInput :: CodeQ (Cursor inp -> Bool)
, nextInput :: CodeQ (Cursor inp -> (# InputToken inp, Cursor inp #))
-- | Used by 'pushInput' and 'loadInput'
-- to restore the 'Horizon' at the restored 'input'.
, horizonStack :: [Horizon]
- -- | Output of 'runGenAnalysis'.
- , finalGenAnalysisByLet :: LetMap GenAnalysis
+ -- | Output of 'runOpenRecs'.
+ , finalGenAnalysisByLet :: LetRecs TH.Name GenAnalysis
}
-- ** Type 'ValueStack'
Right y -> $$(unGen ky ctx{ valueStack = ValueStackCons (splice [||y||]) vs })
||]
}
- choicesBranch fs ks kd = Gen
- { genAnalysisByLet = sconcat $ genAnalysisByLet kd :| (genAnalysisByLet <$> ks)
- , genAnalysis = \final ct -> altGenAnalysis $ (\k -> genAnalysis k final ct) <$> (kd:|ks)
- , unGen = \ctx -> {-trace "unGen.choicesBranch" $-}
- let ValueStackCons v vs = valueStack ctx in
- go ctx{valueStack = vs} v fs ks
+ choicesBranch bs default_ = Gen
+ { genAnalysisByLet = sconcat $ genAnalysisByLet default_ :| (genAnalysisByLet . snd <$> bs)
+ , genAnalysis = \final ct -> altGenAnalysis $
+ (\k -> genAnalysis k final ct)
+ <$> (default_:|(snd <$> bs))
+ , unGen = \ctx0 -> {-trace "unGen.choicesBranch" $-}
+ let ValueStackCons v vs = valueStack ctx0 in
+ let ctx = ctx0{valueStack = vs} in
+ let
+ go x ((p,b):bs') = [||
+ if $$(genCode (p Prod..@ x))
+ then
+ let _ = "choicesBranch.then" in
+ $$({-trace "unGen.choicesBranch.b" $-} unGen b ctx)
+ else
+ let _ = "choicesBranch.else" in
+ $$(go x bs')
+ ||]
+ go _ _ = unGen default_ ctx
+ in go v bs
}
- where
- go ctx x (f:fs') (k:ks') = [||
- if $$(genCode (f Prod..@ x))
- then
- let _ = "choicesBranch.then" in
- $$({-trace "unGen.choicesBranch.k" $-} unGen k ctx)
- else
- let _ = "choicesBranch.else" in
- $$(go ctx x fs' ks')
- ||]
- go ctx _ _ _ = unGen kd ctx
instance InstrExceptionable Gen where
raise exn = Gen
{ genAnalysisByLet = HM.empty
{-trace "unGen.defLet.body" $-}
unGen k ctx
return $ TH.LetE (
- -- | Try to output more deterministic code to be able to golden test it,
- -- at the cost of more computations (at compile-time only though).
+ -- | Use 'List.sortBy' to output more deterministic code
+ -- to be able to golden test it, at the cost of more computations
+ -- (at compile-time only though).
List.sortBy (compare `on` TH.hideName) $
toList decls
) body
, genAnalysisByLet =
- foldMap' (\(SomeLet sub) -> genAnalysisByLet sub) defs <>
- ((\(SomeLet sub) -> genAnalysis sub) <$> defs) <>
- genAnalysisByLet k
+ HM.unions
+ $ genAnalysisByLet k
+ : ((\(SomeLet sub) -> genAnalysis sub) <$> defs)
+ : ((\(SomeLet sub) -> genAnalysisByLet sub) <$> HM.elems defs)
}
where
- makeDecl ctx (n, SomeLet sub) = do
+ makeDecl ctx (subName, SomeLet sub) = do
body <- TH.unTypeQ $ TH.examineCode $ [|| -- buildRec in Parsley
+ -- TODO: takeFreeRegisters
-- Called by 'call' or 'jump'.
- \ !ok{-from generateSuspend or retCode-}
- !inp
- !koByLabel{- 'catchStackByLabel' from the 'call'-site -} ->
- $$({-trace ("unGen.defLet.sub: "<>show n) $-} unGen sub ctx
+ \ !callReturn{-from generateSuspend or returnCall-}
+ !callInput
+ !callCatchStackByLabel{- 'catchStackByLabel' from the 'call'-site -} ->
+ $$({-trace ("unGen.defLet.sub: "<>show subName) $-} unGen sub ctx
{ valueStack = ValueStackEmpty
- -- Build a 'catchStackByLabel' from the one available at the 'call'-site.
- -- Note that all the 'mayRaise' of the 'sub'routine may not be available,
- -- hence 'Map.findWithDefault' is used instead of 'Map.!'.
+ -- Build a 'catchStackByLabel' for the 'mayRaise' of the subroutine,
+ -- where each 'Catcher' calls the one passed by the 'call'-site (in 'callCatchStackByLabel').
+ -- Note that currently the 'call'-site can supply in 'callCatchStackByLabel'
+ -- a subset of the 'mayRaise' needed by this subroutine,
+ -- because 'Map.findWithDefault' is used instead of 'Map.!'.
, catchStackByLabel = Map.mapWithKey
- (\lbl () -> NE.singleton [||Map.findWithDefault $$(defaultCatch ctx) lbl koByLabel||])
- ({-trace ("mayRaise: "<>show n) $-}
- mayRaise (finalGenAnalysisByLet ctx HM.! n))
- , input = [||inp||]
- , retCode = {-trace ("unGen.defLet.sub.retCode: "<>show n) $-} [||ok||]
+ (\lbl () -> NE.singleton [||Map.findWithDefault $$(defaultCatch ctx) lbl callCatchStackByLabel||])
+ ({-trace ("mayRaise: "<>show subName) $-}
+ mayRaise (finalGenAnalysisByLet ctx HM.! subName))
+ , input = [||callInput||]
+ , returnCall = {-trace ("unGen.defLet.sub.returnCall: "<>show subName) $-} [||callReturn||]
- -- These are passed by the caller via 'ok' or 'ko'
+ -- These are passed by the caller via 'callReturn' or 'ko'
-- , farthestInput =
-- , farthestExpecting =
, checkedHorizon = 0
})
||]
- let decl = TH.FunD n [TH.Clause [] (TH.NormalB body) []]
+ let decl = TH.FunD subName [TH.Clause [] (TH.NormalB body) []]
return decl
jump (LetName n) = Gen
{ genAnalysisByLet = HM.empty
, unGen = \ctx -> {-trace ("unGen.jump: "<>show n) $-} [||
let _ = "jump" in
$$(TH.unsafeCodeCoerce (return (TH.VarE n)))
- {-ok-}$$(retCode ctx)
+ {-ok-}$$(returnCall ctx)
$$(input ctx)
$$(liftTypedRaiseByLabel $
catchStackByLabel ctx
[||
-- let _ = $$(liftTypedString $ "call exceptByLet("<>show n<>")="<>show (Map.keys (Map.findWithDefault Map.empty n (exceptByLet ctx))) <> " catchStackByLabel(ctx)="<> show ks) in
$$(TH.unsafeCodeCoerce (return (TH.VarE n)))
- {-ok-}$$(generateSuspend k ctx{callStack = n : callStack ctx})
+ {-ok-}$$(generateSuspend k ctx{analysisCallStack = n : analysisCallStack ctx})
$$(input ctx)
$$(liftTypedRaiseByLabel $
+ -- FIXME: maybe it should rather pass all the 'mayRaise' of 'n'
+ -- and 'defaultCatch' be removed from 'makeDecl''s 'catchStackByLabel'.
catchStackByLabel ctx
-- Pass only the labels raised by the 'defLet'.
`Map.intersection`
{ minReads = Right 0
, mayRaise = Map.empty
}
- , unGen = \ctx -> {-trace "unGen.ret" $-} unGen ({-trace "unGen.ret.generateResume" $-} generateResume ({-trace "unGen.ret.retCode" $-} retCode ctx)) ctx
+ , unGen = \ctx -> {-trace "unGen.ret" $-}
+ {-trace "unGen.ret.generateResume" $-}
+ generateResume ({-trace "unGen.ret.returnCall" $-} returnCall ctx) ctx
}
-- | Like 'TH.liftString' but on 'TH.Code'.
liftTyped Set_.Tip = [|| Set_.Tip ||]
liftTyped (Set_.Bin s a l r) = [|| Set_.Bin $$(TH.liftTyped s) $$(TH.liftTyped a) $$(TH.liftTyped l) $$(TH.liftTyped r) ||]
--- ** Type 'Cont'
-type Cont inp v a =
+-- ** Type 'Return'
+type Return st inp v a =
{-farthestInput-}Cursor inp ->
{-farthestExpecting-}(Set SomeFailure) ->
v ->
Cursor inp ->
- Either (ParsingError inp) a
+ ST st (Either (ParsingError inp) a)
--- | Generate a 'retCode' 'Cont'inuation to be called with 'generateResume'.
+-- | Generate a 'returnCall' 'Return'inuation to be called with 'generateResume'.
-- Used when 'call' 'ret'urns.
-- The return 'v'alue is 'pushValue'-ed on the 'valueStack'.
generateSuspend ::
{-k-}Gen inp (v ': vs) a ->
- GenCtx inp vs a ->
- CodeQ (Cont inp v a)
+ GenCtx st inp vs a ->
+ CodeQ (Return st inp v a)
generateSuspend k ctx = [||
let _ = $$(liftTypedString $ "suspend") in
\farInp farExp v !inp ->
-- | Generate a call to the 'generateSuspend' continuation.
-- Used when 'call' 'ret'urns.
generateResume ::
- CodeQ (Cont inp v a) ->
- Gen inp (v ': vs) a
-generateResume k = Gen
- { genAnalysisByLet = HM.empty
- , genAnalysis = \_final _ct -> GenAnalysis
- { minReads = Right 0
- , mayRaise = Map.empty
- }
- , unGen = \ctx -> {-trace "unGen.generateResume" $-} [||
- let _ = "resume" in
- $$k
- $$(farthestInput ctx)
- $$(farthestExpecting ctx)
- (let _ = "resume.genCode" in $$({-trace "unGen.generateResume.genCode" $-}
- genCode $ valueStackHead $ valueStack ctx))
- $$(input ctx)
- ||]
- }
+ CodeQ (Return st inp v a) ->
+ GenCtx st inp (v ': vs) a ->
+ CodeQ (ST st (Either (ParsingError inp) a))
+generateResume k = \ctx -> {-trace "generateResume" $-} [||
+ let _ = "resume" in
+ $$k
+ $$(farthestInput ctx)
+ $$(farthestExpecting ctx)
+ (let _ = "resume.genCode" in $$({-trace "generateResume.genCode" $-}
+ genCode $ valueStackHead $ valueStack ctx))
+ $$(input ctx)
+ ||]
-- ** Type 'Catcher'
-type Catcher inp a =
+type Catcher st inp a =
Exception ->
{-failInp-}Cursor inp ->
{-farInp-}Cursor inp ->
{-farExp-}(Set SomeFailure) ->
- Either (ParsingError inp) a
+ ST st (Either (ParsingError inp) a)
instance InstrJoinable Gen where
defJoin (LetName n) sub k = k
- { unGen =
- \ctx ->
+ { unGen = \ctx ->
{-trace ("unGen.defJoin: "<>show n) $-}
- TH.unsafeCodeCoerce $ do
- next <- TH.unTypeQ $ TH.examineCode $ [||
- -- Called by 'generateResume'.
- \farInp farExp v !inp ->
- $$({-trace ("unGen.defJoin.next: "<>show n) $-} unGen sub ctx
- { valueStack = ValueStackCons (splice [||v||]) (valueStack ctx)
- , input = [||inp||]
- , farthestInput = [||farInp||]
- , farthestExpecting = [||farExp||]
- , checkedHorizon = 0
- {- FIXME:
- , catchStackByLabel = Map.mapWithKey
- (\lbl () -> NE.singleton [||koByLabel Map.! lbl||])
- (mayRaise sub raiseLabelsByLetButSub)
- -}
- })
- ||]
- let decl = TH.FunD n [TH.Clause [] (TH.NormalB next) []]
- expr <- TH.unTypeQ (TH.examineCode ({-trace ("unGen.defJoin.expr: "<>show n) $-} unGen k ctx))
- return (TH.LetE [decl] expr)
+ TH.unsafeCodeCoerce [|
+ let $(return (TH.VarP n)) = $(TH.unTypeQ $ TH.examineCode [||
+ -- Called by 'generateResume'.
+ \farInp farExp v !inp ->
+ $$({-trace ("unGen.defJoin.next: "<>show n) $-} unGen sub ctx
+ { valueStack = ValueStackCons (splice [||v||]) (valueStack ctx)
+ , input = [||inp||]
+ , farthestInput = [||farInp||]
+ , farthestExpecting = [||farExp||]
+ , checkedHorizon = 0
+ {- FIXME:
+ , catchStackByLabel = Map.mapWithKey
+ (\lbl () -> NE.singleton [||koByLabel Map.! lbl||])
+ (mayRaise sub raiseLabelsByLetButSub)
+ -}
+ })
+ ||])
+ in $(TH.unTypeQ $ TH.examineCode $
+ {-trace ("unGen.defJoin.expr: "<>show n) $-}
+ unGen k ctx)
+ |]
, genAnalysisByLet =
(genAnalysisByLet sub <>) $
HM.insert n (genAnalysis sub) $
refJoin (LetName n) = Gen
{ unGen = \ctx ->
{-trace ("unGen.refJoin: "<>show n) $-}
- unGen (generateResume
- (TH.unsafeCodeCoerce (return (TH.VarE n)))) ctx
+ generateResume
+ (TH.unsafeCodeCoerce (return (TH.VarE n))) ctx
, genAnalysisByLet = HM.empty
, genAnalysis = \final ct ->
if n`List.elem`ct -- FIXME: useless
read fs p = checkHorizon . checkToken fs p
instance InstrReadable Word8 Gen where
read fs p = checkHorizon . checkToken fs p
+instance InstrIterable Gen where
+ iter (LetName jumpName) loop done = Gen
+ { genAnalysisByLet =
+ HM.insert jumpName (genAnalysis loop) $
+ genAnalysisByLet loop <>
+ genAnalysisByLet done
+ , genAnalysis = \final ct ->
+ GenAnalysis
+ { minReads = minReads (genAnalysis done final ct)
+ , mayRaise =
+ Map.delete ExceptionFailure
+ (mayRaise (genAnalysis loop final ct)) <>
+ mayRaise (genAnalysis done final ct)
+ }
+ , unGen = \ctx -> TH.unsafeCodeCoerce [|
+ let _ = "iter" in
+ let
+ {-
+ Exception ->
+ {-failInp-}Cursor inp ->
+ {-farInp-}Cursor inp ->
+ {-farExp-}(Set SomeFailure) ->
+ ST st (Either (ParsingError inp) a)
+ -}
+ catchHandler loopInput !_exn !failInp !farInp !farExp =
+ $(TH.unTypeCode $ {-trace ("unGen.catch.ko: "<>show exn) $-} unGen done ctx
+ -- Push 'input' and 'checkedHorizon'
+ -- as they were when entering 'catch',
+ -- they will be available to 'loadInput', if any.
+ { valueStack = ValueStackCons (splice (TH.unsafeCodeCoerce [|loopInput|])) (valueStack ctx)
+ , horizonStack = checkedHorizon ctx : horizonStack ctx
+ -- Note that 'catchStackByLabel' is reset.
+ -- Move the input to the failing position.
+ , input = TH.unsafeCodeCoerce [|failInp|]
+ -- The 'checkedHorizon' at the 'raise's are not known here.
+ -- Nor whether 'failInp' is after 'checkedHorizon' or not.
+ -- Hence fallback to a safe value.
+ , checkedHorizon = 0
+ -- Set the farthestInput to the farthest computed in 'fail'.
+ , farthestInput = TH.unsafeCodeCoerce [|farInp|]
+ , farthestExpecting = TH.unsafeCodeCoerce [|farExp|]
+ })
+ $(return $ TH.VarP jumpName) = \_callReturn callInput callCatchStackByLabel ->
+ $(TH.unTypeCode $ unGen loop ctx
+ { valueStack = ValueStackEmpty
+ , catchStackByLabel =
+ {-
+ Map.mapWithKey
+ (\lbl () -> NE.singleton $ TH.unsafeCodeCoerce [|
+ Map.findWithDefault $(TH.unTypeCode $ defaultCatch ctx) lbl koByLabel
+ |])
+ (mayRaise (finalGenAnalysisByLet ctx HM.! jumpName))
+ -}
+ Map.insertWith (<>) ExceptionFailure
+ (NE.singleton $ TH.unsafeCodeCoerce [|catchHandler callInput|])
+ (catchStackByLabel ctx)
+ , input = TH.unsafeCodeCoerce [|callInput|]
+ -- FIXME: promote to compile time error?
+ , returnCall = TH.unsafeCodeCoerce [|error "invalid return"|]
+ , checkedHorizon = 0
+ })
+ in $(TH.unTypeCode $ unGen (jump (LetName jumpName)) ctx{valueStack=ValueStackEmpty})
+ |]
+ }
+instance InstrRegisterable Gen where
+ newRegister (UnscopedRegister r) k = k
+ { unGen = \ctx ->
+ let ValueStackCons v vs = valueStack ctx in
+ TH.unsafeCodeCoerce [|
+ do
+ let dupv = $(TH.unTypeCode $ genCode v)
+ $(return (TH.VarP r)) <- ST.newSTRef dupv
+ $(TH.unTypeCode $ unGen k ctx{valueStack=vs})
+ |]
+ }
+ readRegister (UnscopedRegister r) k = k
+ { unGen = \ctx -> [|| do
+ sr <- ST.readSTRef $$(TH.unsafeCodeCoerce (return (TH.VarE r)))
+ $$(unGen k ctx{valueStack=ValueStackCons (splice [||sr||]) (valueStack ctx)})
+ ||]
+ }
+ writeRegister (UnscopedRegister r) k = k
+ { unGen = \ctx ->
+ let ValueStackCons v vs = valueStack ctx in
+ [|| do
+ let dupv = $$(genCode v)
+ ST.writeSTRef $$(TH.unsafeCodeCoerce (return (TH.VarE r))) dupv
+ $$(unGen k ctx{valueStack=vs})
+ ||]
+ }
checkHorizon ::
forall inp vs a.
-- according to the relative position of 'input' wrt. 'farthestInput'.
raiseFailure ::
Cursorable (Cursor inp) =>
- GenCtx inp cs a ->
+ GenCtx st inp cs a ->
TH.CodeQ (Set SomeFailure) ->
- TH.CodeQ (Either (ParsingError inp) a)
+ TH.CodeQ (ST st (Either (ParsingError inp) a))
raiseFailure ctx fs = [||
let failExp = $$fs in
let (# farInp, farExp #) =
-- | @('raiseException' ctx exn)@ raises exception @(exn)@
-- using any entry in 'catchStackByLabel', or 'defaultCatch' if none.
raiseException ::
- GenCtx inp vs a -> Exception ->
- CodeQ (Exception -> Cursor inp -> Cursor inp -> Set SomeFailure -> Either (ParsingError inp) a)
+ GenCtx st inp vs a -> Exception ->
+ CodeQ (Exception -> Cursor inp -> Cursor inp -> Set SomeFailure -> ST st (Either (ParsingError inp) a))
raiseException ctx exn =
NE.head $ Map.findWithDefault
(NE.singleton (defaultCatch ctx))
exn (catchStackByLabel ctx)
-finalGenAnalysis :: GenCtx inp vs a -> Gen inp cs a -> GenAnalysis
+finalGenAnalysis :: GenCtx st inp vs a -> Gen inp cs a -> GenAnalysis
finalGenAnalysis ctx k =
--(\f -> f (error "callTrace")) $
- (\f -> f (callStack ctx)) $
+ (\f -> f (analysisCallStack ctx)) $
genAnalysis k $
((\f _ct -> f) <$>) $
finalGenAnalysisByLet ctx
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE PolyKinds #-}
module Symantic.Parser.Machine.Input where
import Data.Array.Base (UArray(..), listArray)
import Data.Text.Internal (Text(..))
import Data.Text.Unsafe (iter, Iter(..), iter_, reverseIter_)
import Text.Show (Show(..))
-import GHC.Exts (Int(..), Char(..), {-, RuntimeRep(..)-})
+import GHC.Exts (Int(..), Char(..) {-, RuntimeRep(..)-}, TYPE)
import GHC.Word (Word8(..))
import GHC.ForeignPtr (ForeignPtr(..), ForeignPtrContents)
import GHC.Prim ({-Int#,-} Addr#, nullAddr#, indexWideCharArray#, {-indexWord16Array#,-} readWord8OffAddr#, word2Int#, chr#, touch#, realWorld#, plusAddr#, (+#))
class Cursorable (Cursor inp) => Inputable inp where
type Cursor inp :: Type
type InputToken inp :: Type
- cursorOf :: CodeQ inp -> CodeQ
+ cursorOf :: CodeQ inp -> CodeQ (CursorOps inp)
+
+type CursorOps (inp :: TYPE r) =
(# {-init-} Cursor inp
, {-more-} Cursor inp -> Bool
, {-next-} Cursor inp -> (# InputToken inp, Cursor inp #)
commit :: Exception -> repr inp vs a -> repr inp vs a
-- | @('catch' exn l r)@ tries the @(l)@ 'Instr'uction
-- in a new failure scope such that if @(l)@ raises an exception within @(exn)@, it is caught,
- -- then the input (and its 'Horizon') is pushed as it was before trying @(l)@ on the 'valueStack',
+ -- then the input (and its 'Horizon') is pushed
+ -- as it was before trying @(l)@ on the 'valueStack' (resp. on the 'horizonStack'),
-- and the control flow goes on with the @(r)@ 'Instr'uction.
catch ::
Exception ->
repr inp (Either x y ': vs) r
-- | @('choicesBranch' ps bs d)@.
choicesBranch ::
- [Splice (v -> Bool)] ->
- [repr inp vs a] ->
+ [(Splice (v -> Bool), repr inp vs a)] ->
repr inp vs a ->
repr inp (v ': vs) a
-- | @('ifBranch' ok ko)@ pops a 'Bool' from the 'valueStack'
repr inp vs a ->
repr inp vs a ->
repr inp (Bool ': vs) a
- ifBranch ok ko = choicesBranch [Prod.id] [ok] ko
+ ifBranch ok ko = choicesBranch [(Prod.id, ok)] ko
-- ** Class 'InstrCallable'
class InstrCallable (repr::ReprInstr) where
Splice (tok -> Bool) ->
repr inp (tok ': vs) a ->
repr inp vs a
+
+-- ** Class 'InstrIterable'
+class InstrIterable (repr::ReprInstr) where
+ -- | @('iter' loop done)@.
+ iter ::
+ LetName a ->
+ repr inp '[] a ->
+ repr inp (Cursor inp ': vs) a ->
+ repr inp vs a
+
+-- ** Class 'InstrRegisterable'
+class InstrRegisterable (repr::ReprInstr) where
+ newRegister ::
+ UnscopedRegister v ->
+ repr inp vs a ->
+ repr inp (v : vs) a
+ readRegister ::
+ UnscopedRegister v ->
+ repr inp (v : vs) a ->
+ repr inp vs a
+ writeRegister ::
+ UnscopedRegister v ->
+ repr inp vs a ->
+ repr inp (v : vs) a
+
+-- | @('modifyRegister' reg k)@
+-- modifies the content of register @(reg)@
+-- with the function at the 'valueStackHead',
+-- then continues with @(k)@.
+modifyRegister ::
+ InstrRegisterable repr =>
+ InstrValuable repr =>
+ UnscopedRegister v -> repr inp vs a -> repr inp ((v -> v) : vs) a
+modifyRegister r = readRegister r . applyValue . writeRegister r
SomeInstr repr inp (y ': vs) a ->
Instr InstrBranchable repr inp (Either x y ': vs) a
ChoicesBranch ::
- [Splice (v -> Bool)] ->
- [SomeInstr repr inp vs a] ->
+ [(Splice (v -> Bool), SomeInstr repr inp vs a)] ->
SomeInstr repr inp vs a ->
Instr InstrBranchable repr inp (v ': vs) a
instance InstrBranchable repr => Derivable (Instr InstrBranchable repr inp vs) where
derive = \case
CaseBranch l r -> caseBranch (derive l) (derive r)
- ChoicesBranch ps bs d -> choicesBranch ps (derive Functor.<$> bs) (derive d)
+ ChoicesBranch bs d -> choicesBranch ((derive Functor.<$>) Functor.<$> bs) (derive d)
instance InstrBranchable repr => InstrBranchable (SomeInstr repr) where
caseBranch l = SomeInstr . CaseBranch l
- choicesBranch ps bs = SomeInstr . ChoicesBranch ps bs
+ choicesBranch bs = SomeInstr . ChoicesBranch bs
-- InstrCallable
data instance Instr InstrCallable repr inp vs a where
( InstrReadable tok repr, Typeable tok ) =>
InstrReadable tok (SomeInstr repr) where
read fs p = SomeInstr . Read fs p
+
+-- InstrIterable
+data instance Instr InstrIterable repr inp vs a where
+ Iter ::
+ LetName a ->
+ SomeInstr repr inp '[] a ->
+ SomeInstr repr inp (Cursor inp ': vs) a ->
+ Instr InstrIterable repr inp vs a
+instance
+ InstrIterable repr =>
+ Derivable (Instr InstrIterable repr inp vs) where
+ derive = \case
+ Iter n op k -> iter n (derive op) (derive k)
+instance
+ InstrIterable repr =>
+ InstrIterable (SomeInstr repr) where
+ iter n op = SomeInstr . Iter n op
+
+-- InstrRegisterable
+data instance Instr InstrRegisterable repr inp vs a where
+ NewRegister ::
+ UnscopedRegister v ->
+ SomeInstr repr inp vs a ->
+ Instr InstrRegisterable repr inp (v : vs) a
+ ReadRegister ::
+ UnscopedRegister v ->
+ SomeInstr repr inp (v : vs) a ->
+ Instr InstrRegisterable repr inp vs a
+ WriteRegister ::
+ UnscopedRegister v ->
+ SomeInstr repr inp vs a ->
+ Instr InstrRegisterable repr inp (v : vs) a
+instance
+ InstrRegisterable repr =>
+ Derivable (Instr InstrRegisterable repr inp vs) where
+ derive = \case
+ NewRegister r k -> newRegister r (derive k)
+ ReadRegister r k -> readRegister r (derive k)
+ WriteRegister r k -> writeRegister r (derive k)
+instance
+ InstrRegisterable repr =>
+ InstrRegisterable (SomeInstr repr) where
+ newRegister r = SomeInstr . NewRegister r
+ readRegister r = SomeInstr . ReadRegister r
+ writeRegister r = SomeInstr . WriteRegister r
{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE TupleSections #-}
{-# LANGUAGE UndecidableInstances #-} -- For Cursorable (Cursor inp)
-- | Build the 'Instr'uction 'Program' of a 'Machine'
-- from the 'Comb'inators of a 'Grammar'.
import Data.Ord (Ord)
import Text.Show (Show(..))
import qualified Data.Functor as Functor
-import qualified Data.HashMap.Strict as HM
import qualified Data.Set as Set
import qualified Data.Traversable as Traversable
import qualified Language.Haskell.TH as TH
import qualified Language.Haskell.TH.Syntax as TH
-import qualified Symantic.Typed.Lang as Prod
+import qualified Symantic.Lang as Prod
-import Symantic.Typed.Derive
+import Symantic.Derive
import Symantic.Parser.Grammar
import Symantic.Parser.Machine.Input
import Symantic.Parser.Machine.Instructions
-- the next 'Instr'uction.
data Program repr inp a = Program { unProgram ::
forall vs ret.
- -- This is the next instruction
+ -- This is the next instruction.
SomeInstr repr inp (a ': vs) ret ->
-- This is the current instruction
-- IO is needed for 'TH.newName'.
, InstrCallable repr
, InstrValuable repr
, InstrReadable tok repr
+ , InstrIterable repr
+ , InstrRegisterable repr
, Eq tok
, Ord tok
, TH.Lift tok
, Typeable tok
)
-instance
- ( Cursorable (Cursor inp)
- , InstrBranchable repr
- , InstrExceptionable repr
- , InstrInputable repr
- , InstrJoinable repr
- , InstrValuable repr
- , InstrReadable (InputToken inp) repr
- , Typeable (InputToken inp)
- ) =>
- Derivable (Comb CombAlternable (Program repr inp)) where
- derive = \case
- Alt ExceptionFailure
- (Comb (SatisfyOrFail _fs p :: Comb (CombSatisfiable (InputToken inp)) (Program repr inp) a))
- (Comb (Failure sf)) ->
- satisfyOrFail (Set.singleton sf) p
- Alt exn x y -> alt exn (derive x) (derive y)
- Empty -> empty
- Failure sf -> failure sf
- Throw exn -> throw exn
- Try x -> try (derive x)
-
instance
( Cursorable (Cursor inp)
, InstrBranchable repr
alt exn (Program l) (Program r) = joinNext $ Program $ \next ->
liftM2 (catch exn)
(l (commit exn next))
- (failIfConsumed exn Functor.<$> r next)
+ (raiseAgainIfConsumed exn Functor.<$> r next)
throw exn = Program $ \_next -> return $ raise exn
failure flr = Program $ \_next -> return $ fail (Set.singleton flr)
empty = Program $ \_next -> return $ fail (Set.singleton (SomeFailure FailureEmpty))
-- On exception, reset the input, and propagate the failure.
(return $ loadInput $ fail Set.empty)
--- | If no input has been consumed by the failing alternative
--- then continue with the given continuation.
--- Otherwise, propagate the failure.
-failIfConsumed ::
+-- | @(raiseAgainIfConsumed exn ok)@
+-- compares the stacked input position with the current one,
+-- in case they're the same then continue with @(ok)@,
+-- otherwise, re-'raise' @(exn)@,
+-- without updating the farthest error
+-- (which is usually done when 'fail'ing).
+raiseAgainIfConsumed ::
Cursorable (Cursor inp) =>
InstrBranchable repr =>
InstrExceptionable repr =>
Exception ->
SomeInstr repr inp vs ret ->
SomeInstr repr inp (Cursor inp ': vs) ret
-failIfConsumed exn k =
+raiseAgainIfConsumed exn ok =
pushInput $
lift2Value (splice sameOffset) $
- ifBranch k $
+ ifBranch ok $
case exn of
ExceptionLabel lbl -> raise lbl
ExceptionFailure -> fail Set.empty
instance
( Cursorable (Cursor inp)
, InstrBranchable repr
+ , InstrCallable repr
, InstrExceptionable repr
, InstrInputable repr
+ , InstrIterable repr
, InstrJoinable repr
+ , InstrRegisterable repr
, InstrValuable repr
) => CombFoldable (Program repr inp) where
- {-
- chainPre op p = go <*> p
- where go = (Prod..) <$> op <*> go <|> pure Prod.id
- chainPost p op = p <**> go
- where go = (Prod..) <$> op <*> go <|> pure Prod.id
- -}
+ chainPre (Program op) (Program done) =
+ new (pure Prod.id) $ \(Register r) -> Program $ \next -> do
+ !loopName <- TH.newName "loop"
+ liftM2 (iter (LetName loopName))
+ (op $
+ mapValue (Prod.flip Prod..@ (Prod..)) $
+ modifyRegister r $
+ jump (LetName loopName) )
+ (raiseAgainIfConsumed ExceptionFailure .
+ readRegister r Functor.<$>
+ (done (applyValue next)))
+ chainPost (Program done) (Program op) =
+ new (pure Prod.id) $ \(Register r) -> Program $ \next -> do
+ !loopName <- TH.newName "loop"
+ liftM2 (iter (LetName loopName))
+ (op $
+ modifyRegister (UnscopedRegister (unUnscopedRegister r)) $
+ jump (LetName loopName) )
+ (raiseAgainIfConsumed ExceptionFailure .
+ readRegister r Functor.<$>
+ (done (applyValue next)))
instance
InstrCallable repr =>
- Letable TH.Name (Program repr inp) where
- shareable n (Program sub) = Program $ \next -> do
- sub' <- sub ret
- return $ defLet (HM.singleton n (SomeLet sub')) (call (LetName n) next)
- ref _isRec n = Program $ \case
+ Referenceable TH.Name (Program repr inp) where
+ -- TODO: isRec should be passed to 'call' and 'jump'
+ -- instead of redoing the work with 'CallTrace'.
+ ref isRec name = Program $ \case
-- Tail Call Optimization:
-- returning just after a 'call' is useless:
-- using 'jump' lets the 'ret' of the 'defLet'
-- directly return where it would in two 'ret's.
- Instr Ret{} -> return $ jump (LetName n)
- next -> return $ call (LetName n) next
+ Instr Ret{} -> return $ jump (LetName name)
+ next -> return $ call (LetName name) next
+ {-
+ refable n (Program sub) = Program $ \next -> do
+ sub' <- sub ret
+ return $ defLet (HM.singleton n (SomeLet sub')) (call (LetName n) next)
+ -}
instance
InstrCallable repr =>
Letsable TH.Name (Program repr inp) where
- lets defs (Program x) = Program $ \next -> do
- defs' <- Traversable.traverse (\(SomeLet (Program val)) -> liftM SomeLet (val ret)) defs
- liftM (defLet defs') (x next)
+ lets defs (Program body) = Program $ \next -> do
+ -- Every definition becomes a 'call'able subroutine.
+ defs' <- Traversable.traverse
+ (\(SomeLet (Program val)) -> liftM SomeLet (val ret))
+ defs
+ liftM (defLet defs') (body next)
instance
( Eq (InputToken inp)
, Cursorable (Cursor inp)
( InstrBranchable repr
, InstrJoinable repr
) => CombMatchable (Program repr inp) where
- conditional (Program a) ps bs (Program d) = joinNext $ Program $ \next -> do
- bs' <- Control.Monad.sequence $ (\(Program b) -> b next) Functor.<$> bs
- a =<< liftM (choicesBranch (prodCode Functor.<$> ps) bs') (d next)
+ conditional (Program a) bs (Program d) = joinNext $ Program $ \next -> do
+ bs' <- Control.Monad.sequence $ (\(p, b) -> (prodCode p,) Functor.<$> unProgram b next) Functor.<$> bs
+ a =<< liftM (choicesBranch bs') (d next)
instance
( tok ~ InputToken inp
, InstrReadable tok repr
lr =<< liftM2 caseBranch
(l (swapValue (applyValue next)))
(r (swapValue (applyValue next)))
+instance
+ ( InstrValuable repr
+ , InstrRegisterable repr
+ ) => CombRegisterable (Program repr inp) where
+ new (Program p) k = Program $ \next -> do
+ !regName <- TH.newName "reg"
+ p =<< liftM (newRegister (UnscopedRegister regName))
+ (unProgram (k (Register (UnscopedRegister regName))) next)
+ get (Register r) = Program $ \next ->
+ return $ readRegister r next
+ put (Register r) (Program k) = Program $ \next ->
+ k $ writeRegister r $ pushValue Prod.unit next
+instance
+ ( InstrValuable repr
+ , InstrRegisterable repr
+ ) => CombRegisterableUnscoped (Program repr inp) where
+ newUnscoped r (Program p) k = Program $ \next ->
+ p =<< liftM (newRegister r) (unProgram k next)
+ getUnscoped r = Program $ return . readRegister r
+ putUnscoped r (Program k) = Program $
+ k . writeRegister r . pushValue Prod.unit
import qualified Language.Haskell.TH.Syntax as TH
import Prelude (error)
-import Symantic.Parser.Grammar.ObserveSharing (ShowLetName(..))
+import Symantic.Parser.Grammar.Combinators (UnscopedRegister(..))
+import Symantic.Parser.Grammar.ObserveSharing
import Symantic.Parser.Machine.Instructions
import Symantic.ObserveSharing (SomeLet(..))
import Symantic.Parser.Machine.Generate
data ViewMachine (showName::Bool) inp (vs:: [Type]) a
= ViewMachine
{ viewGen :: Gen inp vs a
- -- ^ Provide 'GenAnalysis', which next important for debugging
+ -- ^ Provide 'GenAnalysis', which is important for debugging
-- and improving golden tests, see 'viewInstrCmd'.
, unViewMachine ::
CallTrace ->
- LetMap GenAnalysis -> -- Output of 'runGenAnalysis'.
+ LetRecs TH.Name GenAnalysis -> -- Output of 'runOpenRecs'.
Tree.Forest (String, String) ->
Tree.Forest (String, String)
}
viewInstrCmd ::
Either TH.Name (Gen inp vs a) ->
CallTrace ->
- LetMap GenAnalysis ->
+ LetRecs TH.Name GenAnalysis ->
(String, String) -> Tree.Forest (String, String) -> Tree.Tree (String, String)
viewInstrCmd gen ct lm (n, no) = Tree.Node $ (n
<> "\nminReads="<>showsPrec 11 (minReads ga) ""
instance Show (ViewMachine sN inp vs a) where
show vm = List.unlines $ drawTrees $
- unViewMachine vm [] (runGenAnalysis (genAnalysisByLet (viewGen vm))) []
+ unViewMachine vm [] (runOpenRecs (genAnalysisByLet (viewGen vm))) []
where
draw :: Tree.Tree (String, String) -> [String]
draw (Tree.Node (x, n) ts0) =
] : next
, viewGen = gen
} where gen = caseBranch (viewGen l) (viewGen r)
- choicesBranch ps bs d = ViewMachine
+ choicesBranch bs d = ViewMachine
{ unViewMachine = \ct lm next ->
- viewInstrCmd (Right gen) ct lm ("choicesBranch "<>show ps, "") (
- ((\b -> viewInstrArg "branch" $ unViewMachine b ct lm []) <$> bs) <>
+ viewInstrCmd (Right gen) ct lm ("choicesBranch", "") (
+ ((\(p, b) -> viewInstrArg ("branch "<>showsPrec 10 p "") $
+ unViewMachine b ct lm []) <$> bs) <>
[ viewInstrArg "default" (unViewMachine d ct lm []) ]
) : next
, viewGen = gen
- } where gen = choicesBranch ps (viewGen <$> bs) (viewGen d)
+ } where gen = choicesBranch ((viewGen <$>) <$> bs) (viewGen d)
instance
ShowLetName sN TH.Name =>
InstrCallable (ViewMachine sN) where
unViewMachine k ct lm next
, viewGen = gen
} where gen = loadInput (viewGen k)
-instance InstrReadable tok Gen => InstrReadable tok (ViewMachine sN) where
+instance
+ InstrReadable tok Gen =>
+ InstrReadable tok (ViewMachine sN) where
read es p k = ViewMachine
{ unViewMachine = \ct lm next ->
viewInstrCmd (Right gen) ct lm ("read "<>showsPrec 10 p "", "") [] :
unViewMachine k ct lm next
, viewGen = gen
} where gen = read es p (viewGen k)
+instance
+ ShowLetName sN TH.Name =>
+ InstrIterable (ViewMachine sN) where
+ iter jumpName@(LetName n) ok ko = ViewMachine
+ { unViewMachine = \ct lm next ->
+ viewInstrCmd (Right gen) ct lm ("iter", " "<>showLetName @sN n)
+ [ viewInstrArg "ok" (unViewMachine ok ct lm [])
+ , viewInstrArg "ko" (unViewMachine ko ct lm [])
+ ] : next
+ , viewGen = gen
+ } where gen = iter jumpName (viewGen ok) (viewGen ko)
+instance
+ ShowLetName sN TH.Name =>
+ InstrRegisterable (ViewMachine sN) where
+ newRegister reg@(UnscopedRegister r) k = ViewMachine
+ { unViewMachine = \ct lm next ->
+ viewInstrCmd (Right gen) ct lm ("newRegister", " "<>showLetName @sN r) [] :
+ unViewMachine k ct lm next
+ , viewGen = gen
+ } where gen = newRegister reg (viewGen k)
+ readRegister reg@(UnscopedRegister r) k = ViewMachine
+ { unViewMachine = \ct lm next ->
+ viewInstrCmd (Right gen) ct lm ("readRegister", " "<>showLetName @sN r) [] :
+ unViewMachine k ct lm next
+ , viewGen = gen
+ } where gen = readRegister reg (viewGen k)
+ writeRegister reg@(UnscopedRegister r) k = ViewMachine
+ { unViewMachine = \ct lm next ->
+ viewInstrCmd (Right gen) ct lm ("writeRegister", " "<>showLetName @sN r) [] :
+ unViewMachine k ct lm next
+ , viewGen = gen
+ } where gen = writeRegister reg (viewGen k)
cabal-version: 3.0
name: symantic-parser
-version: 0.2.0.20210703
+version: 0.2.1.20210728
synopsis: Parser combinators statically optimized and staged via typed meta-programming
description:
This is a work-in-progress experimental library to generate parsers,
leveraging Tagless-Final interpreters and Typed Template Haskell staging.
- .
+
This is an alternative but less powerful/reviewed
implementation of [ParsleyHaskell](https://github.com/J-mie6/ParsleyHaskell).
See the paper by Jamie Willis, Nicolas Wu, and Matthew Pickering,
transformers >= 0.4,
unix >= 2.7,
unordered-containers
+ -- ghc-options: -ddump-splices
test-suite symantic-parser-test
import: boilerplate
goldens :: TestTree
goldens = testGroup "Grammar" $
[ testGroup "ViewGrammar" $
- (\f -> List.zipWith f Grammar.grammars [1::Int ..]) $ \gram g ->
- let grammarFile = getGoldenDir $ "Grammar/ViewGrammar/G"<>show g<>".expected.txt" in
- goldenVsStringDiff ("G"<>show g) goldenDiff grammarFile $ do
+ (\f -> List.zipWith f Grammar.grammars [1::Int ..]) $ \g gNum ->
+ let grammarFile = getGoldenDir $ "Grammar/ViewGrammar/G"<>show gNum<>".expected.txt" in
+ goldenVsStringDiff ("G"<>show gNum) goldenDiff grammarFile $ do
resetTHNameCounter
return $ fromString $ show $
- P.viewGrammar @'False gram
+ P.viewGrammar @'False g
, testGroup "OptimizeGrammar" $
- (\f -> List.zipWith f Grammar.grammars [1::Int ..]) $ \gram g ->
- let grammarFile = getGoldenDir $ "Grammar/OptimizeGrammar/G"<>show g<>".expected.txt" in
- goldenVsStringDiff ("G"<>show g) goldenDiff grammarFile $ do
+ (\f -> List.zipWith f Grammar.grammars [1::Int ..]) $ \g gNum ->
+ let grammarFile = getGoldenDir $ "Grammar/OptimizeGrammar/G"<>show gNum<>".expected.txt" in
+ goldenVsStringDiff ("G"<>show gNum) goldenDiff grammarFile $ do
resetTHNameCounter
return $ fromString $ show $
P.viewGrammar @'False $
- P.optimizeGrammar gram
+ P.optimizeGrammar g
]
lets
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'a' (x_1 x_2))
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
` <*>
+ <*>
- | + pure (\x_0 -> \x_1 -> GHC.Show.show (x_0 GHC.Types.[]))
- | ` ref <hidden>
+ | + pure (\x_0 -> \x_1 -> GHC.Show.show x_0)
+ | ` chainPre
+ | + <*>
+ | | + pure (\x_0 -> (GHC.Types.:) 'a')
+ | | ` satisfy
+ | ` pure GHC.Types.[]
` satisfy
lets
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) x_0 (x_1 x_2))
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
` <*>
+ <*>
- | + pure (\x_0 -> \x_1 -> GHC.Show.show (x_0 GHC.Types.[]))
- | ` ref <hidden>
+ | + pure (\x_0 -> \x_1 -> GHC.Show.show x_0)
+ | ` chainPre
+ | + <*>
+ | | + pure (GHC.Types.:)
+ | | ` satisfy
+ | ` pure GHC.Types.[]
` eof
+ let <hidden>
| ` <*>
| + pure (\x_0 -> GHC.Tuple.())
-| ` ref <hidden>
+| ` chainPost
+| + pure GHC.Tuple.()
+| ` <*>
+| + pure (\x_0 -> \x_1 -> x_1)
+| ` satisfy
+ let <hidden>
-| ` <*>
-| + pure (\x_0 -> x_0 GHC.Types.[])
-| ` ref <hidden>
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> (GHC.Types.:) x_0 (x_2 x_3))
-| | | | ` 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
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> Parsers.Brainfuck.Types.Loop x_2)
-| | | | | | | | ` satisfy
-| | | | | | | ` ref <hidden>
-| | | | | | ` rec <hidden>
-| | | | | ` satisfy
-| | | | ` failure
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
+| ` chainPre
| + <*>
| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_1 x_2)
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
+| | | + 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
+| | | | ` <*>
+| | | | + <*>
+| | | | | + <*>
+| | | | | | + <*>
+| | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> Parsers.Brainfuck.Types.Loop x_2)
+| | | | | | | ` satisfy
+| | | | | | ` ref <hidden>
+| | | | | ` rec <hidden>
+| | | | ` satisfy
+| | | ` failure
+| | ` ref <hidden>
+| ` pure GHC.Types.[]
` <*>
+ <*>
| + pure (\x_0 -> \x_1 -> GHC.Show.show x_1)
+ let <hidden>
| ` <*>
| + <*>
+| | + pure (\x_0 -> \x_1 -> GHC.Tuple.())
+| | ` ref <hidden>
+| ` chainPost
+| + pure GHC.Tuple.()
+| ` <*>
+| + pure (\x_0 -> \x_1 -> x_1)
+| ` ref <hidden>
++ let <hidden>
+| ` <*>
+| + <*>
| | + <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
-| | | | ` ref <hidden>
+| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_2)
| | | ` ref <hidden>
-| | ` ref <hidden>
+| | ` chainPost
+| | + ref <hidden>
+| | ` <*>
+| | + <*>
+| | | + <*>
+| | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
+| | | | ` satisfy
+| | | ` ref <hidden>
+| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
| ` <*>
| | | + <*>
| | | | + <*>
| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> x_4)
-| | | | | | | ` satisfy
-| | | | | | ` ref <hidden>
+| | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> GHC.Tuple.())
+| | | | | | ` satisfy
| | | | | ` ref <hidden>
| | | | ` ref <hidden>
-| | | ` ref <hidden>
+| | | ` chainPost
+| | | + pure GHC.Tuple.()
+| | | ` <*>
+| | | + pure (\x_0 -> \x_1 -> x_1)
+| | | ` ref <hidden>
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| | | + <*>
| | | | + <*>
| | | | | + <*>
-| | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> GHC.Tuple.())
+| | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> x_3)
| | | | | | ` satisfy
| | | | | ` ref <hidden>
-| | | | ` ref <hidden>
+| | | | ` chainPost
+| | | | + ref <hidden>
+| | | | ` <*>
+| | | | + pure (\x_0 -> \x_1 -> x_1)
+| | | | ` <|>
+| | | | + <*>
+| | | | | + <*>
+| | | | | | + pure (\x_0 -> \x_1 -> x_1)
+| | | | | | ` try
+| | | | | | ` <*>
+| | | | | | + <*>
+| | | | | | | + pure (\x_0 -> \x_1 -> (GHC.Types.:) 'i' ((GHC.Types.:) 'f' GHC.Types.[]))
+| | | | | | | ` satisfy
+| | | | | | ` satisfy
+| | | | | ` ref <hidden>
+| | | | ` <|>
+| | | | + <*>
+| | | | | + <*>
+| | | | | | + <*>
+| | | | | | | + <*>
+| | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
+| | | | | | | | ` try
+| | | | | | | | ` <*>
+| | | | | | | | + <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + <*>
+| | | | | | | | | | | + <*>
+| | | | | | | | | | | | + 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
+| | | | | | | ` ref <hidden>
+| | | | | | ` ref <hidden>
+| | | | | ` rec <hidden>
+| | | | ` <|>
+| | | | + try
+| | | | | ` <*>
+| | | | | + <*>
+| | | | | | + <*>
+| | | | | | | + <*>
+| | | | | | | | + <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + <*>
+| | | | | | | | | | | + <*>
+| | | | | | | | | | | | + <*>
+| | | | | | | | | | | | | + <*>
+| | | | | | | | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> \x_7 -> \x_8 -> \x_9 -> x_8)
+| | | | | | | | | | | | | | ` <|>
+| | | | | | | | | | | | | | + <*>
+| | | | | | | | | | | | | | | + <*>
+| | | | | | | | | | | | | | | | + pure (\x_0 -> \x_1 -> GHC.Tuple.())
+| | | | | | | | | | | | | | | | ` try
+| | | | | | | | | | | | | | | | ` <*>
+| | | | | | | | | | | | | | | | + <*>
+| | | | | | | | | | | | | | | | | + <*>
+| | | | | | | | | | | | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'v' ((GHC.Types.:) 'a' ((GHC.Types.:) 'r' GHC.Types.[])))
+| | | | | | | | | | | | | | | | | | ` satisfy
+| | | | | | | | | | | | | | | | | ` satisfy
+| | | | | | | | | | | | | | | | ` satisfy
+| | | | | | | | | | | | | | | ` ref <hidden>
+| | | | | | | | | | | | | | ` ref <hidden>
+| | | | | | | | | | | | | ` ref <hidden>
+| | | | | | | | | | | | ` chainPost
+| | | | | | | | | | | | + ref <hidden>
+| | | | | | | | | | | | ` <*>
+| | | | | | | | | | | | + <*>
+| | | | | | | | | | | | | + <*>
+| | | | | | | | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
+| | | | | | | | | | | | | | ` ref <hidden>
+| | | | | | | | | | | | | ` ref <hidden>
+| | | | | | | | | | | | ` ref <hidden>
+| | | | | | | | | | | ` ref <hidden>
+| | | | | | | | | | ` satisfy
+| | | | | | | | | ` ref <hidden>
+| | | | | | | | ` ref <hidden>
+| | | | | | | ` chainPost
+| | | | | | | + ref <hidden>
+| | | | | | | ` <*>
+| | | | | | | + <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
+| | | | | | | | | ` ref <hidden>
+| | | | | | | | ` ref <hidden>
+| | | | | | | ` ref <hidden>
+| | | | | | ` ref <hidden>
+| | | | | ` ref <hidden>
+| | | | ` <*>
+| | | | + <*>
+| | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | ` ref <hidden>
+| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\x_0 -> \x_1 -> GHC.Tuple.())
-| | ` ref <hidden>
-| ` ref <hidden>
-+ let <hidden>
-| ` <*>
-| + <*>
| | + pure (\x_0 -> \x_1 -> x_1)
| | ` satisfy
| ` ref <hidden>
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
-| | | | | ` satisfy
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
+| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_2)
+| | | | ` satisfy
+| | | ` chainPost
+| | | + ref <hidden>
+| | | ` <*>
+| | | + pure (\x_0 -> \x_1 -> x_1)
+| | | ` satisfy
| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
| | | | + <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> GHC.Tuple.())
-| | | | | | | | ` rec <hidden>
-| | | | | | | ` ref <hidden>
-| | | | | | ` ref <hidden>
+| | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
+| | | | | | | ` rec <hidden>
+| | | | | | ` chainPost
+| | | | | | + ref <hidden>
+| | | | | | ` <*>
+| | | | | | + <*>
+| | | | | | | + <*>
+| | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
+| | | | | | | | ` ref <hidden>
+| | | | | | | ` ref <hidden>
+| | | | | | ` rec <hidden>
| | | | | ` ref <hidden>
| | | | ` ref <hidden>
| | | ` ref <hidden>
| + <*>
| | + <*>
| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> x_0 x_2 (x_3 x_4))
-| | | | | ` ref <hidden>
-| | | | ` ref <hidden>
-| | | ` rec <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + <*>
-| | | | | | | | + <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> \x_7 -> \x_8 -> \x_9 -> x_8 x_9)
-| | | | | | | | | | ` try
-| | | | | | | | | | ` <*>
-| | | | | | | | | | + <*>
-| | | | | | | | | | | + <*>
-| | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | | | + 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
-| | | | | | | | | ` ref <hidden>
-| | | | | | | | ` ref <hidden>
-| | | | | | | ` ref <hidden>
-| | | | | | ` ref <hidden>
-| | | | | ` <|>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
-| | | | | | | | ` satisfy
-| | | | | | | ` ref <hidden>
-| | | | | | ` ref <hidden>
-| | | | | ` ref <hidden>
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> x_0 x_2 (x_3 x_4))
-| | | | | ` ref <hidden>
+| | | | + pure (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> x_0 x_2 (x_3 x_4))
-| | | | | ` ref <hidden>
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> x_0 x_2 (x_3 x_4))
-| | | | | ` ref <hidden>
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> x_3 x_4)
-| | | | | ` satisfy
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_1 x_2)
-| | | ` <|>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> x_1)
-| | | | | ` try
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + pure (\x_0 -> \x_1 -> (GHC.Types.:) 'i' ((GHC.Types.:) 'f' GHC.Types.[]))
-| | | | | | ` satisfy
-| | | | | ` satisfy
-| | | | ` ref <hidden>
-| | | ` <|>
+| | | ` chainPost
+| | | + ref <hidden>
+| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
-| | | | | | | ` try
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + <*>
-| | | | | | | | | | | + 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
-| | | | | | ` ref <hidden>
+| | | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
| | | | | ` ref <hidden>
-| | | | ` rec <hidden>
-| | | ` <|>
-| | | + try
-| | | | ` <*>
-| | | | + <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + <*>
-| | | | | | | | + <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + <*>
-| | | | | | | | | | | + <*>
-| | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> \x_7 -> \x_8 -> \x_9 -> \x_10 -> \x_11 -> x_10)
-| | | | | | | | | | | | | | | ` <|>
-| | | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | | | + pure (\x_0 -> \x_1 -> GHC.Tuple.())
-| | | | | | | | | | | | | | | | | ` try
-| | | | | | | | | | | | | | | | | ` <*>
-| | | | | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'v' ((GHC.Types.:) 'a' ((GHC.Types.:) 'r' GHC.Types.[])))
-| | | | | | | | | | | | | | | | | | | ` satisfy
-| | | | | | | | | | | | | | | | | | ` satisfy
-| | | | | | | | | | | | | | | | | ` satisfy
-| | | | | | | | | | | | | | | | ` ref <hidden>
-| | | | | | | | | | | | | | | ` ref <hidden>
-| | | | | | | | | | | | | | ` ref <hidden>
-| | | | | | | | | | | | | ` ref <hidden>
-| | | | | | | | | | | | ` ref <hidden>
-| | | | | | | | | | | ` ref <hidden>
-| | | | | | | | | | ` satisfy
-| | | | | | | | | ` ref <hidden>
-| | | | | | | | ` ref <hidden>
-| | | | | | | ` ref <hidden>
-| | | | | | ` ref <hidden>
-| | | | | ` ref <hidden>
-| | | | ` ref <hidden>
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_1 x_2)
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_1 x_2)
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_1 x_2)
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> GHC.Tuple.())
-| | | | | ` ref <hidden>
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
+| | | | ` ref <hidden>
+| | | ` ref <hidden>
| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
+ <*>
| + <*>
| | + <*>
- | | | + <*>
- | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> GHC.Show.show x_3)
- | | | | ` ref <hidden>
+ | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> GHC.Show.show x_2)
| | | ` ref <hidden>
- | | ` ref <hidden>
+ | | ` chainPost
+ | | + ref <hidden>
+ | | ` <*>
+ | | + <*>
+ | | | + <*>
+ | | | | + <*>
+ | | | | | + <*>
+ | | | | | | + <*>
+ | | | | | | | + <*>
+ | | | | | | | | + <*>
+ | | | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> \x_7 -> \x_8 -> x_8)
+ | | | | | | | | | ` try
+ | | | | | | | | | ` <*>
+ | | | | | | | | | + <*>
+ | | | | | | | | | | + <*>
+ | | | | | | | | | | | + <*>
+ | | | | | | | | | | | | + <*>
+ | | | | | | | | | | | | | + <*>
+ | | | | | | | | | | | | | | + <*>
+ | | | | | | | | | | | | | | | + <*>
+ | | | | | | | | | | | | | | | | + 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
+ | | | | | | | | ` ref <hidden>
+ | | | | | | | ` ref <hidden>
+ | | | | | | ` ref <hidden>
+ | | | | | ` ref <hidden>
+ | | | | ` <|>
+ | | | | + <*>
+ | | | | | + <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
+ | | | | | | | ` satisfy
+ | | | | | | ` ref <hidden>
+ | | | | | ` ref <hidden>
+ | | | | ` ref <hidden>
+ | | | ` ref <hidden>
+ | | ` ref <hidden>
| ` ref <hidden>
` eof
lets
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'a' (x_1 x_2))
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
` <*>
- + pure (\x_0 -> GHC.Show.show (x_0 GHC.Types.[]))
- ` ref <hidden>
+ + pure GHC.Show.show
+ ` chainPre
+ + <*>
+ | + pure (\x_0 -> (GHC.Types.:) 'a')
+ | ` satisfy
+ ` pure GHC.Types.[]
lets
+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) x_0 (x_1 x_2))
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
| ` try
| ` <*>
| + <*>
| ` satisfy
` <*>
+ <*>
- | + pure (\x_0 -> \x_1 -> GHC.Show.show ((GHC.Types.:) x_0 (x_1 GHC.Types.[])))
+ | + pure (\x_0 -> \x_1 -> GHC.Show.show ((GHC.Types.:) x_0 x_1))
| ` ref <hidden>
- ` ref <hidden>
+ ` chainPre
+ + <*>
+ | + pure (GHC.Types.:)
+ | ` ref <hidden>
+ ` pure GHC.Types.[]
lets
+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) x_0 (x_1 x_2))
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
| ` try
| ` <*>
| + <*>
` <*>
+ <*>
| + <*>
- | | + pure (\x_0 -> \x_1 -> \x_2 -> GHC.Show.show ((GHC.Types.:) x_0 (x_1 GHC.Types.[])))
+ | | + pure (\x_0 -> \x_1 -> \x_2 -> GHC.Show.show ((GHC.Types.:) x_0 x_1))
| | ` ref <hidden>
- | ` ref <hidden>
+ | ` chainPre
+ | + <*>
+ | | + pure (GHC.Types.:)
+ | | ` ref <hidden>
+ | ` pure GHC.Types.[]
` eof
lets
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'r' (x_1 x_2))
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
` <*>
+ <*>
- | + pure (\x_0 -> \x_1 -> GHC.Show.show (x_0 GHC.Types.[]))
- | ` ref <hidden>
+ | + pure (\x_0 -> \x_1 -> GHC.Show.show x_0)
+ | ` chainPre
+ | + <*>
+ | | + pure (\x_0 -> (GHC.Types.:) 'r')
+ | | ` satisfy
+ | ` pure GHC.Types.[]
` eof
lets
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + pure (GHC.Types.:)
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | ` pure 'a'
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
` <*>
+ pure GHC.Show.show
` <*>
+ <*>
| + pure (\x_0 -> \x_1 -> x_0)
- | ` <*>
- | + ref <hidden>
+ | ` chainPre
+ | + <*>
+ | | + pure (GHC.Types.:)
+ | | ` <*>
+ | | + <*>
+ | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | ` pure 'a'
+ | | ` satisfy
| ` pure GHC.Types.[]
` <*>
+ <*>
lets
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + pure (GHC.Types.:)
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
` <*>
+ pure GHC.Show.show
` <*>
+ <*>
| + pure (\x_0 -> \x_1 -> x_0)
- | ` <*>
- | + ref <hidden>
+ | ` chainPre
+ | + <*>
+ | | + pure (GHC.Types.:)
+ | | ` satisfy
| ` pure GHC.Types.[]
` eof
| | + <*>
| | | + pure (\x_0 -> \x_1 -> x_0)
| | | ` pure (\x_0 -> x_0)
+| | ` chainPost
+| | + pure GHC.Tuple.()
+| | ` <*>
+| | + <*>
+| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
+| | | ` pure (\x_0 -> \x_1 -> x_0)
+| | ` satisfy
+| ` pure GHC.Tuple.()
++ let <hidden>
+| ` chainPre
+| + <*>
+| | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
-| | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | ` pure GHC.Tuple.()
+| | | + 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
+| | | | ` <*>
+| | | | + <*>
+| | | | | + 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
| | ` ref <hidden>
-| ` pure GHC.Tuple.()
-+ let <hidden>
-| ` <*>
-| + ref <hidden>
| ` pure GHC.Types.[]
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | | ` pure (\x_0 -> \x_1 -> x_0)
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + pure (GHC.Types.:)
-| | | ` <*>
-| | | + <*>
-| | | | + 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
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + 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
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
` <*>
+ pure GHC.Show.show
` <*>
| | + <*>
| | | + pure (\x_0 -> \x_1 -> x_0)
| | | ` pure (\x_0 -> x_0)
-| | ` <*>
-| | + <*>
-| | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | ` pure GHC.Tuple.()
-| | ` ref <hidden>
+| | ` chainPost
+| | + pure GHC.Tuple.()
+| | ` <*>
+| | + <*>
+| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
+| | | ` pure (\x_0 -> \x_1 -> x_0)
+| | ` ref <hidden>
| ` pure GHC.Tuple.()
+ let <hidden>
| ` <*>
| | + <*>
| | | + pure (\x_0 -> \x_1 -> x_0)
| | | ` pure (\x_0 -> x_0)
-| | ` <*>
-| | + <*>
-| | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | ` ref <hidden>
-| | ` ref <hidden>
+| | ` chainPost
+| | + ref <hidden>
+| | ` <*>
+| | + <*>
+| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
+| | | ` 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)
+| | | | ` <*>
+| | | | + <*>
+| | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | ` pure '!'
+| | | | ` satisfy
+| | | ` ref <hidden>
+| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
| ` <*>
| | | + <*>
| | | | + pure (\x_0 -> \x_1 -> x_0)
| | | | ` pure (\x_0 -> x_0)
-| | | ` <*>
-| | | + <*>
-| | | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | ` pure GHC.Tuple.()
-| | | ` ref <hidden>
+| | | ` chainPost
+| | | + pure GHC.Tuple.()
+| | | ` <*>
+| | | + <*>
+| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
+| | | | ` pure (\x_0 -> \x_1 -> x_0)
+| | | ` ref <hidden>
| | ` pure GHC.Tuple.()
| ` <*>
| + <*>
| | | + <*>
| | | | + pure (\x_0 -> \x_1 -> x_0)
| | | | ` pure (\x_0 -> x_0)
-| | | ` <*>
-| | | + <*>
-| | | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
+| | | ` chainPost
+| | | + ref <hidden>
+| | | ` <*>
+| | | + <*>
+| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
+| | | | ` pure (\x_0 -> \x_1 -> x_0)
+| | | ` <|>
+| | | + <|>
+| | | | + <|>
+| | | | | + <*>
+| | | | | | + <*>
+| | | | | | | + <*>
+| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | ` try
+| | | | | | | ` <*>
+| | | | | | | + <*>
+| | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | ` <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | ` pure 'i'
+| | | | | | | | ` satisfy
+| | | | | | | ` <*>
+| | | | | | | + <*>
+| | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | ` <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | ` pure 'f'
+| | | | | | | | ` satisfy
+| | | | | | | ` pure GHC.Types.[]
+| | | | | | ` ref <hidden>
+| | | | | ` <*>
+| | | | | + <*>
+| | | | | | + <*>
+| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | ` <*>
+| | | | | | + <*>
+| | | | | | | + <*>
+| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | ` <*>
+| | | | | | | + <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | | ` try
+| | | | | | | | ` <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | | ` <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | ` pure 'w'
+| | | | | | | | | ` satisfy
+| | | | | | | | ` <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | | ` <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | ` pure 'h'
+| | | | | | | | | ` satisfy
+| | | | | | | | ` <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | | ` <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | ` pure 'i'
+| | | | | | | | | ` satisfy
+| | | | | | | | ` <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | | ` <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | ` pure 'l'
+| | | | | | | | | ` satisfy
+| | | | | | | | ` <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | | ` <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | ` pure 'e'
+| | | | | | | | | ` satisfy
+| | | | | | | | ` pure GHC.Types.[]
+| | | | | | | ` ref <hidden>
+| | | | | | ` ref <hidden>
+| | | | | ` rec <hidden>
+| | | | ` try
+| | | | ` <*>
+| | | | + <*>
+| | | | | + 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)
+| | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | ` <*>
+| | | | | | | + <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | | ` <|>
+| | | | | | | | + <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | ` pure GHC.Tuple.()
+| | | | | | | | | ` <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + <*>
+| | | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | | | | ` try
+| | | | | | | | | | ` <*>
+| | | | | | | | | | + <*>
+| | | | | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | | | | ` <*>
+| | | | | | | | | | | + <*>
+| | | | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | | | ` pure 'v'
+| | | | | | | | | | | ` satisfy
+| | | | | | | | | | ` <*>
+| | | | | | | | | | + <*>
+| | | | | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | | | | ` <*>
+| | | | | | | | | | | + <*>
+| | | | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | | | ` pure 'a'
+| | | | | | | | | | | ` satisfy
+| | | | | | | | | | ` <*>
+| | | | | | | | | | + <*>
+| | | | | | | | | | | + pure (GHC.Types.:)
+| | | | | | | | | | | ` <*>
+| | | | | | | | | | | + <*>
+| | | | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | | | ` pure 'r'
+| | | | | | | | | | | ` satisfy
+| | | | | | | | | | ` pure GHC.Types.[]
+| | | | | | | | | ` ref <hidden>
+| | | | | | | | ` ref <hidden>
+| | | | | | | ` <*>
+| | | | | | | + <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | | ` ref <hidden>
+| | | | | | | ` <*>
+| | | | | | | + <*>
+| | | | | | | | + <*>
+| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | | ` chainPost
+| | | | | | | | + ref <hidden>
+| | | | | | | | ` <*>
+| | | | | | | | + ref <hidden>
+| | | | | | | | ` <*>
+| | | | | | | | + <*>
+| | | | | | | | | + <*>
+| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | | | ` ref <hidden>
+| | | | | | | | ` ref <hidden>
+| | | | | | | ` ref <hidden>
+| | | | | | ` <*>
+| | | | | | + <*>
+| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | ` <*>
+| | | | | | | + <*>
+| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | ` pure '='
+| | | | | | | ` satisfy
+| | | | | | ` ref <hidden>
+| | | | | ` <*>
+| | | | | + <*>
+| | | | | | + <*>
+| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | ` ref <hidden>
+| | | | | ` <*>
+| | | | | + <*>
+| | | | | | + <*>
+| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | ` chainPost
+| | | | | | + ref <hidden>
+| | | | | | ` <*>
+| | | | | | + ref <hidden>
+| | | | | | ` <*>
+| | | | | | + <*>
+| | | | | | | + <*>
+| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | ` ref <hidden>
+| | | | | | ` ref <hidden>
+| | | | | ` ref <hidden>
+| | | | ` ref <hidden>
+| | | ` <*>
+| | | + <*>
+| | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | ` ref <hidden>
+| | | ` ref <hidden>
| | ` ref <hidden>
| ` <*>
| + <*>
| | | + <*>
| | | | + pure (\x_0 -> \x_1 -> x_0)
| | | | ` pure (\x_0 -> x_0)
-| | | ` <*>
-| | | + <*>
-| | | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
+| | | ` chainPost
+| | | + ref <hidden>
+| | | ` <*>
+| | | + <*>
+| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
+| | | | ` pure (\x_0 -> \x_1 -> x_0)
+| | | ` satisfy
| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | | ` 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)
-| | | | | | ` pure (\x_0 -> x_0)
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | ` <*>
-| | | | | | + <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | ` try
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 'f'
-| | | | | | | | ` satisfy
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 'u'
-| | | | | | | | ` satisfy
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 'n'
-| | | | | | | | ` satisfy
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 'c'
-| | | | | | | | ` satisfy
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 't'
-| | | | | | | | ` satisfy
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 'i'
-| | | | | | | | ` satisfy
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 'o'
-| | | | | | | | ` satisfy
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 'n'
-| | | | | | | | ` satisfy
-| | | | | | | ` pure GHC.Types.[]
-| | | | | | ` ref <hidden>
-| | | | | ` ref <hidden>
-| | | | ` <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | ` ref <hidden>
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | ` ref <hidden>
-| | | | | ` <|>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | ` pure GHC.Tuple.()
-| | | | | | ` <*>
-| | | | | | + <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure ':'
-| | | | | | | | ` satisfy
-| | | | | | | ` ref <hidden>
-| | | | | | ` ref <hidden>
-| | | | | ` ref <hidden>
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | | ` 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)
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | ` pure '!'
-| | | | | ` satisfy
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | | ` pure (\x_0 -> \x_1 -> x_0)
-| | | ` <|>
-| | | + <|>
-| | | | + <|>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | ` try
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 'i'
-| | | | | | | | ` satisfy
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure 'f'
-| | | | | | | | ` satisfy
-| | | | | | | ` pure GHC.Types.[]
-| | | | | | ` ref <hidden>
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | ` <*>
-| | | | | | + <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | | ` try
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | | ` <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | ` pure 'w'
-| | | | | | | | | ` satisfy
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | | ` <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | ` pure 'h'
-| | | | | | | | | ` satisfy
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | | ` <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | ` pure 'i'
-| | | | | | | | | ` satisfy
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | | ` <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | ` pure 'l'
-| | | | | | | | | ` satisfy
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | | ` <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | ` pure 'e'
-| | | | | | | | | ` satisfy
-| | | | | | | | ` pure GHC.Types.[]
-| | | | | | | ` ref <hidden>
-| | | | | | ` ref <hidden>
-| | | | | ` rec <hidden>
-| | | | ` try
-| | | | ` <*>
-| | | | + <*>
-| | | | | + 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)
-| | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | | ` <|>
-| | | | | | | | + <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | ` pure GHC.Tuple.()
-| | | | | | | | | ` <*>
-| | | | | | | | | + <*>
-| | | | | | | | | | + <*>
-| | | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | | | | ` try
-| | | | | | | | | | ` <*>
-| | | | | | | | | | + <*>
-| | | | | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | | | | ` <*>
-| | | | | | | | | | | + <*>
-| | | | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | ` pure 'v'
-| | | | | | | | | | | ` satisfy
-| | | | | | | | | | ` <*>
-| | | | | | | | | | + <*>
-| | | | | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | | | | ` <*>
-| | | | | | | | | | | + <*>
-| | | | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | ` pure 'a'
-| | | | | | | | | | | ` satisfy
-| | | | | | | | | | ` <*>
-| | | | | | | | | | + <*>
-| | | | | | | | | | | + pure (GHC.Types.:)
-| | | | | | | | | | | ` <*>
-| | | | | | | | | | | + <*>
-| | | | | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | ` pure 'r'
-| | | | | | | | | | | ` satisfy
-| | | | | | | | | | ` pure GHC.Types.[]
-| | | | | | | | | ` ref <hidden>
-| | | | | | | | ` ref <hidden>
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | | ` ref <hidden>
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | | | ` <*>
-| | | | | | | | + <*>
-| | | | | | | | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | | | | | | ` ref <hidden>
-| | | | | | | | ` ref <hidden>
-| | | | | | | ` ref <hidden>
-| | | | | | ` <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | ` <*>
-| | | | | | | + <*>
-| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | | ` pure '='
-| | | | | | | ` satisfy
-| | | | | | ` ref <hidden>
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | ` ref <hidden>
-| | | | | ` <*>
-| | | | | + <*>
-| | | | | | + <*>
-| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | ` <*>
-| | | | | | + <*>
-| | | | | | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | | | | ` ref <hidden>
-| | | | | | ` ref <hidden>
-| | | | | ` ref <hidden>
-| | | | ` ref <hidden>
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | | ` pure (\x_0 -> \x_1 -> x_0)
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | | ` pure (\x_0 -> \x_1 -> x_0)
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | | ` pure (\x_0 -> \x_1 -> x_0)
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + ref <hidden>
-| | | ` <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | ` pure (\x_0 -> x_0)
-| | | | ` ref <hidden>
-| | | ` rec <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + ref <hidden>
-| | | ` <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | ` pure (\x_0 -> x_0)
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + ref <hidden>
-| | | ` <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | ` pure (\x_0 -> x_0)
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + ref <hidden>
-| | | ` <*>
-| | | + <*>
-| | | | + <*>
-| | | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | | ` pure (\x_0 -> x_0)
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
| | | + pure (\x_0 -> \x_1 -> x_0)
| | | ` pure GHC.Tuple.()
| | ` <*>
| | | + <*>
| | | | + pure (\x_0 -> \x_1 -> x_0)
| | | | ` pure (\x_0 -> x_0)
-| | | ` <*>
-| | | + <*>
-| | | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | ` ref <hidden>
-| | | ` ref <hidden>
+| | | ` chainPost
+| | | + ref <hidden>
+| | | ` <*>
+| | | + ref <hidden>
+| | | ` <*>
+| | | + <*>
+| | | | + <*>
+| | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | ` pure (\x_0 -> x_0)
+| | | | ` ref <hidden>
+| | | ` ref <hidden>
| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
| | | | | | + <*>
| | | | | | | + pure (\x_0 -> \x_1 -> x_0)
| | | | | | | ` pure (\x_0 -> x_0)
-| | | | | | ` <*>
-| | | | | | + <*>
-| | | | | | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | | | | ` ref <hidden>
-| | | | | | ` ref <hidden>
+| | | | | | ` chainPost
+| | | | | | + ref <hidden>
+| | | | | | ` <*>
+| | | | | | + ref <hidden>
+| | | | | | ` <*>
+| | | | | | + <*>
+| | | | | | | + <*>
+| | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+| | | | | | | | ` pure (\x_0 -> x_0)
+| | | | | | | ` ref <hidden>
+| | | | | | ` rec <hidden>
| | | | | ` ref <hidden>
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | + <*>
| | | + pure (\x_0 -> \x_1 -> x_0)
| | | ` pure (\x_0 -> x_0)
- | | ` <*>
- | | + <*>
- | | | + pure ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
- | | | ` ref <hidden>
- | | ` ref <hidden>
+ | | ` chainPost
+ | | + ref <hidden>
+ | | ` <*>
+ | | + <*>
+ | | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
+ | | | ` 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)
+ | | | | | ` pure (\x_0 -> x_0)
+ | | | | ` <*>
+ | | | | + <*>
+ | | | | | + <*>
+ | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | ` pure (\x_0 -> x_0)
+ | | | | | ` <*>
+ | | | | | + <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | ` pure (\x_0 -> x_0)
+ | | | | | | ` try
+ | | | | | | ` <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (GHC.Types.:)
+ | | | | | | | ` <*>
+ | | | | | | | + <*>
+ | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | | ` pure 'f'
+ | | | | | | | ` satisfy
+ | | | | | | ` <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (GHC.Types.:)
+ | | | | | | | ` <*>
+ | | | | | | | + <*>
+ | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | | ` pure 'u'
+ | | | | | | | ` satisfy
+ | | | | | | ` <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (GHC.Types.:)
+ | | | | | | | ` <*>
+ | | | | | | | + <*>
+ | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | | ` pure 'n'
+ | | | | | | | ` satisfy
+ | | | | | | ` <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (GHC.Types.:)
+ | | | | | | | ` <*>
+ | | | | | | | + <*>
+ | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | | ` pure 'c'
+ | | | | | | | ` satisfy
+ | | | | | | ` <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (GHC.Types.:)
+ | | | | | | | ` <*>
+ | | | | | | | + <*>
+ | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | | ` pure 't'
+ | | | | | | | ` satisfy
+ | | | | | | ` <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (GHC.Types.:)
+ | | | | | | | ` <*>
+ | | | | | | | + <*>
+ | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | | ` pure 'i'
+ | | | | | | | ` satisfy
+ | | | | | | ` <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (GHC.Types.:)
+ | | | | | | | ` <*>
+ | | | | | | | + <*>
+ | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | | ` pure 'o'
+ | | | | | | | ` satisfy
+ | | | | | | ` <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (GHC.Types.:)
+ | | | | | | | ` <*>
+ | | | | | | | + <*>
+ | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | | ` pure 'n'
+ | | | | | | | ` satisfy
+ | | | | | | ` pure GHC.Types.[]
+ | | | | | ` ref <hidden>
+ | | | | ` ref <hidden>
+ | | | ` <*>
+ | | | + <*>
+ | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | ` <*>
+ | | | | + <*>
+ | | | | | + <*>
+ | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | ` pure (\x_0 -> x_0)
+ | | | | | ` ref <hidden>
+ | | | | ` <*>
+ | | | | + <*>
+ | | | | | + <*>
+ | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | ` pure (\x_0 -> x_0)
+ | | | | | ` ref <hidden>
+ | | | | ` <|>
+ | | | | + <*>
+ | | | | | + <*>
+ | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | ` pure GHC.Tuple.()
+ | | | | | ` <*>
+ | | | | | + <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | ` pure (\x_0 -> x_0)
+ | | | | | | ` <*>
+ | | | | | | + <*>
+ | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | ` <*>
+ | | | | | | | + <*>
+ | | | | | | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | | | | | | ` pure ':'
+ | | | | | | | ` satisfy
+ | | | | | | ` ref <hidden>
+ | | | | | ` ref <hidden>
+ | | | | ` ref <hidden>
+ | | | ` ref <hidden>
+ | | ` ref <hidden>
| ` ref <hidden>
` eof
lets
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + pure (GHC.Types.:)
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | ` pure 'a'
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
` <*>
+ pure GHC.Show.show
- ` <*>
- + ref <hidden>
+ ` chainPre
+ + <*>
+ | + pure (GHC.Types.:)
+ | ` <*>
+ | + <*>
+ | | + pure (\x_0 -> \x_1 -> x_0)
+ | | ` pure 'a'
+ | ` satisfy
` pure GHC.Types.[]
lets
+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + pure (GHC.Types.:)
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
| ` try
| ` <*>
| + <*>
+ <*>
| + pure (GHC.Types.:)
| ` ref <hidden>
- ` <*>
- + ref <hidden>
+ ` chainPre
+ + <*>
+ | + pure (GHC.Types.:)
+ | ` ref <hidden>
` pure GHC.Types.[]
lets
+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + pure (GHC.Types.:)
-| | | ` ref <hidden>
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
-+ let <hidden>
| ` try
| ` <*>
| + <*>
| + <*>
| | + pure (GHC.Types.:)
| | ` ref <hidden>
- | ` <*>
- | + ref <hidden>
+ | ` chainPre
+ | + <*>
+ | | + pure (GHC.Types.:)
+ | | ` ref <hidden>
| ` pure GHC.Types.[]
` eof
lets
-+ let <hidden>
-| ` <|>
-| + <*>
-| | + <*>
-| | | + pure (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | ` <*>
-| | | + pure (GHC.Types.:)
-| | | ` <*>
-| | | + <*>
-| | | | + pure (\x_0 -> \x_1 -> x_0)
-| | | | ` pure 'r'
-| | | ` satisfy
-| | ` rec <hidden>
-| ` pure (\x_0 -> x_0)
` <*>
+ pure GHC.Show.show
` <*>
+ <*>
| + pure (\x_0 -> \x_1 -> x_0)
- | ` <*>
- | + ref <hidden>
+ | ` chainPre
+ | + <*>
+ | | + pure (GHC.Types.:)
+ | | ` <*>
+ | | + <*>
+ | | | + pure (\x_0 -> \x_1 -> x_0)
+ | | | ` pure 'r'
+ | | ` satisfy
| ` pure GHC.Types.[]
` eof
import Data.Char (Char)
import Control.Monad (Monad(..))
import Data.Int (Int)
-import Data.Function (($))
+import Data.Function (($), (.))
import Data.Functor ((<$>))
import Data.Semigroup (Semigroup(..))
import Data.String (String, IsString(..))
P.Cursorable (P.Cursor inp) =>
P.Machinable (P.InputToken inp) repr =>
[IO (repr inp '[] String)]
-machines = P.optimizeMachine <$> grammars
+machines = P.optimizeMachine . P.optimizeGrammar <$> grammars
-pushValue GHC.Show.show
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-pushValue 'a'
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+pushValue (\x_0 -> GHC.Show.show 'a')
minReads=(Right 1)
mayRaise=[ExceptionFailure]
read ((GHC.Classes.==) 'a')
lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[]
ret
minReads=(Right 0)
mayRaise=[]
minReads=(Right 1)
mayRaise=[ExceptionFailure]
| <ok>
-| | pushValue (\x_0 -> \x_1 -> x_0)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | pushValue (\x_0 -> 'a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
| | read ((GHC.Classes.==) 'a')
| | _) -> i_0 GHC.Classes.== j_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
+| | choicesBranch
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | | <branch>
-| | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'b'
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | <branch (\x_0 -> x_0)>
+| | | | pushValue (\x_0 -> 'b')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
| | | | read ((GHC.Classes.==) 'b')
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'a'
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | read ((GHC.Classes.==) 'a')
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-pushValue GHC.Show.show
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-call <hidden>
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-pushValue GHC.Types.[]
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
+pushValue (\x_0 -> \x_1 -> GHC.Show.show x_0)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue 'b'
+pushValue (\x_0 -> x_0)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+newRegister <hidden>
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-read ((GHC.Classes.==) 'b')
+iter <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 0)
- mayRaise=[]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[]
-ret
- minReads=(Right 0)
- mayRaise=[]
+| <ok>
+| | pushValue (\x_0 -> (GHC.Types.:) 'a')
+| | minReads=(Right 3)
+| | mayRaise=[ExceptionFailure]
+| | read ((GHC.Classes.==) 'a')
+| | minReads=(Right 3)
+| | 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]
+| | readRegister <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | writeRegister <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | jump <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| <ko>
+| | pushInput
+| | minReads=(Right 1)
+| | mayRaise=[ExceptionFailure]
+| | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | j_1
+| | _) -> i_0 GHC.Classes.== j_1)
+| | minReads=(Right 1)
+| | mayRaise=[ExceptionFailure]
+| | choicesBranch
+| | minReads=(Right 1)
+| | mayRaise=[ExceptionFailure]
+| | | <branch (\x_0 -> x_0)>
+| | | | readRegister <hidden>
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | pushValue GHC.Types.[]
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | read ((GHC.Classes.==) 'b')
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | ret
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | <default>
+| | | | fail []
+| | | | minReads=(Left ExceptionFailure)
+| | | | mayRaise=[ExceptionFailure]
-let <hidden>
+pushValue (\x_0 -> \x_1 -> GHC.Show.show x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | 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 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-pushValue GHC.Show.show
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-call <hidden>
+pushValue (\x_0 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue GHC.Types.[]
+newRegister <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-join <hidden>
- minReads=(Right 0)
- mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-catch ExceptionFailure
+iter <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
| <ok>
-| | catch ExceptionFailure
-| | minReads=(Right 0)
-| | mayRaise=[]
-| | | <ok>
-| | | | pushInput
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | popValue
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | commit ExceptionFailure
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | loadInput
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | fail []
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | <ko>
-| | | | loadInput
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | pushValue GHC.Tuple.()
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | commit ExceptionFailure
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | refJoin <hidden>
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
+| | pushValue (GHC.Types.:)
+| | minReads=(Right 3)
+| | 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)
+| | 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]
+| | readRegister <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | writeRegister <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | jump <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
| <ko>
| | pushInput
-| | minReads=(Left ExceptionFailure)
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
| | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
| | j_1
| | _) -> i_0 GHC.Classes.== j_1)
-| | minReads=(Left ExceptionFailure)
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
-| | minReads=(Left ExceptionFailure)
+| | choicesBranch
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
-| | | <branch>
-| | | | fail [FailureEnd]
-| | | | minReads=(Left ExceptionFailure)
+| | | <branch (\x_0 -> x_0)>
+| | | | readRegister <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | pushValue GHC.Types.[]
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | join <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | ret
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | catch ExceptionFailure
+| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
+| | | | | <ok>
+| | | | | | catch ExceptionFailure
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | | <ok>
+| | | | | | | | pushInput
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | popValue
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | commit ExceptionFailure
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | loadInput
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <ko>
+| | | | | | | | loadInput
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | pushValue GHC.Tuple.()
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | commit ExceptionFailure
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | refJoin <hidden>
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | <ko>
+| | | | | | pushInput
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | j_1
+| | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | choicesBranch
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | fail [FailureEnd]
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <default>
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
| | | <default>
| | | | fail []
| | | | minReads=(Left ExceptionFailure)
let <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-| call <hidden>
+| pushValue (\x_0 -> GHC.Tuple.())
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue GHC.Types.[]
+| pushValue (\x_0 -> x_0)
| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| mayRaise=[ExceptionFailure]
+| newRegister <hidden>
| minReads=(Right 0)
-| mayRaise=[]
-| ret
+| mayRaise=[ExceptionFailure]
+| iter <hidden>
| minReads=(Right 0)
-| mayRaise=[]
+| mayRaise=[ExceptionFailure]
+| | <ok>
+| | | pushValue (\x_0 -> \x_1 -> x_1)
+| | | minReads=(Right 3)
+| | | 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)
+| | | mayRaise=[ExceptionFailure]
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | readRegister <hidden>
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | writeRegister <hidden>
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | jump <hidden>
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | <ko>
+| | | pushInput
+| | | minReads=(Right 0)
+| | | mayRaise=[ExceptionFailure]
+| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | j_1
+| | | _) -> i_0 GHC.Classes.== j_1)
+| | | minReads=(Right 0)
+| | | mayRaise=[ExceptionFailure]
+| | | choicesBranch
+| | | minReads=(Right 0)
+| | | mayRaise=[ExceptionFailure]
+| | | | <branch (\x_0 -> x_0)>
+| | | | | readRegister <hidden>
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | pushValue GHC.Tuple.()
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | ret
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | <default>
+| | | | | fail []
+| | | | | minReads=(Left ExceptionFailure)
+| | | | | mayRaise=[ExceptionFailure]
let <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
+| pushValue (\x_0 -> x_0)
+| minReads=(Right 0)
+| mayRaise=[ExceptionFailure]
+| newRegister <hidden>
+| minReads=(Right 0)
+| mayRaise=[ExceptionFailure]
+| iter <hidden>
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
+| | | pushValue (\x_0 -> \x_1 -> (GHC.Types.:) x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | join <hidden>
-| | | minReads=(Right 0)
+| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
+| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
| | | | call <hidden>
-| | | | minReads=(Right 0)
+| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
+| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
+| | | | 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_0 x_1)
-| | | | minReads=(Right 0)
+| | | | 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]
-| | | | call <hidden>
-| | | | minReads=(Right 0)
+| | | | readRegister <hidden>
+| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | commit ExceptionFailure
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | ret
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | writeRegister <hidden>
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | jump <hidden>
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
| | | pushInput
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | read (\x_0 -> GHC.Types.True)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | swapValue
| | | loadInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [(GHC.Classes.==) '<',(GHC.Classes.==) '>',(GHC.Classes.==) '+',(GHC.Classes.==) '-',(GHC.Classes.==) ',',(GHC.Classes.==) '.',(GHC.Classes.==) '[']
+| | | choicesBranch
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
+| | | | <branch (\x_0 -> (\x_1 -> \x_2 -> (GHC.Classes.==) x_1 x_2) '<' x_0)>
+| | | | | pushValue (\x_0 -> Parsers.Brainfuck.Types.Backward)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Parsers.Brainfuck.Types.Backward
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | read (\x_0 -> GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Parsers.Brainfuck.Types.Forward
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | <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)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | read (\x_0 -> GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Parsers.Brainfuck.Types.Increment
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | <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)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | read (\x_0 -> GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
+| | | | <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)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Parsers.Brainfuck.Types.Decrement
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | read (\x_0 -> GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
+| | | | <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)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Parsers.Brainfuck.Types.Input
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | read (\x_0 -> GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
+| | | | <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)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Parsers.Brainfuck.Types.Output
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | read (\x_0 -> GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 2)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 2)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> x_0)
+| | | | <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)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 2)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 2)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | read (\x_0 -> GHC.Types.True)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Parsers.Brainfuck.Types.Loop
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
| | | | | call <hidden>
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue ']'
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 1)
-| | | | | mayRaise=[ExceptionFailure]
| | | | | read ((GHC.Classes.==) ']')
| | | | | 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 0)
-| | | | | mayRaise=[]
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | _) -> i_0 GHC.Classes.== j_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
+| | | choicesBranch
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
+| | | | <branch (\x_0 -> x_0)>
+| | | | | readRegister <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | | ret
+| | | | | pushValue GHC.Types.[]
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | 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 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| | | | | fail []
| | | | | minReads=(Left ExceptionFailure)
| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| pushValue GHC.Tuple.()
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| call <hidden>
-| minReads=(Right 0)
-| 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 0)
-| mayRaise=[]
-| pushValue GHC.Tuple.()
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-pushValue GHC.Show.show
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> x_0)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+pushValue (\x_0 -> \x_1 -> GHC.Show.show x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
call <hidden>
lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[]
ret
minReads=(Right 0)
mayRaise=[]
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
+| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
+| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
+| | | newRegister <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
+| | | iter <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
+| | | | <ok>
+| | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
+| | | | | minReads=(Right 2)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | call <hidden>
+| | | | | minReads=(Right 2)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | 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=[]
-| | | | | ret
+| | | | | call <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 8)
| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | 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=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
+| | | | | readRegister <hidden>
+| | | | | minReads=(Right 8)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 8)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | writeRegister <hidden>
+| | | | | minReads=(Right 8)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | jump <hidden>
+| | | | | minReads=(Right 8)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | <ko>
+| | | | | pushInput
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | j_1
+| | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | choicesBranch
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | readRegister <hidden>
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | call <hidden>
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | call <hidden>
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | commit ExceptionFailure
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | ret
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | <default>
+| | | | | | | fail []
+| | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | mayRaise=[ExceptionFailure]
| | <ko>
| | | pushInput
| | | minReads=(Right 0)
| | | _) -> i_0 GHC.Classes.== j_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
+| | | choicesBranch
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
+| | | | <branch (\x_0 -> x_0)>
+| | | | | jump <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | <default>
| | | | | mayRaise=[ExceptionFailure]
let <hidden>
minReads=(Right 0)
+ mayRaise=[]
+| pushValue (\x_0 -> \x_1 -> x_1)
+| minReads=(Right 0)
+| mayRaise=[]
+| ret
+| minReads=(Right 0)
+| mayRaise=[]
+let <hidden>
+ minReads=(Right 0)
+ mayRaise=[]
+| pushValue GHC.Tuple.()
+| minReads=(Right 0)
+| mayRaise=[]
+| ret
+| minReads=(Right 0)
+| mayRaise=[]
+let <hidden>
+ minReads=(Right 0)
+ mayRaise=[]
+| pushValue GHC.Tuple.()
+| minReads=(Right 0)
+| mayRaise=[]
+| ret
+| minReads=(Right 0)
+| mayRaise=[]
+let <hidden>
+ minReads=(Right 1)
mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
+| pushValue (\x_0 -> \x_1 -> GHC.Tuple.())
+| 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=[ExceptionFailure]
+| pushValue (\x_0 -> x_0)
+| minReads=(Right 0)
+| mayRaise=[ExceptionFailure]
+| newRegister <hidden>
+| minReads=(Right 0)
+| mayRaise=[ExceptionFailure]
+| iter <hidden>
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
+| | | pushValue (\x_0 -> \x_1 -> x_1)
+| | | minReads=(Right 0)
+| | | mayRaise=[]
+| | | call <hidden>
+| | | minReads=(Right 0)
+| | | mayRaise=[]
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
+| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | read Parsers.Nandlang.nandIdentLetter
-| | | minReads=(Right 1)
+| | | readRegister <hidden>
+| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
+| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
+| | | writeRegister <hidden>
+| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
+| | | jump <hidden>
+| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
| | <ko>
| | | pushInput
| | | minReads=(Right 0)
| | | _) -> i_0 GHC.Classes.== j_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
+| | | choicesBranch
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
+| | | | <branch (\x_0 -> x_0)>
+| | | | | readRegister <hidden>
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | pushValue GHC.Tuple.()
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| | | | | minReads=(Left ExceptionFailure)
| | | | | mayRaise=[ExceptionFailure]
let <hidden>
- minReads=(Right 0)
+ minReads=(Right 1)
mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
+| pushValue (\x_0 -> \x_1 -> x_1)
+| minReads=(Right 1)
+| mayRaise=[ExceptionFailure]
+| read GHC.Unicode.isSpace
+| minReads=(Right 1)
+| mayRaise=[ExceptionFailure]
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| minReads=(Right 0)
+| mayRaise=[]
+| call <hidden>
+| minReads=(Right 0)
+| mayRaise=[]
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| minReads=(Right 0)
+| mayRaise=[]
+| ret
+| minReads=(Right 0)
+| mayRaise=[]
+let <hidden>
+ minReads=(Right 1)
+ mayRaise=[ExceptionFailure]
+| read (\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))))))))))
+| minReads=(Right 1)
+| mayRaise=[ExceptionFailure]
+| ret
| minReads=(Right 0)
+| mayRaise=[]
+let <hidden>
+ minReads=(Right 2)
+ mayRaise=[ExceptionFailure]
+| catch ExceptionFailure
+| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 18)
+| | | pushValue (\x_0 -> \x_1 -> x_1)
+| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 18)
+| | | join <hidden>
+| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | catch ExceptionFailure
-| | | minReads=(Right 18)
-| | | mayRaise=[ExceptionFailure]
-| | | | <ok>
-| | | | | pushValue (GHC.Types.:)
-| | | | | minReads=(Right 18)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 18)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'f'
-| | | | | minReads=(Right 18)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 18)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((GHC.Classes.==) 'f')
-| | | | | minReads=(Right 18)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 17)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 17)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (GHC.Types.:)
-| | | | | minReads=(Right 17)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 17)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'u'
-| | | | | minReads=(Right 17)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 17)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((GHC.Classes.==) 'u')
-| | | | | minReads=(Right 17)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 16)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 16)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (GHC.Types.:)
-| | | | | minReads=(Right 16)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 16)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'n'
-| | | | | minReads=(Right 16)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 16)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((GHC.Classes.==) 'n')
-| | | | | minReads=(Right 16)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 15)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 15)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (GHC.Types.:)
-| | | | | minReads=(Right 15)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 15)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'c'
-| | | | | minReads=(Right 15)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 15)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((GHC.Classes.==) 'c')
-| | | | | minReads=(Right 15)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 14)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 14)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (GHC.Types.:)
-| | | | | minReads=(Right 14)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 14)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 't'
-| | | | | minReads=(Right 14)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 14)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((GHC.Classes.==) 't')
-| | | | | minReads=(Right 14)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 13)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 13)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (GHC.Types.:)
-| | | | | minReads=(Right 13)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 13)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'i'
-| | | | | minReads=(Right 13)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 13)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((GHC.Classes.==) 'i')
-| | | | | minReads=(Right 13)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 12)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 12)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (GHC.Types.:)
-| | | | | minReads=(Right 12)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 12)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'o'
-| | | | | minReads=(Right 12)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 12)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((GHC.Classes.==) 'o')
-| | | | | minReads=(Right 12)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 11)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 11)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (GHC.Types.:)
-| | | | | minReads=(Right 11)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 11)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'n'
-| | | | | minReads=(Right 11)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 11)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((GHC.Classes.==) 'n')
-| | | | | minReads=(Right 11)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue GHC.Types.[]
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | commit ExceptionFailure
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | call <hidden>
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | call <hidden>
-| | | | | minReads=(Right 10)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 8)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 8)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 8)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 8)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 8)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 8)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | call <hidden>
-| | | | | minReads=(Right 8)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 6)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 6)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 6)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 6)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | call <hidden>
-| | | | | minReads=(Right 6)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 2)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | join <hidden>
-| | | | | minReads=(Right 6)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 6)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 6)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 6)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | call <hidden>
-| | | | | | minReads=(Right 6)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 4)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | 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 0)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | call <hidden>
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | | commit ExceptionFailure
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | | ret
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | catch ExceptionFailure
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | | <ok>
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue GHC.Tuple.()
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue ':'
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | read ((GHC.Classes.==) ':')
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 1)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | 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 0)
-| | | | | | | mayRaise=[]
-| | | | | | | call <hidden>
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[]
-| | | | | | | commit ExceptionFailure
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[]
-| | | | | | | refJoin <hidden>
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[]
-| | | | | | <ko>
-| | | | | | | pushInput
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | | | | | j_1
-| | | | | | | _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | choicesBranch [\x_0 -> x_0]
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | <branch>
-| | | | | | | | | call <hidden>
-| | | | | | | | | minReads=(Right 0)
-| | | | | | | | | mayRaise=[]
-| | | | | | | | | refJoin <hidden>
-| | | | | | | | | minReads=(Right 0)
-| | | | | | | | | mayRaise=[]
-| | | | | | | | <default>
-| | | | | | | | | fail []
-| | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | <ko>
-| | | | | loadInput
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | join <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[ExceptionFailure]
-| | | | call <hidden>
-| | | | minReads=(Right 0)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | commit ExceptionFailure
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | ret
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | catch ExceptionFailure
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | | <ok>
-| | | | | join <hidden>
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | | commit ExceptionFailure
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | | refJoin <hidden>
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | catch ExceptionFailure
-| | | | | minReads=(Right 2)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | | <ok>
-| | | | | | | join <hidden>
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | commit ExceptionFailure
-| | | | | | | | minReads=(Right 0)
-| | | | | | | | mayRaise=[]
-| | | | | | | | refJoin <hidden>
-| | | | | | | | minReads=(Right 0)
-| | | | | | | | mayRaise=[]
-| | | | | | | catch ExceptionFailure
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | <ok>
-| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | minReads=(Right 2)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | minReads=(Right 2)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | minReads=(Right 2)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | catch ExceptionFailure
-| | | | | | | | | minReads=(Right 2)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | <ok>
-| | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue 'i'
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | read ((GHC.Classes.==) 'i')
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue 'f'
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | read ((GHC.Classes.==) 'f')
-| | | | | | | | | | | 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 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | pushValue GHC.Types.[]
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | call <hidden>
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | <ko>
-| | | | | | | | | | | loadInput
-| | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | fail []
-| | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | <ko>
-| | | | | | | | | pushInput
-| | | | | | | | | minReads=(Right 11)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | | | | | | | j_1
-| | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | | | minReads=(Right 11)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | choicesBranch [\x_0 -> x_0]
-| | | | | | | | | minReads=(Right 11)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | <branch>
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | catch ExceptionFailure
-| | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | <ok>
-| | | | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'w'
-| | | | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ((GHC.Classes.==) 'w')
-| | | | | | | | | | | | | minReads=(Right 11)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 10)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 10)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | | | minReads=(Right 10)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | minReads=(Right 10)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'h'
-| | | | | | | | | | | | | minReads=(Right 10)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 10)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ((GHC.Classes.==) 'h')
-| | | | | | | | | | | | | minReads=(Right 10)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 9)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 9)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | | | minReads=(Right 9)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | minReads=(Right 9)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'i'
-| | | | | | | | | | | | | minReads=(Right 9)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 9)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ((GHC.Classes.==) 'i')
-| | | | | | | | | | | | | minReads=(Right 9)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'l'
-| | | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ((GHC.Classes.==) 'l')
-| | | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 7)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 7)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | | | minReads=(Right 7)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | minReads=(Right 7)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'e'
-| | | | | | | | | | | | | minReads=(Right 7)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 7)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ((GHC.Classes.==) 'e')
-| | | | | | | | | | | | | minReads=(Right 7)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue GHC.Types.[]
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | 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 0)
-| | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | <ko>
-| | | | | | | | | | | | | loadInput
-| | | | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | fail []
-| | | | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | <default>
-| | | | | | | | | | | fail []
-| | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | <ko>
-| | | | | | | pushInput
-| | | | | | | 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 8)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | choicesBranch [\x_0 -> x_0]
-| | | | | | | minReads=(Right 8)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | <branch>
-| | | | | | | | | catch ExceptionFailure
-| | | | | | | | | minReads=(Right 8)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | <ok>
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | join <hidden>
-| | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | minReads=(Right 8)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | minReads=(Right 6)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | 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 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 4)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 4)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 4)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 4)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | minReads=(Right 4)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | minReads=(Right 4)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue '='
-| | | | | | | | | | | | minReads=(Right 4)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 4)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | read ((GHC.Classes.==) '=')
-| | | | | | | | | | | | minReads=(Right 4)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | 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=[]
-| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | 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 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | 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=[]
-| | | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | catch ExceptionFailure
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | <ok>
-| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue GHC.Tuple.()
-| | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | catch ExceptionFailure
-| | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | <ok>
-| | | | | | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue 'v'
-| | | | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | read ((GHC.Classes.==) 'v')
-| | | | | | | | | | | | | | | minReads=(Right 3)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue 'a'
-| | | | | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | read ((GHC.Classes.==) 'a')
-| | | | | | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue (GHC.Types.:)
-| | | | | | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue 'r'
-| | | | | | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | read ((GHC.Classes.==) 'r')
-| | | | | | | | | | | | | | | 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 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | pushValue GHC.Types.[]
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | <ko>
-| | | | | | | | | | | | | | | loadInput
-| | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | fail []
-| | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | <ko>
-| | | | | | | | | | | | | pushInput
-| | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | | | | | | | | | | | j_1
-| | | | | | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | choicesBranch [\x_0 -> x_0]
-| | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | <branch>
-| | | | | | | | | | | | | | | call <hidden>
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | <default>
-| | | | | | | | | | | | | | | fail []
-| | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | <ko>
-| | | | | | | | | | | loadInput
-| | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | fail []
-| | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | <default>
-| | | | | | | | | fail []
-| | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | <ko>
-| | | | | pushInput
-| | | | | 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 4)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | choicesBranch [\x_0 -> x_0]
-| | | | | minReads=(Right 4)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | | <branch>
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | call <hidden>
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | 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=[]
-| | | | | | | refJoin <hidden>
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[]
-| | | | | | <default>
-| | | | | | | fail []
-| | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | 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)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | 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)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | 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)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | 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)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue '!'
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | read ((GHC.Classes.==) '!')
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | 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=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue GHC.Tuple.()
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | 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=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | 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 0)
-| | | mayRaise=[]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | jump <hidden>
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[]
-| pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[]
-| pushValue GHC.Tuple.()
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[]
-| pushValue GHC.Tuple.()
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-let <hidden>
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| 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=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| pushValue GHC.Tuple.()
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| call <hidden>
-| minReads=(Right 0)
-| 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 0)
-| mayRaise=[]
-| pushValue GHC.Tuple.()
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-let <hidden>
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| read GHC.Unicode.isSpace
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| call <hidden>
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-let <hidden>
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-| read (\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))))))))))
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-let <hidden>
- minReads=(Right 2)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | join <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | 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=[]
| | | | commit ExceptionFailure
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | catch ExceptionFailure
-| | | minReads=(Right 2)
+| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | | <ok>
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 2)
+| | | | | pushValue (\x_0 -> '0')
+| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 2)
+| | | | | read ((GHC.Classes.==) '0')
+| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | minReads=(Right 2)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | commit ExceptionFailure
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | refJoin <hidden>
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | <ko>
+| | | | | pushInput
+| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | join <hidden>
+| | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | j_1
+| | | | | _) -> i_0 GHC.Classes.== j_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | 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=[]
-| | | | | | commit ExceptionFailure
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | | refJoin <hidden>
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | catch ExceptionFailure
+| | | | | choicesBranch
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | | <ok>
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
+| | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | pushValue (\x_0 -> '1')
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue '0'
+| | | | | | | read ((GHC.Classes.==) '1')
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 1)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | read ((GHC.Classes.==) '0')
-| | | | | | | minReads=(Right 1)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[]
-| | | | | | | commit ExceptionFailure
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
| | | | | | | refJoin <hidden>
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
-| | | | | | <ko>
-| | | | | | | pushInput
-| | | | | | | minReads=(Right 1)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | | | | | j_1
-| | | | | | | _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | minReads=(Right 1)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | choicesBranch [\x_0 -> x_0]
-| | | | | | | minReads=(Right 1)
+| | | | | | <default>
+| | | | | | | fail []
+| | | | | | | minReads=(Left ExceptionFailure)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | <branch>
-| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | minReads=(Right 1)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue '1'
-| | | | | | | | | minReads=(Right 1)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | minReads=(Right 1)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | read ((GHC.Classes.==) '1')
-| | | | | | | | | minReads=(Right 1)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | minReads=(Right 0)
-| | | | | | | | | mayRaise=[]
-| | | | | | | | | refJoin <hidden>
-| | | | | | | | | minReads=(Right 0)
-| | | | | | | | | mayRaise=[]
-| | | | | | | | <default>
-| | | | | | | | | fail []
-| | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | <ko>
-| | | | | pushInput
-| | | | | 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 4)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | choicesBranch [\x_0 -> x_0]
-| | | | | minReads=(Right 4)
+| | <ko>
+| | | pushInput
+| | | 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 2)
+| | | mayRaise=[ExceptionFailure]
+| | | choicesBranch
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | | <branch (\x_0 -> x_0)>
+| | | | | catch ExceptionFailure
+| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | | <branch>
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue '\''
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | read ((GHC.Classes.==) '\'')
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 3)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 3)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | join <hidden>
-| | | | | | | minReads=(Right 2)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | minReads=(Right 2)
-| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | minReads=(Right 2)
-| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | minReads=(Right 2)
-| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | minReads=(Right 2)
-| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | pushValue '\''
-| | | | | | | | minReads=(Right 2)
-| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | <ok>
+| | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_1)
+| | | | | | | minReads=(Right 4)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | read ((GHC.Classes.==) '\'')
+| | | | | | | minReads=(Right 4)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | minReads=(Right 3)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | join <hidden>
+| | | | | | | minReads=(Right 2)
+| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 2)
| | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 1)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | 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)
+| | | | | | | | commit ExceptionFailure
| | | | | | | | minReads=(Right 0)
| | | | | | | | mayRaise=[]
-| | | | | | | | refJoin <hidden>
+| | | | | | | | ret
| | | | | | | | minReads=(Right 0)
| | | | | | | | mayRaise=[]
| | | | | | | catch ExceptionFailure
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | <ok>
-| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | minReads=(Right 1)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | minReads=(Right 1)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_1)
| | | | | | | | | minReads=(Right 1)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | read Parsers.Nandlang.nandStringLetter
| | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | choicesBranch [\x_0 -> x_0]
+| | | | | | | | | choicesBranch
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | <branch>
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue '\\'
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_2)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | read ((GHC.Classes.==) '\\')
| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 1)
-| | | | | | | | | | | 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)
| | | | | | | | | | | 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 0)
-| | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | refJoin <hidden>
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | fail []
| | | | | | | | | | | minReads=(Left ExceptionFailure)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | <default>
-| | | | | | | fail []
-| | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | <ko>
-| | | pushInput
-| | | 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 2)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | minReads=(Right 2)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 2)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | 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=[ExceptionFailure]
-| | | | | join <hidden>
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | | ret
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | catch ExceptionFailure
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[ExceptionFailure]
-| | | | | | <ok>
-| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | minReads=(Right 4)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue GHC.Tuple.()
-| | | | | | | minReads=(Right 4)
+| | | | | | <ko>
+| | | | | | | pushInput
+| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | minReads=(Right 4)
+| | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | | j_1
+| | | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | join <hidden>
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[]
-| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | minReads=(Right 0)
-| | | | | | | | mayRaise=[]
-| | | | | | | | commit ExceptionFailure
-| | | | | | | | minReads=(Right 0)
-| | | | | | | | mayRaise=[]
-| | | | | | | | refJoin <hidden>
-| | | | | | | | minReads=(Right 0)
-| | | | | | | | mayRaise=[]
-| | | | | | | catch ExceptionFailure
-| | | | | | | minReads=(Right 4)
+| | | | | | | choicesBranch
+| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | <ok>
-| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | minReads=(Right 4)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | minReads=(Right 4)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | minReads=(Right 4)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | minReads=(Right 4)
+| | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_1)
+| | | | | | | | | 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)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | call <hidden>
-| | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | minReads=(Right 0)
+| | | | | | | | | mayRaise=[]
| | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | mayRaise=[]
-| | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | mayRaise=[]
-| | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | ret
| | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | mayRaise=[]
| | | | | | | | | catch ExceptionFailure
| | | | | | | | | minReads=(Right 0)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | <ok>
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue GHC.Tuple.()
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 2)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | 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=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\x_0 -> x_0)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | call <hidden>
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | call <hidden>
-| | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | pushValue (\x_0 -> GHC.Tuple.())
+| | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | 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 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | call <hidden>
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | commit ExceptionFailure
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | join <hidden>
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | commit ExceptionFailure
+| | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | catch ExceptionFailure
+| | | | | | | | | | | minReads=(Right 4)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | <ok>
+| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> 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)
+| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | join <hidden>
+| | | | | | | | | | | | | minReads=(Right 2)
+| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | 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=[]
+| | | | | | | | | | | | | | commit ExceptionFailure
+| | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | catch ExceptionFailure
+| | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | <ok>
+| | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
+| | | | | | | | | | | | | | | 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=[ExceptionFailure]
+| | | | | | | | | | | | | | | pushValue (\x_0 -> x_0)
+| | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | newRegister <hidden>
+| | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | iter <hidden>
+| | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | <ok>
+| | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
+| | | | | | | | | | | | | | | | | minReads=(Right 2)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | minReads=(Right 2)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | 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=[]
+| | | | | | | | | | | | | | | | | call <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]
+| | | | | | | | | | | | | | | | | writeRegister <hidden>
+| | | | | | | | | | | | | | | | | minReads=(Right 8)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | jump <hidden>
+| | | | | | | | | | | | | | | | | minReads=(Right 8)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | <ko>
+| | | | | | | | | | | | | | | | | pushInput
+| | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | | | | | | | | | | | | j_1
+| | | | | | | | | | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | choicesBranch
+| | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | | | | | | | | | | | readRegister <hidden>
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | commit ExceptionFailure
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | <default>
+| | | | | | | | | | | | | | | | | | | fail []
+| | | | | | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | <ko>
+| | | | | | | | | | | | | | | pushInput
+| | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | | | | | | | | | | j_1
+| | | | | | | | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | choicesBranch
+| | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | <default>
+| | | | | | | | | | | | | | | | | fail []
+| | | | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | <ko>
+| | | | | | | | | | | | | pushInput
+| | | | | | | | | | | | | minReads=(Right 5)
+| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | | | | | | | | j_1
+| | | | | | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | | | | | | | | minReads=(Right 5)
+| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | choicesBranch
+| | | | | | | | | | | | | minReads=(Right 5)
+| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | minReads=(Right 5)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | <default>
+| | | | | | | | | | | | | | | fail []
+| | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | <ko>
| | | | | | | | | | | pushInput
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | choicesBranch [\x_0 -> x_0]
+| | | | | | | | | | | choicesBranch
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | <branch>
+| | | | | | | | | | | | <branch (\x_0 -> x_0)>
| | | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | | | fail []
| | | | | | | | | | | | | minReads=(Left ExceptionFailure)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | <ko>
-| | | | | | | | | pushInput
-| | | | | | | | | minReads=(Right 5)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | | | | | | | j_1
-| | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | | | minReads=(Right 5)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | choicesBranch [\x_0 -> x_0]
-| | | | | | | | | minReads=(Right 5)
-| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | <branch>
-| | | | | | | | | | | call <hidden>
-| | | | | | | | | | | minReads=(Right 5)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | refJoin <hidden>
-| | | | | | | | | | | minReads=(Right 0)
-| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | <default>
-| | | | | | | | | | | fail []
-| | | | | | | | | | | minReads=(Left ExceptionFailure)
-| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | <ko>
-| | | | | | | pushInput
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | | | | | j_1
-| | | | | | | _) -> i_0 GHC.Classes.== j_1)
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | choicesBranch [\x_0 -> x_0]
-| | | | | | | minReads=(Right 0)
-| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | <branch>
-| | | | | | | | | call <hidden>
-| | | | | | | | | minReads=(Right 0)
-| | | | | | | | | mayRaise=[]
-| | | | | | | | | refJoin <hidden>
-| | | | | | | | | minReads=(Right 0)
-| | | | | | | | | mayRaise=[]
| | | | | | | | <default>
| | | | | | | | | fail []
| | | | | | | | | minReads=(Left ExceptionFailure)
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue '('
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| pushValue (\x_0 -> \x_1 -> '(')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| read ((GHC.Classes.==) '(')
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue ')'
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| pushValue (\x_0 -> \x_1 -> ')')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| read ((GHC.Classes.==) ')')
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue ','
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| pushValue (\x_0 -> \x_1 -> ',')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| read ((GHC.Classes.==) ',')
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue ';'
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| pushValue (\x_0 -> \x_1 -> ';')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| read ((GHC.Classes.==) ';')
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
+| pushValue (\x_0 -> \x_1 -> \x_2 -> x_2)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
+| call <hidden>
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| minReads=(Right 0)
+| mayRaise=[ExceptionFailure]
+| pushValue (\x_0 -> x_0)
+| minReads=(Right 0)
+| mayRaise=[ExceptionFailure]
+| newRegister <hidden>
+| minReads=(Right 0)
+| mayRaise=[ExceptionFailure]
+| iter <hidden>
+| minReads=(Right 0)
+| mayRaise=[ExceptionFailure]
+| | <ok>
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | read ((GHC.Classes.==) '!')
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | 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=[]
+| | | call <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]
+| | | writeRegister <hidden>
+| | | minReads=(Right 8)
+| | | mayRaise=[ExceptionFailure]
+| | | jump <hidden>
+| | | minReads=(Right 8)
+| | | mayRaise=[ExceptionFailure]
+| | <ko>
+| | | pushInput
+| | | minReads=(Right 0)
+| | | mayRaise=[ExceptionFailure]
+| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | j_1
+| | | _) -> i_0 GHC.Classes.== j_1)
+| | | minReads=(Right 0)
+| | | mayRaise=[ExceptionFailure]
+| | | choicesBranch
+| | | minReads=(Right 0)
+| | | mayRaise=[ExceptionFailure]
+| | | | <branch (\x_0 -> x_0)>
+| | | | | readRegister <hidden>
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | call <hidden>
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | call <hidden>
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | ret
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | <default>
+| | | | | fail []
+| | | | | minReads=(Left ExceptionFailure)
+| | | | | mayRaise=[ExceptionFailure]
+let <hidden>
+ minReads=(Right 2)
+ mayRaise=[ExceptionFailure]
+| pushValue (\x_0 -> \x_1 -> x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 5)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue GHC.Tuple.()
-| | | minReads=(Right 5)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | pushValue (\x_0 -> GHC.Tuple.())
| | | minReads=(Right 5)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | _) -> i_0 GHC.Classes.== j_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
+| | | choicesBranch
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
+| | | | <branch (\x_0 -> x_0)>
| | | | | call <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| 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=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| call <hidden>
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| call <hidden>
-| minReads=(Right 0)
-| 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 0)
-| mayRaise=[]
-| call <hidden>
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-let <hidden>
- minReads=(Right 2)
- mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| pushValue (\x_0 -> \x_1 -> x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| catch ExceptionFailure
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> x_0)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_2)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | read Parsers.Nandlang.nandIdentStart
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 1)
| | | 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_3 x_4))
-| | | 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=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | 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 0)
-| | | mayRaise=[]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | commit ExceptionFailure
+| | | newRegister <hidden>
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
+| | | iter <hidden>
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
+| | | | <ok>
+| | | | | pushValue (\x_0 -> \x_1 -> x_1)
+| | | | | minReads=(Right 3)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | read Parsers.Nandlang.nandIdentLetter
+| | | | | minReads=(Right 3)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 2)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | readRegister <hidden>
+| | | | | minReads=(Right 2)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 2)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | writeRegister <hidden>
+| | | | | minReads=(Right 2)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | jump <hidden>
+| | | | | minReads=(Right 2)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | <ko>
+| | | | | pushInput
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | j_1
+| | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | choicesBranch
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | readRegister <hidden>
+| | | | | | | 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 0)
+| | | | | | | mayRaise=[]
+| | | | | | | call <hidden>
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | minReads=(Right 1)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | commit ExceptionFailure
+| | | | | | | minReads=(Right 1)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | 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=[]
+| | | | | | | ret
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | <default>
+| | | | | | | fail []
+| | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | mayRaise=[ExceptionFailure]
| | <ko>
| | | loadInput
| | | minReads=(Left ExceptionFailure)
let <hidden>
minReads=(Right 4)
mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 4)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 4)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 4)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 4)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 4)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 4)
-| mayRaise=[ExceptionFailure]
-| pushValue '{'
-| minReads=(Right 4)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> x_3)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
| read ((GHC.Classes.==) '{')
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 3)
| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 3)
-| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 3)
| mayRaise=[ExceptionFailure]
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
| pushValue (\x_0 -> x_0)
| minReads=(Right 1)
| 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_3 x_4))
-| 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=[ExceptionFailure]
-| call <hidden>
-| minReads=(Right 0)
-| 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 0)
-| mayRaise=[]
-| call <hidden>
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue '}'
+| newRegister <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| read ((GHC.Classes.==) '}')
+| iter <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 0)
-| mayRaise=[]
-| call <hidden>
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
+| | <ok>
+| | | pushValue (\x_0 -> \x_1 -> x_1)
+| | | minReads=(Right 4)
+| | | mayRaise=[ExceptionFailure]
+| | | join <hidden>
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 4)
+| | | | mayRaise=[ExceptionFailure]
+| | | | readRegister <hidden>
+| | | | minReads=(Right 4)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 4)
+| | | | mayRaise=[ExceptionFailure]
+| | | | writeRegister <hidden>
+| | | | minReads=(Right 4)
+| | | | mayRaise=[ExceptionFailure]
+| | | | jump <hidden>
+| | | | minReads=(Right 4)
+| | | | mayRaise=[ExceptionFailure]
+| | | catch ExceptionFailure
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | | <ok>
+| | | | | pushValue (\x_0 -> \x_1 -> x_1)
+| | | | | minReads=(Right 2)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | catch ExceptionFailure
+| | | | | minReads=(Right 2)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | | <ok>
+| | | | | | | pushValue (\x_0 -> \x_1 -> (GHC.Types.:) 'i' ((GHC.Types.:) 'f' GHC.Types.[]))
+| | | | | | | minReads=(Right 2)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | read ((GHC.Classes.==) 'i')
+| | | | | | | minReads=(Right 2)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | minReads=(Right 1)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | read ((GHC.Classes.==) 'f')
+| | | | | | | minReads=(Right 1)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | commit ExceptionFailure
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | call <hidden>
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | commit ExceptionFailure
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | | refJoin <hidden>
+| | | | | | | minReads=(Right 0)
+| | | | | | | mayRaise=[]
+| | | | | | <ko>
+| | | | | | | loadInput
+| | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | fail []
+| | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | <ko>
+| | | | | pushInput
+| | | | | 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 4)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | choicesBranch
+| | | | | minReads=(Right 4)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | catch ExceptionFailure
+| | | | | | | minReads=(Right 4)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | <ok>
+| | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3)
+| | | | | | | | | minReads=(Right 11)
+| | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | catch ExceptionFailure
+| | | | | | | | | minReads=(Right 11)
+| | | | | | | | | 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)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | read ((GHC.Classes.==) 'w')
+| | | | | | | | | | | minReads=(Right 11)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | minReads=(Right 10)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | read ((GHC.Classes.==) 'h')
+| | | | | | | | | | | minReads=(Right 10)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | minReads=(Right 9)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | read ((GHC.Classes.==) 'i')
+| | | | | | | | | | | minReads=(Right 9)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | minReads=(Right 8)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | read ((GHC.Classes.==) 'l')
+| | | | | | | | | | | minReads=(Right 8)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | minReads=(Right 7)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | read ((GHC.Classes.==) 'e')
+| | | | | | | | | | | minReads=(Right 7)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | minReads=(Right 6)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | commit ExceptionFailure
+| | | | | | | | | | | minReads=(Right 6)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | minReads=(Right 6)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | call <hidden>
+| | | | | | | | | | | minReads=(Right 6)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | minReads=(Right 6)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | call <hidden>
+| | | | | | | | | | | minReads=(Right 6)
+| | | | | | | | | | | 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 0)
+| | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | commit ExceptionFailure
+| | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | <ko>
+| | | | | | | | | | | loadInput
+| | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | fail []
+| | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | <ko>
+| | | | | | | | | pushInput
+| | | | | | | | | 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 4)
+| | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | choicesBranch
+| | | | | | | | | minReads=(Right 4)
+| | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | | | catch ExceptionFailure
+| | | | | | | | | | | minReads=(Right 4)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | <ok>
+| | | | | | | | | | | | | catch ExceptionFailure
+| | | | | | | | | | | | | minReads=(Right 10)
+| | | | | | | | | | | | | 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)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | join <hidden>
+| | | | | | | | | | | | | | | minReads=(Right 10)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | minReads=(Right 3)
+| | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | minReads=(Right 3)
+| | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | pushValue (\x_0 -> x_0)
+| | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | newRegister <hidden>
+| | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | iter <hidden>
+| | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | <ok>
+| | | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
+| | | | | | | | | | | | | | | | | | minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | 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=[]
+| | | | | | | | | | | | | | | | | | call <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]
+| | | | | | | | | | | | | | | | | | writeRegister <hidden>
+| | | | | | | | | | | | | | | | | | minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | jump <hidden>
+| | | | | | | | | | | | | | | | | | minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | <ko>
+| | | | | | | | | | | | | | | | | | pushInput
+| | | | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | | | | | | | | | | | | | j_1
+| | | | | | | | | | | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | choicesBranch
+| | | | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | | | | | | | | | | | | readRegister <hidden>
+| | | | | | | | | | | | | | | | | | | | 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 0)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | read ((GHC.Classes.==) '=')
+| | | | | | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | | 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=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | pushValue (\x_0 -> x_0)
+| | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | newRegister <hidden>
+| | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | iter <hidden>
+| | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | <ok>
+| | | | | | | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2)
+| | | | | | | | | | | | | | | | | | | | | | minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | | | | minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | | | | 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=[]
+| | | | | | | | | | | | | | | | | | | | | | call <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]
+| | | | | | | | | | | | | | | | | | | | | | writeRegister <hidden>
+| | | | | | | | | | | | | | | | | | | | | | minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | | jump <hidden>
+| | | | | | | | | | | | | | | | | | | | | | minReads=(Right 8)
+| | | | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | <ko>
+| | | | | | | | | | | | | | | | | | | | | | pushInput
+| | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | | | | | | | | | | | | | | | | | j_1
+| | | | | | | | | | | | | | | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | | choicesBranch
+| | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | | | | | | | | | | | | | | | | readRegister <hidden>
+| | | | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | | | | | | 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=[]
+| | | | | | | | | | | | | | | | | | | | | | | | commit ExceptionFailure
+| | | | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | | commit ExceptionFailure
+| | | | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | | | | | <default>
+| | | | | | | | | | | | | | | | | | | | | | | | fail []
+| | | | | | | | | | | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | <default>
+| | | | | | | | | | | | | | | | | | | | fail []
+| | | | | | | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | catch ExceptionFailure
+| | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | <ok>
+| | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> GHC.Tuple.())
+| | | | | | | | | | | | | | | | | minReads=(Right 3)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | catch ExceptionFailure
+| | | | | | | | | | | | | | | | | minReads=(Right 3)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | <ok>
+| | | | | | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'v' ((GHC.Types.:) 'a' ((GHC.Types.:) 'r' GHC.Types.[])))
+| | | | | | | | | | | | | | | | | | | minReads=(Right 3)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | read ((GHC.Classes.==) 'v')
+| | | | | | | | | | | | | | | | | | | minReads=(Right 3)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | read ((GHC.Classes.==) 'a')
+| | | | | | | | | | | | | | | | | | | minReads=(Right 2)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | read ((GHC.Classes.==) 'r')
+| | | | | | | | | | | | | | | | | | | minReads=(Right 1)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | commit ExceptionFailure
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | commit ExceptionFailure
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | <ko>
+| | | | | | | | | | | | | | | | | | | loadInput
+| | | | | | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | | fail []
+| | | | | | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | <ko>
+| | | | | | | | | | | | | | | | | pushInput
+| | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | | | | | | | | | | | | j_1
+| | | | | | | | | | | | | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | choicesBranch
+| | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | | | | | <default>
+| | | | | | | | | | | | | | | | | | | fail []
+| | | | | | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | <ko>
+| | | | | | | | | | | | | | | loadInput
+| | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | fail []
+| | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | <ko>
+| | | | | | | | | | | | | pushInput
+| | | | | | | | | | | | | 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 4)
+| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | choicesBranch
+| | | | | | | | | | | | | minReads=(Right 4)
+| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
+| | | | | | | | | | | | | | | minReads=(Right 4)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | call <hidden>
+| | | | | | | | | | | | | | | minReads=(Right 4)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | | | | | | | | 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=[]
+| | | | | | | | | | | | | | | refJoin <hidden>
+| | | | | | | | | | | | | | | minReads=(Right 0)
+| | | | | | | | | | | | | | | mayRaise=[]
+| | | | | | | | | | | | | | <default>
+| | | | | | | | | | | | | | | fail []
+| | | | | | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | | | <default>
+| | | | | | | | | | | fail []
+| | | | | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | <default>
+| | | | | | | fail []
+| | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | mayRaise=[ExceptionFailure]
+| | <ko>
+| | | pushInput
+| | | minReads=(Right 1)
+| | | mayRaise=[ExceptionFailure]
+| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | j_1
+| | | _) -> i_0 GHC.Classes.== j_1)
+| | | minReads=(Right 1)
+| | | mayRaise=[ExceptionFailure]
+| | | choicesBranch
+| | | minReads=(Right 1)
+| | | mayRaise=[ExceptionFailure]
+| | | | <branch (\x_0 -> x_0)>
+| | | | | readRegister <hidden>
+| | | | | 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 0)
+| | | | | mayRaise=[]
+| | | | | call <hidden>
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | read ((GHC.Classes.==) '}')
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | call <hidden>
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | ret
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | <default>
+| | | | | fail []
+| | | | | minReads=(Left ExceptionFailure)
+| | | | | mayRaise=[ExceptionFailure]
let <hidden>
minReads=(Right 5)
mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 5)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 5)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 5)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 5)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 5)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 5)
-| mayRaise=[ExceptionFailure]
-| pushValue '['
-| minReads=(Right 5)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> GHC.Tuple.())
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
| read ((GHC.Classes.==) '[')
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| 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)
| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> x_0)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 2)
-| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
| pushValue (\x_0 -> x_0)
| minReads=(Right 1)
| 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_3 x_4))
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue GHC.Tuple.()
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| call <hidden>
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue GHC.Tuple.()
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
+| newRegister <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue ']'
+| iter <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| read ((GHC.Classes.==) ']')
-| 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 0)
-| mayRaise=[]
-| call <hidden>
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-pushValue GHC.Show.show
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> x_0)
- minReads=(Right 1)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | <ok>
+| | | pushValue (\x_0 -> \x_1 -> x_1)
+| | | minReads=(Right 0)
+| | | mayRaise=[]
+| | | call <hidden>
+| | | 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]
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | writeRegister <hidden>
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | | jump <hidden>
+| | | minReads=(Right 2)
+| | | mayRaise=[ExceptionFailure]
+| | <ko>
+| | | pushInput
+| | | minReads=(Right 1)
+| | | mayRaise=[ExceptionFailure]
+| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | j_1
+| | | _) -> i_0 GHC.Classes.== j_1)
+| | | minReads=(Right 1)
+| | | mayRaise=[ExceptionFailure]
+| | | choicesBranch
+| | | minReads=(Right 1)
+| | | mayRaise=[ExceptionFailure]
+| | | | <branch (\x_0 -> x_0)>
+| | | | | readRegister <hidden>
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | pushValue GHC.Tuple.()
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | read ((GHC.Classes.==) ']')
+| | | | | minReads=(Right 1)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | call <hidden>
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | ret
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | <default>
+| | | | | fail []
+| | | | | minReads=(Left ExceptionFailure)
+| | | | | mayRaise=[ExceptionFailure]
+pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> GHC.Show.show x_2)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
call <hidden>
lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
pushValue (\x_0 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-pushValue ((\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1) (\x_3 -> \x_4 -> x_3 x_4))
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-call <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-call <hidden>
- minReads=(Right 0)
- 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 0)
- mayRaise=[]
-call <hidden>
- minReads=(Right 0)
- mayRaise=[]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+newRegister <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-join <hidden>
- minReads=(Right 0)
- mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-catch ExceptionFailure
+iter <hidden>
minReads=(Right 0)
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)
+| | mayRaise=[ExceptionFailure]
| | catch ExceptionFailure
-| | minReads=(Right 0)
-| | mayRaise=[]
+| | minReads=(Right 13)
+| | mayRaise=[ExceptionFailure]
| | | <ok>
-| | | | pushInput
-| | | | minReads=(Left ExceptionFailure)
+| | | | 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)
| | | | mayRaise=[ExceptionFailure]
-| | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
-| | | | minReads=(Left ExceptionFailure)
+| | | | read ((GHC.Classes.==) 'f')
+| | | | minReads=(Right 13)
| | | | mayRaise=[ExceptionFailure]
-| | | | popValue
-| | | | minReads=(Left ExceptionFailure)
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 12)
+| | | | mayRaise=[ExceptionFailure]
+| | | | read ((GHC.Classes.==) 'u')
+| | | | minReads=(Right 12)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 11)
+| | | | mayRaise=[ExceptionFailure]
+| | | | read ((GHC.Classes.==) 'n')
+| | | | minReads=(Right 11)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 10)
+| | | | mayRaise=[ExceptionFailure]
+| | | | read ((GHC.Classes.==) 'c')
+| | | | minReads=(Right 10)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 9)
+| | | | mayRaise=[ExceptionFailure]
+| | | | read ((GHC.Classes.==) 't')
+| | | | minReads=(Right 9)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 8)
+| | | | mayRaise=[ExceptionFailure]
+| | | | read ((GHC.Classes.==) 'i')
+| | | | minReads=(Right 8)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 7)
+| | | | mayRaise=[ExceptionFailure]
+| | | | read ((GHC.Classes.==) 'o')
+| | | | minReads=(Right 7)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 6)
+| | | | mayRaise=[ExceptionFailure]
+| | | | read ((GHC.Classes.==) 'n')
+| | | | minReads=(Right 6)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 5)
| | | | mayRaise=[ExceptionFailure]
| | | | commit ExceptionFailure
-| | | | minReads=(Left ExceptionFailure)
+| | | | minReads=(Right 5)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 5)
+| | | | mayRaise=[ExceptionFailure]
+| | | | call <hidden>
+| | | | minReads=(Right 5)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 5)
+| | | | mayRaise=[ExceptionFailure]
+| | | | call <hidden>
+| | | | minReads=(Right 5)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 3)
+| | | | mayRaise=[ExceptionFailure]
+| | | | call <hidden>
+| | | | minReads=(Right 3)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | call <hidden>
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 1)
+| | | | mayRaise=[ExceptionFailure]
+| | | | join <hidden>
+| | | | minReads=(Right 24)
+| | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 36)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | call <hidden>
+| | | | | minReads=(Right 36)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 34)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | call <hidden>
+| | | | | minReads=(Right 34)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 30)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | readRegister <hidden>
+| | | | | minReads=(Right 30)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 30)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | writeRegister <hidden>
+| | | | | minReads=(Right 30)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | | jump <hidden>
+| | | | | minReads=(Right 30)
+| | | | | mayRaise=[ExceptionFailure]
+| | | | catch ExceptionFailure
+| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
+| | | | | <ok>
+| | | | | | pushValue (\x_0 -> \x_1 -> \x_2 -> GHC.Tuple.())
+| | | | | | minReads=(Right 1)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | read ((GHC.Classes.==) ':')
+| | | | | | minReads=(Right 1)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | call <hidden>
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | call <hidden>
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | commit ExceptionFailure
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | refJoin <hidden>
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | <ko>
+| | | | | | pushInput
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | j_1
+| | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | choicesBranch
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | call <hidden>
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | refJoin <hidden>
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | <default>
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | <ko>
| | | | loadInput
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
| | | | fail []
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
-| | | <ko>
-| | | | loadInput
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | pushValue GHC.Tuple.()
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | commit ExceptionFailure
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | refJoin <hidden>
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
| <ko>
| | pushInput
-| | minReads=(Left ExceptionFailure)
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
| | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
| | j_1
| | _) -> i_0 GHC.Classes.== j_1)
-| | minReads=(Left ExceptionFailure)
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
-| | minReads=(Left ExceptionFailure)
+| | choicesBranch
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
-| | | <branch>
-| | | | fail [FailureEnd]
-| | | | minReads=(Left ExceptionFailure)
+| | | <branch (\x_0 -> x_0)>
+| | | | readRegister <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | call <hidden>
+| | | | minReads=(Right 0)
+| | | | 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 0)
+| | | | mayRaise=[]
+| | | | call <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | join <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | ret
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | catch ExceptionFailure
+| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
+| | | | | <ok>
+| | | | | | catch ExceptionFailure
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | | <ok>
+| | | | | | | | pushInput
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | popValue
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | commit ExceptionFailure
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | loadInput
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <ko>
+| | | | | | | | loadInput
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | pushValue GHC.Tuple.()
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | commit ExceptionFailure
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | refJoin <hidden>
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | <ko>
+| | | | | | pushInput
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | j_1
+| | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | choicesBranch
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | fail [FailureEnd]
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <default>
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
| | | <default>
| | | | fail []
| | | | minReads=(Left ExceptionFailure)
-pushValue GHC.Show.show
- minReads=(Right 2)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
+pushValue (\x_0 -> \x_1 -> GHC.Show.show x_0)
minReads=(Right 2)
mayRaise=[ExceptionFailure]
join <hidden>
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue 'c'
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
| read ((GHC.Classes.==) 'c')
| 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 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
| ret
| minReads=(Right 0)
| mayRaise=[]
minReads=(Right 1)
mayRaise=[ExceptionFailure]
| <ok>
-| | pushValue (\x_0 -> \x_1 -> x_0)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | pushValue (\x_0 -> 'a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
| | read ((GHC.Classes.==) 'a')
| | _) -> i_0 GHC.Classes.== j_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
+| | choicesBranch
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | | <branch>
-| | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'b'
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | <branch (\x_0 -> x_0)>
+| | | | pushValue (\x_0 -> 'b')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
| | | | read ((GHC.Classes.==) 'b')
-pushValue GHC.Show.show
- minReads=(Right 2)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
+pushValue (\x_0 -> \x_1 -> GHC.Show.show x_0)
minReads=(Right 2)
mayRaise=[ExceptionFailure]
join <hidden>
| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\x_0 -> \x_1 -> x_0)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| pushValue 'd'
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 1)
-| mayRaise=[ExceptionFailure]
| read ((GHC.Classes.==) 'd')
| 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 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
| ret
| minReads=(Right 0)
| mayRaise=[]
minReads=(Right 1)
mayRaise=[ExceptionFailure]
| <ok>
-| | join <hidden>
+| | pushValue (\x_0 -> 'a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | refJoin <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | catch ExceptionFailure
+| | read ((GHC.Classes.==) 'a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | | <ok>
-| | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'a'
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | read ((GHC.Classes.==) 'a')
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | commit ExceptionFailure
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | refJoin <hidden>
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | <ko>
-| | | | pushInput
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | | j_1
-| | | | _) -> i_0 GHC.Classes.== j_1)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | choicesBranch [\x_0 -> x_0]
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | minReads=(Right 0)
+| | mayRaise=[]
+| | commit ExceptionFailure
+| | minReads=(Right 0)
+| | mayRaise=[]
+| | refJoin <hidden>
+| | minReads=(Right 0)
+| | mayRaise=[]
+| <ko>
+| | pushInput
+| | minReads=(Right 1)
+| | mayRaise=[ExceptionFailure]
+| | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | j_1
+| | _) -> i_0 GHC.Classes.== j_1)
+| | minReads=(Right 1)
+| | mayRaise=[ExceptionFailure]
+| | choicesBranch
+| | minReads=(Right 1)
+| | mayRaise=[ExceptionFailure]
+| | | <branch (\x_0 -> x_0)>
+| | | | catch ExceptionFailure
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | | <branch>
-| | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | minReads=(Right 1)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue 'b'
-| | | | | | minReads=(Right 1)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | <ok>
+| | | | | | pushValue (\x_0 -> 'b')
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
| | | | | | read ((GHC.Classes.==) 'b')
| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
+| | | | | | commit ExceptionFailure
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
| | | | | | refJoin <hidden>
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
-| | | | | <default>
-| | | | | | fail []
-| | | | | | minReads=(Left ExceptionFailure)
+| | | | | <ko>
+| | | | | | pushInput
+| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| <ko>
-| | pushInput
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | j_1
-| | _) -> i_0 GHC.Classes.== j_1)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | | <branch>
-| | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'c'
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | read ((GHC.Classes.==) 'c')
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | refJoin <hidden>
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
+| | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | j_1
+| | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | minReads=(Right 1)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | choicesBranch
+| | | | | | minReads=(Right 1)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | pushValue (\x_0 -> 'c')
+| | | | | | | | minReads=(Right 1)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | read ((GHC.Classes.==) 'c')
+| | | | | | | | minReads=(Right 1)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | refJoin <hidden>
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | <default>
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
| | | <default>
| | | | fail []
| | | | minReads=(Left ExceptionFailure)
minReads=(Right 3)
mayRaise=[ExceptionFailure]
| <ok>
-| | pushValue (GHC.Types.:)
-| | minReads=(Right 3)
-| | mayRaise=[ExceptionFailure]
-| | pushValue (\x_0 -> \x_1 -> x_0)
-| | minReads=(Right 3)
-| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
-| | minReads=(Right 3)
-| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | pushValue (\x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' GHC.Types.[])))
| | minReads=(Right 3)
| | mayRaise=[ExceptionFailure]
| | read ((GHC.Classes.==) 'a')
| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 2)
-| | mayRaise=[ExceptionFailure]
-| | pushValue (GHC.Types.:)
-| | minReads=(Right 2)
-| | mayRaise=[ExceptionFailure]
-| | pushValue (\x_0 -> \x_1 -> x_0)
-| | minReads=(Right 2)
-| | mayRaise=[ExceptionFailure]
-| | pushValue 'b'
-| | minReads=(Right 2)
-| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 2)
-| | mayRaise=[ExceptionFailure]
| | read ((GHC.Classes.==) 'b')
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | pushValue (GHC.Types.:)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | pushValue (\x_0 -> \x_1 -> x_0)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | pushValue 'c'
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
| | read ((GHC.Classes.==) 'c')
| | 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 0)
-| | mayRaise=[]
-| | pushValue GHC.Types.[]
-| | minReads=(Right 0)
-| | mayRaise=[]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 0)
-| | mayRaise=[]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 0)
-| | mayRaise=[]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 0)
-| | mayRaise=[]
| | commit ExceptionFailure
| | minReads=(Right 0)
| | mayRaise=[]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'a'
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | read ((GHC.Classes.==) 'a')
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
pushValue GHC.Show.show
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-call <hidden>
+pushValue (\x_0 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue GHC.Types.[]
- minReads=(Right 0)
- mayRaise=[]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+newRegister <hidden>
minReads=(Right 0)
- mayRaise=[]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[]
-ret
+ mayRaise=[ExceptionFailure]
+iter <hidden>
minReads=(Right 0)
- mayRaise=[]
+ mayRaise=[ExceptionFailure]
+| <ok>
+| | pushValue (\x_0 -> (GHC.Types.:) 'a')
+| | minReads=(Right 3)
+| | mayRaise=[ExceptionFailure]
+| | read ((GHC.Classes.==) 'a')
+| | minReads=(Right 3)
+| | 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]
+| | readRegister <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | writeRegister <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | jump <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| <ko>
+| | pushInput
+| | minReads=(Right 0)
+| | mayRaise=[ExceptionFailure]
+| | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | j_1
+| | _) -> i_0 GHC.Classes.== j_1)
+| | minReads=(Right 0)
+| | mayRaise=[ExceptionFailure]
+| | choicesBranch
+| | minReads=(Right 0)
+| | mayRaise=[ExceptionFailure]
+| | | <branch (\x_0 -> x_0)>
+| | | | readRegister <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | pushValue GHC.Types.[]
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | ret
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | <default>
+| | | | fail []
+| | | | minReads=(Left ExceptionFailure)
+| | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | 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=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
let <hidden>
minReads=(Right 4)
mayRaise=[ExceptionFailure]
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'a'
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types.[]))))
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
| | | read ((GHC.Classes.==) 'a')
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'b'
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
| | | read ((GHC.Classes.==) 'b')
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'c'
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
| | | read ((GHC.Classes.==) 'c')
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'd'
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
| | | read ((GHC.Classes.==) 'd')
| | | 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 0)
-| | | mayRaise=[]
-| | | pushValue GHC.Types.[]
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
| | | commit ExceptionFailure
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | fail []
| | | minReads=(Left ExceptionFailure)
| | | mayRaise=[ExceptionFailure]
-pushValue GHC.Show.show
- minReads=(Right 4)
- mayRaise=[ExceptionFailure]
-pushValue (GHC.Types.:)
+pushValue (\x_0 -> \x_1 -> GHC.Show.show ((GHC.Types.:) x_0 x_1))
minReads=(Right 4)
mayRaise=[ExceptionFailure]
call <hidden>
lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-call <hidden>
+pushValue (\x_0 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue GHC.Types.[]
- minReads=(Right 0)
- mayRaise=[]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+newRegister <hidden>
minReads=(Right 0)
- mayRaise=[]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[]
-ret
+ mayRaise=[ExceptionFailure]
+iter <hidden>
minReads=(Right 0)
- mayRaise=[]
+ mayRaise=[ExceptionFailure]
+| <ok>
+| | pushValue (GHC.Types.:)
+| | minReads=(Right 0)
+| | mayRaise=[]
+| | call <hidden>
+| | 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]
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | minReads=(Right 8)
+| | mayRaise=[ExceptionFailure]
+| | writeRegister <hidden>
+| | minReads=(Right 8)
+| | mayRaise=[ExceptionFailure]
+| | jump <hidden>
+| | minReads=(Right 8)
+| | mayRaise=[ExceptionFailure]
+| <ko>
+| | pushInput
+| | minReads=(Right 0)
+| | mayRaise=[ExceptionFailure]
+| | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | j_1
+| | _) -> i_0 GHC.Classes.== j_1)
+| | minReads=(Right 0)
+| | mayRaise=[ExceptionFailure]
+| | choicesBranch
+| | minReads=(Right 0)
+| | mayRaise=[ExceptionFailure]
+| | | <branch (\x_0 -> x_0)>
+| | | | readRegister <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | pushValue GHC.Types.[]
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | ret
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | <default>
+| | | | fail []
+| | | | minReads=(Left ExceptionFailure)
+| | | | mayRaise=[ExceptionFailure]
-let <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | 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=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
let <hidden>
minReads=(Right 4)
mayRaise=[ExceptionFailure]
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'a'
-| | | minReads=(Right 4)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> \x_3 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types.[]))))
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
| | | read ((GHC.Classes.==) 'a')
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'b'
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 3)
-| | | mayRaise=[ExceptionFailure]
| | | read ((GHC.Classes.==) 'b')
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'c'
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 2)
-| | | mayRaise=[ExceptionFailure]
| | | read ((GHC.Classes.==) 'c')
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'd'
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
| | | read ((GHC.Classes.==) 'd')
| | | 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 0)
-| | | mayRaise=[]
-| | | pushValue GHC.Types.[]
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
| | | commit ExceptionFailure
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | fail []
| | | minReads=(Left ExceptionFailure)
| | | mayRaise=[ExceptionFailure]
-pushValue GHC.Show.show
- minReads=(Right 4)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
- minReads=(Right 4)
- mayRaise=[ExceptionFailure]
-pushValue (GHC.Types.:)
+pushValue (\x_0 -> \x_1 -> \x_2 -> GHC.Show.show ((GHC.Types.:) x_0 x_1))
minReads=(Right 4)
mayRaise=[ExceptionFailure]
call <hidden>
lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-call <hidden>
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-pushValue GHC.Types.[]
+pushValue (\x_0 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+newRegister <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-join <hidden>
- minReads=(Right 0)
- mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-catch ExceptionFailure
+iter <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
| <ok>
-| | catch ExceptionFailure
+| | pushValue (GHC.Types.:)
| | minReads=(Right 0)
| | mayRaise=[]
-| | | <ok>
-| | | | pushInput
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | popValue
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | commit ExceptionFailure
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | loadInput
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | fail []
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | <ko>
-| | | | loadInput
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | pushValue GHC.Tuple.()
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | commit ExceptionFailure
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | refJoin <hidden>
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
+| | call <hidden>
+| | 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]
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | minReads=(Right 8)
+| | mayRaise=[ExceptionFailure]
+| | writeRegister <hidden>
+| | minReads=(Right 8)
+| | mayRaise=[ExceptionFailure]
+| | jump <hidden>
+| | minReads=(Right 8)
+| | mayRaise=[ExceptionFailure]
| <ko>
| | pushInput
-| | minReads=(Left ExceptionFailure)
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
| | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
| | j_1
| | _) -> i_0 GHC.Classes.== j_1)
-| | minReads=(Left ExceptionFailure)
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
-| | minReads=(Left ExceptionFailure)
+| | choicesBranch
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
-| | | <branch>
-| | | | fail [FailureEnd]
-| | | | minReads=(Left ExceptionFailure)
+| | | <branch (\x_0 -> x_0)>
+| | | | readRegister <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | pushValue GHC.Types.[]
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | join <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | ret
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | catch ExceptionFailure
+| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
+| | | | | <ok>
+| | | | | | catch ExceptionFailure
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | | <ok>
+| | | | | | | | pushInput
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | popValue
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | commit ExceptionFailure
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | loadInput
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <ko>
+| | | | | | | | loadInput
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | pushValue GHC.Tuple.()
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | commit ExceptionFailure
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | refJoin <hidden>
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | <ko>
+| | | | | | pushInput
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | j_1
+| | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | choicesBranch
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | fail [FailureEnd]
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <default>
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
| | | <default>
| | | | fail []
| | | | minReads=(Left ExceptionFailure)
minReads=(Right 2)
mayRaise=[ExceptionFailure]
| <ok>
-| | pushValue (GHC.Types.:)
-| | minReads=(Right 2)
-| | mayRaise=[ExceptionFailure]
-| | pushValue (\x_0 -> \x_1 -> x_0)
-| | minReads=(Right 2)
-| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
-| | minReads=(Right 2)
-| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | pushValue (\x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types.[]))
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
| | read ((GHC.Classes.==) 'a')
| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | pushValue (GHC.Types.:)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | pushValue (\x_0 -> \x_1 -> x_0)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 1)
-| | mayRaise=[ExceptionFailure]
| | read ((GHC.Classes.==) 'a')
| | 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 0)
-| | mayRaise=[]
-| | pushValue GHC.Types.[]
-| | minReads=(Right 0)
-| | mayRaise=[]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 0)
-| | mayRaise=[]
-| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | minReads=(Right 0)
-| | mayRaise=[]
| | commit ExceptionFailure
| | minReads=(Right 0)
| | mayRaise=[]
| | _) -> i_0 GHC.Classes.== j_1)
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
+| | choicesBranch
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | | <branch>
-| | | | pushValue (GHC.Types.:)
-| | | | minReads=(Right 2)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | minReads=(Right 2)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'a'
-| | | | minReads=(Right 2)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | <branch (\x_0 -> x_0)>
+| | | | pushValue (\x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types.[]))
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
| | | | read ((GHC.Classes.==) 'a')
| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (GHC.Types.:)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'b'
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
| | | | read ((GHC.Classes.==) 'b')
| | | | 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 0)
-| | | | mayRaise=[]
-| | | | pushValue GHC.Types.[]
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
| | | | refJoin <hidden>
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
| | | <ok>
-| | | | pushValue (GHC.Types.:)
-| | | | minReads=(Right 2)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | minReads=(Right 2)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'a'
-| | | | minReads=(Right 2)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | pushValue (\x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types.[]))
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
| | | | read ((GHC.Classes.==) 'a')
| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (GHC.Types.:)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'a'
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 1)
-| | | | mayRaise=[ExceptionFailure]
| | | | read ((GHC.Classes.==) 'a')
| | | | 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 0)
-| | | | mayRaise=[]
-| | | | pushValue GHC.Types.[]
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | _) -> i_0 GHC.Classes.== j_1)
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
+| | choicesBranch
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | | <branch>
+| | | <branch (\x_0 -> x_0)>
| | | | catch ExceptionFailure
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
| | | | | <ok>
-| | | | | | pushValue (GHC.Types.:)
-| | | | | | minReads=(Right 2)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | minReads=(Right 2)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue 'a'
-| | | | | | minReads=(Right 2)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | | pushValue (\x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types.[]))
| | | | | | minReads=(Right 2)
| | | | | | mayRaise=[ExceptionFailure]
| | | | | | read ((GHC.Classes.==) 'a')
| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 1)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue (GHC.Types.:)
-| | | | | | minReads=(Right 1)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | | | | minReads=(Right 1)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue 'b'
-| | | | | | minReads=(Right 1)
-| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 1)
-| | | | | | mayRaise=[ExceptionFailure]
| | | | | | read ((GHC.Classes.==) 'b')
| | | | | | 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 0)
-| | | | | | mayRaise=[]
-| | | | | | pushValue GHC.Types.[]
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
-| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | | | | minReads=(Right 0)
-| | | | | | mayRaise=[]
| | | | | | commit ExceptionFailure
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
-let <hidden>
+pushValue (\x_0 -> \x_1 -> GHC.Show.show x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-| catch ExceptionFailure
-| minReads=(Right 0)
-| mayRaise=[ExceptionFailure]
-| | <ok>
-| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (GHC.Types.:)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\x_0 -> \x_1 -> x_0)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'r'
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | read ((GHC.Classes.==) 'r')
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
-| | | j_1
-| | | _) -> i_0 GHC.Classes.== j_1)
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [\x_0 -> x_0]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\x_0 -> x_0)
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | | ret
-| | | | | minReads=(Right 0)
-| | | | | mayRaise=[]
-| | | | <default>
-| | | | | fail []
-| | | | | minReads=(Left ExceptionFailure)
-| | | | | mayRaise=[ExceptionFailure]
-pushValue GHC.Show.show
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-pushValue (\x_0 -> \x_1 -> x_0)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-call <hidden>
+pushValue (\x_0 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue GHC.Types.[]
+newRegister <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-lift2Value (\x_0 -> \x_1 -> x_0 x_1)
- minReads=(Right 0)
- mayRaise=[ExceptionFailure]
-join <hidden>
- minReads=(Right 0)
- mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
-| minReads=(Right 0)
-| mayRaise=[]
-| ret
-| minReads=(Right 0)
-| mayRaise=[]
-catch ExceptionFailure
+iter <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
| <ok>
-| | catch ExceptionFailure
-| | minReads=(Right 0)
-| | mayRaise=[]
-| | | <ok>
-| | | | pushInput
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | popValue
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | commit ExceptionFailure
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | loadInput
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | | fail []
-| | | | minReads=(Left ExceptionFailure)
-| | | | mayRaise=[ExceptionFailure]
-| | | <ko>
-| | | | loadInput
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | pushValue GHC.Tuple.()
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | commit ExceptionFailure
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
-| | | | refJoin <hidden>
-| | | | minReads=(Right 0)
-| | | | mayRaise=[]
+| | pushValue (\x_0 -> (GHC.Types.:) 'r')
+| | minReads=(Right 3)
+| | mayRaise=[ExceptionFailure]
+| | read ((GHC.Classes.==) 'r')
+| | minReads=(Right 3)
+| | 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]
+| | readRegister <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | writeRegister <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
+| | jump <hidden>
+| | minReads=(Right 2)
+| | mayRaise=[ExceptionFailure]
| <ko>
| | pushInput
-| | minReads=(Left ExceptionFailure)
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
| | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
| | j_1
| | _) -> i_0 GHC.Classes.== j_1)
-| | minReads=(Left ExceptionFailure)
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
-| | minReads=(Left ExceptionFailure)
+| | choicesBranch
+| | minReads=(Right 0)
| | mayRaise=[ExceptionFailure]
-| | | <branch>
-| | | | fail [FailureEnd]
-| | | | minReads=(Left ExceptionFailure)
+| | | <branch (\x_0 -> x_0)>
+| | | | readRegister <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | pushValue GHC.Types.[]
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | minReads=(Right 0)
+| | | | mayRaise=[ExceptionFailure]
+| | | | join <hidden>
+| | | | minReads=(Right 0)
+| | | | mayRaise=[]
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | | ret
+| | | | | minReads=(Right 0)
+| | | | | mayRaise=[]
+| | | | catch ExceptionFailure
+| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
+| | | | | <ok>
+| | | | | | catch ExceptionFailure
+| | | | | | minReads=(Right 0)
+| | | | | | mayRaise=[]
+| | | | | | | <ok>
+| | | | | | | | pushInput
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | popValue
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | commit ExceptionFailure
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | loadInput
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <ko>
+| | | | | | | | loadInput
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | pushValue GHC.Tuple.()
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | commit ExceptionFailure
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | | | | refJoin <hidden>
+| | | | | | | | minReads=(Right 0)
+| | | | | | | | mayRaise=[]
+| | | | | <ko>
+| | | | | | pushInput
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | lift2Value (\(Data.Text.Internal.Text _ i_0 _) (Data.Text.Internal.Text _
+| | | | | | j_1
+| | | | | | _) -> i_0 GHC.Classes.== j_1)
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | choicesBranch
+| | | | | | minReads=(Left ExceptionFailure)
+| | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <branch (\x_0 -> x_0)>
+| | | | | | | | fail [FailureEnd]
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
+| | | | | | | <default>
+| | | | | | | | fail []
+| | | | | | | | minReads=(Left ExceptionFailure)
+| | | | | | | | mayRaise=[ExceptionFailure]
| | | <default>
| | | | fail []
| | | | minReads=(Left ExceptionFailure)
| | _) -> i_0 GHC.Classes.== j_1)
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
-| | choicesBranch [\x_0 -> x_0]
+| | choicesBranch
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
-| | | <branch>
+| | | <branch (\x_0 -> x_0)>
| | | | fail [FailureEnd]
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
parsers :: [Text -> Either (P.ParsingError Text) String]
parsers =
[ p1, p2, p3, p4, p5, p6, p7, p8, p9
- , p10, p11, p12, p13, p14, p15, p16
+ , p10, p11, p12, p13, p14, p15, p16--, p17
]
p1 = $$(TH.Code $ TH.runIO s1)
p14 = $$(TH.Code $ TH.runIO s14)
p15 = $$(TH.Code $ TH.runIO s15)
p16 = $$(TH.Code $ TH.runIO s16)
+--p17 = $$(TH.Code $ TH.runIO s17)
-ParsingErrorStandard {parsingErrorOffset = 4, parsingErrorException = ExceptionFailure, parsingErrorUnexpected = Just 'c', parsingErrorExpecting = fromList [FailureToken 'a',FailureToken 'b']}
\ No newline at end of file
+ParsingErrorStandard {parsingErrorOffset = 3, parsingErrorException = ExceptionFailure, parsingErrorUnexpected = Just 'a', parsingErrorExpecting = fromList [FailureHorizon 3,FailureToken 'b']}
\ No newline at end of file
-"baacbccbaa"
\ No newline at end of file
+ParsingErrorStandard {parsingErrorOffset = 8, parsingErrorException = ExceptionFailure, parsingErrorUnexpected = Just 'a', parsingErrorExpecting = fromList [FailureEnd,FailureHorizon 3]}
\ No newline at end of file
-"aaaaa"
\ No newline at end of file
+"aaa"
\ 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
+ParsingErrorStandard {parsingErrorOffset = 2, parsingErrorException = ExceptionFailure, parsingErrorUnexpected = Just 'r', parsingErrorExpecting = fromList [FailureEnd,FailureHorizon 3]}
\ No newline at end of file
import Golden.Utils
import qualified Grammar
+import Symantic.Parser.Grammar (optimizeGrammar)
goldens :: TestTree
goldens = testGroup "Splice"
- [ let spliceFile = getGoldenDir $ "Splice/"</>"G"++show g<.>"expected"<.>"txt" in
+ [ let spliceFile = getGoldenDir $ "Splice/"</>"G"++show gNum<.>"expected"<.>"txt" in
goldenVsStringDiff (takeBaseName (dropExtensions spliceFile)) goldenDiff spliceFile $ do
tExp <- splice
fromString <$> Process.readProcess "ormolu"
, "-o", "-XUnboxedTuples"
]
(show (TH.ppr (TH.hideName (TH.unType tExp))))
- | (g, splice) <- List.zip [1::Int ..] splices
+ | (gNum, splice) <- List.zip [1::Int ..] splices
]
splices :: [IO (TH.TExp (Text -> Either (ParsingError Text) String))]
splices = (<$> Grammar.grammars) $ \g -> TH.runQ $ do
- TH.runIO resetTHNameCounter
- mach <- TH.runIO $ optimizeMachine g
+ mach <- TH.runIO $ do
+ resetTHNameCounter
+ optimizeMachine $ optimizeGrammar g
TH.examineCode $ generateCode mach
[ s1,s2,s3,s4,s5,s6,s7,s8,s9
- ,s10,s11,s12,s13,s14,s15,s16
+ ,s10,s11,s12,s13,s14,s15,s16,s17
] = splices
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let
- in let readFail = finalRaise
- in if readMore init
- then
- let !(# c, cs #) = readNext init
- in if (GHC.Classes.==) 'a' c
- then
- let _ = "resume"
- in finalRet
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in GHC.Show.show 'a'
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in let readFail = finalRaise
+ in if readMore init
+ then
+ let !(# c, cs #) = readNext init
+ in if (GHC.Classes.==) 'a' c
+ then
+ let _ = "resume"
+ in finalRet
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in GHC.Show.show 'a'
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let
- in let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show v
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
)
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- init
- failInp
- then
- let _ = "choicesBranch.then"
- in let readFail = finalRaise
- in if readMore failInp
- then
- let !(#
- c,
- cs
- #) = readNext failInp
- in if (GHC.Classes.==) 'b' c
- then
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in 'b'
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show v
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ init
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = finalRaise
+ in if readMore failInp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) 'b' c
+ then
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in 'b'
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore init
- then
- let !(# c, cs #) = readNext init
- in if (GHC.Classes.==) 'a' c
- then
- let _ = "resume"
- in join
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in 'a'
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let readFail = catchHandler
+ in if readMore init
+ then
+ let !(# c, cs #) = readNext init
+ in if (GHC.Classes.==) 'a' c
+ then
+ let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in 'a'
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
_
i
_
_
) -> i GHC.Classes.== j
)
- inp
+ loopInput
failInp
then
let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let readFail = finalRaise
+ in if readMore failInp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) 'b' c
+ then
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show (sr GHC.Types . [])
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
else
let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'a' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> (GHC.Types.:) 'a' (v x)
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let readFail = finalRaise
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'b' c
- then
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show (v GHC.Types . [])
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) 'a' c
+ then do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = \x -> sr ((GHC.Types.:) 'a' x)
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") cs (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
farInp,
farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
farInp,
farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- init
- Data.Map.Internal.Tip
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop finalRet init Data.Map.Internal.Tip
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
_
i
_
_
) -> i GHC.Classes.== j
)
- inp
+ loopInput
failInp
then
let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show (sr GHC.Types . [])
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ failInp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ failInp
+ in let readFail = catchHandler
+ in if readMore failInp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
else
let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (\t -> ('a' GHC.Classes.== t) GHC.Classes.|| (('b' GHC.Classes.== t) GHC.Classes.|| (('c' GHC.Classes.== t) GHC.Classes.|| (('d' GHC.Classes.== t) GHC.Classes.|| GHC.Types.False)))) c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> (GHC.Types.:) c (v x)
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 4
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
- )
- )
- ( Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- )
- ( Data.Set.Internal.Bin
- 2
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
- )
- )
- Data.Set.Internal.Tip
- ( Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'd'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- )
- )
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show (v GHC.Types . [])
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (\t -> ('a' GHC.Classes.== t) GHC.Classes.|| (('b' GHC.Classes.== t) GHC.Classes.|| (('c' GHC.Classes.== t) GHC.Classes.|| (('d' GHC.Classes.== t) GHC.Classes.|| GHC.Types.False)))) c
+ then do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = \x -> sr ((GHC.Types.:) c x)
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") cs (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 4
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ )
+ )
+ ( Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ )
+ ( Data.Set.Internal.Bin
+ 2
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
+ )
+ )
+ Data.Set.Internal.Tip
+ ( Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'd'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ )
+ )
in let (#
farInp,
farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
GHC.Types.LT ->
(#
- failInp,
+ callInput,
failExp
#)
GHC.Types.EQ ->
(#
- farInp,
- failExp GHC.Base.<> farExp
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
#)
GHC.Types.GT ->
(#
- farInp,
- farExp
+ init,
+ Data.Set.Internal.empty
#)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- init
- Data.Map.Internal.Tip
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop finalRet init Data.Map.Internal.Tip
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let name = \(!ok) (!inp) (!koByLabel) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
- name = \(!ok) (!inp) (!koByLabel) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v GHC.Types . []
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let name = \(!callReturn) (!callInput) (!callCatchStackByLabel) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
_
i
_
_
) -> i GHC.Classes.== j
)
- inp
+ loopInput
failInp
then
let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ failInp
else
let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let join = \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> (GHC.Types.:) v (v x)
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) '<' c
- then
- let _ = "choicesBranch.then"
- in let readFail = readFail
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in let _ = "resume"
- in join
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Backward
- )
- cs
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (\c -> GHC.Classes.not (('<' GHC.Classes.== c) GHC.Classes.|| (('>' GHC.Classes.== c) GHC.Classes.|| (('+' GHC.Classes.== c) GHC.Classes.|| (('-' GHC.Classes.== c) GHC.Classes.|| ((',' GHC.Classes.== c) GHC.Classes.|| (('.' GHC.Classes.== c) GHC.Classes.|| (('[' GHC.Classes.== c) GHC.Classes.|| ((']' GHC.Classes.== c) GHC.Classes.|| GHC.Types.False))))))))) c
+ then do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") cs (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput init Data.Set.Internal.empty
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop callReturn callInput (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in sr GHC.Types . []
+ )
+ failInp
+ else
+ let _ = "choicesBranch.else"
+ 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 join = \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = \x -> sr ((GHC.Types.:) v x)
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let readFail = catchHandler callInput
+ in if readMore callInput
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (\x -> (\x -> \x -> (GHC.Classes.==) x x) '<' x) c
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = readFail
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in Parsers.Brainfuck.Types.Backward
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "choicesBranch.else"
- in if (GHC.Classes.==) '>' c
- then
- let _ = "choicesBranch.then"
- in let readFail = readFail
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in let _ = "resume"
- in join
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Forward
+ cs
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
)
- cs
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "choicesBranch.else"
- in if (GHC.Classes.==) '+' c
- then
- let _ = "choicesBranch.then"
- in let readFail = readFail
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in let _ = "resume"
- in join
- init
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Increment
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in if (\x -> (\x -> \x -> (GHC.Classes.==) x x) '>' x) c
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = readFail
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in Parsers.Brainfuck.Types.Forward
+ )
+ cs
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
)
- cs
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "choicesBranch.else"
- in if (GHC.Classes.==) '-' c
- then
- let _ = "choicesBranch.then"
- in let readFail = readFail
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in let _ = "resume"
- in join
- init
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Decrement
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in if (\x -> (\x -> \x -> (GHC.Classes.==) x x) '+' x) c
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = readFail
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in Parsers.Brainfuck.Types.Increment
+ )
+ cs
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
)
- cs
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "choicesBranch.else"
- in if (GHC.Classes.==) ',' c
- then
- let _ = "choicesBranch.then"
- in let readFail = readFail
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in let _ = "resume"
- in join
- init
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Input
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in if (\x -> (\x -> \x -> (GHC.Classes.==) x x) '-' x) c
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = readFail
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in Parsers.Brainfuck.Types.Decrement
+ )
+ cs
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
)
- cs
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "choicesBranch.else"
- in if (GHC.Classes.==) '.' c
- then
- let _ = "choicesBranch.then"
- in let readFail = readFail
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in let _ = "resume"
- in join
- init
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Output
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in if (\x -> (\x -> \x -> (GHC.Classes.==) x x) ',' x) c
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = readFail
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in Parsers.Brainfuck.Types.Input
+ )
+ cs
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
)
- cs
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in if (\x -> (\x -> \x -> (GHC.Classes.==) x x) '.' x) c
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = readFail
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in Parsers.Brainfuck.Types.Output
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "choicesBranch.else"
- in if (GHC.Classes.==) '[' c
- then
- let _ = "choicesBranch.then"
- in let readFail = readFail
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let readFail = readFail
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) ']' c
- then
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Loop v
- )
- cs
- else
- let _ = "checkToken.else"
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
+ cs
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in if (\x -> (\x -> \x -> (GHC.Classes.==) x x) '[' x) c
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = readFail
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let readFail = readFail
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext inp
+ in if (GHC.Classes.==) ']' c
+ then
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in Parsers.Brainfuck.Types.Loop v
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
farInp,
farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
- )
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "choicesBranch.else"
- in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEmpty) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEmpty) Data.Set.Internal.Tip Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop callReturn callInput (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in finalRet
farInp
farExp
( let _ = "resume.genCode"
- in \x -> x
+ in GHC.Show.show v
)
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (\c -> GHC.Classes.not (('<' GHC.Classes.== c) GHC.Classes.|| (('>' GHC.Classes.== c) GHC.Classes.|| (('+' GHC.Classes.== c) GHC.Classes.|| (('-' GHC.Classes.== c) GHC.Classes.|| ((',' GHC.Classes.== c) GHC.Classes.|| (('.' GHC.Classes.== c) GHC.Classes.|| (('[' GHC.Classes.== c) GHC.Classes.|| ((']' GHC.Classes.== c) GHC.Classes.|| GHC.Types.False))))))))) c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v x
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp init Data.Set.Internal.empty
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show v
- )
- inp
- )
- inp
- Data.Map.Internal.Tip
- )
- init
- Data.Map.Internal.Tip
+ inp
+ )
+ inp
+ Data.Map.Internal.Tip
+ )
+ init
+ Data.Map.Internal.Tip
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let name = \(!ok) (!inp) (!koByLabel) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
- name = \(!ok) (!inp) (!koByLabel) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let join = \farInp farExp v (!inp) ->
let _ = "resume"
- in ok
+ in callReturn
farInp
farExp
( let _ = "resume.genCode"
- in GHC.Tuple . ()
+ in v
)
inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
- name = \(!ok) (!inp) (!koByLabel) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ inp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ inp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ inp
+ Data.Map.Internal.Tip
)
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ 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)
then
- let _ = "choicesBranch.then"
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) '!' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
)
inp
- )
- failInp
- Data.Map.Internal.Tip
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '!'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
- name = \(!ok) (!inp) (!koByLabel) ->
- let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if GHC.Unicode.isSpace c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- cs
- Data.Map.Internal.Tip
- else
- let _ = "checkToken.else"
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp init Data.Set.Internal.empty
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (\t -> ('0' GHC.Classes.== t) GHC.Classes.|| (('1' GHC.Classes.== t) GHC.Classes.|| (('2' GHC.Classes.== t) GHC.Classes.|| (('3' GHC.Classes.== t) GHC.Classes.|| (('4' GHC.Classes.== t) GHC.Classes.|| (('5' GHC.Classes.== t) GHC.Classes.|| (('6' GHC.Classes.== t) GHC.Classes.|| (('7' GHC.Classes.== t) GHC.Classes.|| (('8' GHC.Classes.== t) GHC.Classes.|| (('9' GHC.Classes.== t) GHC.Classes.|| GHC.Types.False)))))))))) c
- then
- let _ = "resume"
- in ok
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in c
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 10
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '3'
- )
- )
- ( Data.Set.Internal.Bin
- 3
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '1'
- )
- )
- ( Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '0'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop callReturn inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
)
- ( Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '2'
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
)
+ failInp
+ else
+ let _ = "choicesBranch.else"
+ 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 ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let _ = "jump"
+ in loop callReturn inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel
+ in if readMore callInput
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if GHC.Unicode.isSpace c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- )
+ inp
+ )
+ cs
+ Data.Map.Internal.Tip
+ else
+ let _ = "checkToken.else"
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput init Data.Set.Internal.empty
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- ( Data.Set.Internal.Bin
- 6
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel
+ in if readMore callInput
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (\t -> ('0' GHC.Classes.== t) GHC.Classes.|| (('1' GHC.Classes.== t) GHC.Classes.|| (('2' GHC.Classes.== t) GHC.Classes.|| (('3' GHC.Classes.== t) GHC.Classes.|| (('4' GHC.Classes.== t) GHC.Classes.|| (('5' GHC.Classes.== t) GHC.Classes.|| (('6' GHC.Classes.== t) GHC.Classes.|| (('7' GHC.Classes.== t) GHC.Classes.|| (('8' GHC.Classes.== t) GHC.Classes.|| (('9' GHC.Classes.== t) GHC.Classes.|| GHC.Types.False)))))))))) c
+ then
+ let _ = "resume"
+ in callReturn
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in c
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 10
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '7'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '3'
)
)
( Data.Set.Internal.Bin
3
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '5'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '1'
)
)
( Data.Set.Internal.Bin
1
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '4'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '0'
)
)
Data.Set.Internal.Tip
1
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '6'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '2'
)
)
Data.Set.Internal.Tip
)
)
( Data.Set.Internal.Bin
- 2
+ 6
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '8'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '7'
)
)
- Data.Set.Internal.Tip
( Data.Set.Internal.Bin
- 1
+ 3
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '9'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '5'
+ )
+ )
+ ( Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '4'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ )
+ ( Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '6'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ )
+ )
+ ( Data.Set.Internal.Bin
+ 2
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '8'
)
)
Data.Set.Internal.Tip
- Data.Set.Internal.Tip
+ ( Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '9'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ )
)
)
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) '(' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in '('
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '('
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) '(' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in '('
+ )
+ inp
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '('
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) ')' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in ')'
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ')'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) ')' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in ')'
+ )
+ inp
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ')'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) ',' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in ','
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ','
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) ',' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in ','
+ )
+ inp
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ','
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) ';' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in ';'
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ';'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) ';' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in ';'
+ )
+ inp
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ';'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) '{' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let readFail = readFail
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) '}' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '}'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) '{' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let readFail = readFail
+ in if readMore inp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext inp
+ in if (GHC.Classes.==) '}' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '}'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
farInp,
farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '{'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 4 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) '[' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let readFail = readFail
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) ']' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ']'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '['
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 5
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if Parsers.Nandlang.nandIdentStart c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- cs
- Data.Map.Internal.Tip
- else
- let _ = "checkToken.else"
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp init Data.Set.Internal.empty
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ )
+ inp
+ Data.Map.Internal.Tip
+ )
failInp
- then
- let _ = "choicesBranch.then"
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ loop = \_callReturn callInput callCatchStackByLabel ->
+ let join = \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ callInput
failInp
- Data.Map.Internal.Tip
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- failInp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let join = \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
+ then
+ let _ = "choicesBranch.then"
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
)
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- failInp
- Data.Map.Internal.Tip
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ failInp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ failInp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ failInp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler callInput Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let join = \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let readFail = catchHandler
+ in if readMore inp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext inp
+ in if (GHC.Classes.==) '=' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ Data.Map.Internal.Tip
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ loop = \_callReturn callInput callCatchStackByLabel ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = v v sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ Data.Map.Internal.Tip
+ in let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '='
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ )
+ inp
+ Data.Map.Internal.Tip
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ loop = \_callReturn callInput callCatchStackByLabel ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = v v sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ Data.Map.Internal.Tip
+ in let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ failInp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) 'v' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'a' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'r' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ inp
+ )
+ cs
+ Data.Map.Internal.Tip
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'r'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'v'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 13
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler callInput Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) 'w' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'h' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'i' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'l' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'e' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ cs
+ Data.Map.Internal.Tip
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'e'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'l'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'i'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'h'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'w'
+ )
)
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 13
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler callInput Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) 'i' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'f' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
)
- inp
+ cs
Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- failInp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 failInp)
- then
- let !(#
- c,
- cs
- #) = readNext failInp
- in if (GHC.Classes.==) '\'' c
- then
- let join = \farInp farExp v (!inp) ->
- let readFail = readFail
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) '\'' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '\''
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'f'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'i'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop callReturn inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '{'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let readFail = Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 4 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) '[' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let readFail = readFail
+ in if readMore failInp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) ']' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ inp
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ']'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ loop = \_callReturn callInput callCatchStackByLabel ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let _ = "jump"
+ in loop callReturn inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '['
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 5
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if Parsers.Nandlang.nandIdentStart c
+ then do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ Data.Map.Internal.Tip
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if Parsers.Nandlang.nandIdentLetter c
+ then do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") cs (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput init Data.Set.Internal.empty
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop callReturn cs (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput init Data.Set.Internal.empty
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ callInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ failInp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ inp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ inp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ failInp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let join = \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ inp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ inp
+ )
+ inp
+ Data.Map.Internal.Tip
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ loop = \_callReturn callInput callCatchStackByLabel ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = v v sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ Data.Map.Internal.Tip
+ in let _ = "jump"
+ in loop callReturn inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ failInp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "choicesBranch.else"
+ in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 failInp)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) '\'' c
+ then
+ let join = \farInp farExp v (!inp) ->
+ let readFail = readFail
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext inp
+ in if (GHC.Classes.==) '\'' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '\''
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ else
let _ = "checkHorizon.else"
in let failExp =
Data.Set.Internal.Bin
farExp
#)
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let join = \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
+ else
+ let _ = "choicesBranch.else"
+ in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let join = \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ callInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) '1' c
then
- let !(#
- c,
- cs
- #) = readNext failInp
- in if (GHC.Classes.==) '1' c
- then
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in '1'
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '1'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in '1'
+ )
+ cs
else
- let _ = "checkHorizon.else"
+ let _ = "checkToken.else"
in let failExp =
Data.Set.Internal.Bin
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.FailureToken '1'
)
)
Data.Set.Internal.Tip
farExp
#)
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) '0' c
then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) '0' c
- then
- let _ = "resume"
- in join
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in '0'
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '0'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in '0'
+ )
+ cs
else
- let _ = "checkHorizon.else"
+ let _ = "checkToken.else"
in let failExp =
Data.Set.Internal.Bin
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.FailureToken '0'
)
)
Data.Set.Internal.Tip
in let (#
farInp,
farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
GHC.Types.LT ->
(#
- inp,
+ callInput,
failExp
#)
GHC.Types.EQ ->
init,
Data.Set.Internal.empty
#)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "jump"
- in name ok failInp Data.Map.Internal.Tip
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v v (v x)
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v v (v x)
- )
- inp
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ callInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let _ = "jump"
+ in name callReturn failInp Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
)
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v v (v x)
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in callReturn
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ inp
)
inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v v (v x)
+ Data.Map.Internal.Tip
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ loop = \_callReturn callInput callCatchStackByLabel ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = v v sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
)
inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v x
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
)
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ callInput
+ Data.Map.Internal.Tip
+ in let _ = "jump"
+ in loop callReturn inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let _ = "resume"
+ in callReturn
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
)
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v x
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ callInput
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let _ = "resume"
+ in callReturn
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
)
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let join = \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v x
+ callInput
+ name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let _ = "resume"
+ in callReturn
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in \x -> \x -> x
+ )
+ callInput
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
)
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show v
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ inp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ inp
+ in let readFail = catchHandler
+ in if readMore inp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext inp
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ )
+ inp
+ Data.Map.Internal.Tip
)
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- failInp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let join = \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) '=' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '='
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- failInp
- failInp
- then
- let _ = "choicesBranch.then"
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- failInp
- Data.Map.Internal.Tip
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- 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 10 failInp)
- then
- let !(#
- c,
- cs
- #) = readNext failInp
- in if (GHC.Classes.==) 'v' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'a' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'r' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- )
- cs
- Data.Map.Internal.Tip
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'r'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'v'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 11
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- 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 10 failInp)
- then
- let !(#
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ loop = \_callReturn callInput callCatchStackByLabel ->
+ let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) 'f' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'u' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'n' c
+ then
+ let readFail = readFail
+ in let !(#
c,
cs
- #) = readNext failInp
- in if (GHC.Classes.==) 'w' c
+ #) = readNext cs
+ in if (GHC.Classes.==) 'c' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if (GHC.Classes.==) 'h' c
+ in if (GHC.Classes.==) 't' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if (GHC.Classes.==) 'l' c
+ in if (GHC.Classes.==) 'o' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if (GHC.Classes.==) 'e' c
+ in if (GHC.Classes.==) 'n' c
then
name
( let _ = "suspend"
name
( let _ = "suspend"
in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let join = \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = sr
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ inp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in v
+ )
+ inp
+ )
+ failInp
+ Data.Map.Internal.Tip
+ else
+ let _ = "choicesBranch.else"
+ in catchHandler callInput Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let readFail = catchHandler
+ in if readMore inp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext inp
+ in if (GHC.Classes.==) ':' c
+ then
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ inp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ cs
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ':'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ )
+ inp
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
)
inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
)
inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
)
cs
Data.Map.Internal.Tip
1
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'e'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'n'
)
)
Data.Set.Internal.Tip
1
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'l'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'o'
)
)
Data.Set.Internal.Tip
1
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'h'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 't'
)
)
Data.Set.Internal.Tip
1
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'w'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
)
)
Data.Set.Internal.Tip
in let (#
farInp,
farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
GHC.Types.LT ->
(#
- failInp,
+ cs,
failExp
#)
GHC.Types.EQ ->
farInp,
farExp
#)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 11
- )
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'n'
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'i' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'f' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
)
- cs
- Data.Map.Internal.Tip
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'f'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'i'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if Parsers.Nandlang.nandIdentLetter c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v x
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp init Data.Set.Internal.empty
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) '!' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'u'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'f'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
farExp
- ( let _ = "resume.genCode"
- in \x -> v x
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken '!'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 17 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'f' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'u' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'n' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'c' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 't' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'i' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'o' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'n' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let join = \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> v x
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- )
- failInp
- Data.Map.Internal.Tip
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) ':' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken ':'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- cs
- Data.Map.Internal.Tip
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'n'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'o'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'i'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 't'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'n'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'u'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 13
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
farInp,
farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'f'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 18
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "resume"
- in ok
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "resume"
- in ok
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "resume"
- in ok
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in \x -> \x -> x
- )
- inp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show v
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- Data.Map.Internal.Tip
- )
- inp
- Data.Map.Internal.Tip
- )
- init
- Data.Map.Internal.Tip
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop finalRet inp Data.Map.Internal.Tip
+ )
+ init
+ Data.Map.Internal.Tip
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let
- in let join = \farInp farExp v (!inp) ->
- let readFail = finalRaise
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'c' c
- then
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show v
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in let join = \farInp farExp v (!inp) ->
+ let readFail = finalRaise
+ in if readMore inp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext inp
+ in if (GHC.Classes.==) 'c' c
+ then
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show v
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- init
- failInp
- then
- let _ = "choicesBranch.then"
- in let readFail = finalRaise
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
- then
- let !(#
- c,
- cs
- #) = readNext failInp
- in if (GHC.Classes.==) 'b' c
- then
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in 'b'
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ init
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = finalRaise
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) 'b' c
+ then
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in 'b'
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
- then
- let !(# c, cs #) = readNext init
- in if (GHC.Classes.==) 'a' c
- then
- let _ = "resume"
- in join
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in 'a'
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
+ then
+ let !(# c, cs #) = readNext init
+ in if (GHC.Classes.==) 'a' c
+ then
+ let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in 'a'
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let
- in let join = \farInp farExp v (!inp) ->
- let readFail = finalRaise
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'd' c
- then
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show v
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'd'
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in let join = \farInp farExp v (!inp) ->
+ let readFail = finalRaise
+ in if readMore inp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext inp
+ in if (GHC.Classes.==) 'd' c
+ then
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show v
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'd'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- init
- failInp
- then
- let _ = "choicesBranch.then"
- in let readFail = finalRaise
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
- then
- let !(#
- c,
- cs
- #) = readNext failInp
- in if (GHC.Classes.==) 'c' c
- then
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in 'c'
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in v
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- init
- failInp
- then
- let _ = "choicesBranch.then"
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
+ GHC.Types.LT ->
+ (#
+ inp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ init
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ failInp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = finalRaise
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) 'c' c
+ then
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in 'c'
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
in let readFail = catchHandler
in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
then
farExp
#)
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
+ then
+ let !(# c, cs #) = readNext init
+ in if (GHC.Classes.==) 'a' c
then
- let !(# c, cs #) = readNext init
- in if (GHC.Classes.==) 'a' c
- then
- let _ = "resume"
- in join
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in 'a'
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in 'a'
+ )
+ cs
else
- let _ = "checkHorizon.else"
+ let _ = "checkToken.else"
in let failExp =
Data.Set.Internal.Bin
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.FailureToken 'a'
)
)
Data.Set.Internal.Tip
Data.Set.Internal.empty
#)
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 init)
- then
- let !(# c, cs #) = readNext init
- in if (GHC.Classes.==) 'a' c
- then
- let readFail = readFail
- in let !(# c, cs #) = readNext cs
- in if (GHC.Classes.==) 'b' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'c' c
- then
- let _ = "resume"
- in finalRet
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in GHC.Show.show ((GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' GHC.Types . [])))
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 init)
+ then
+ let !(# c, cs #) = readNext init
+ in if (GHC.Classes.==) 'a' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'b' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'c' c
+ then
+ let _ = "resume"
+ in finalRet
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in GHC.Show.show ((GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' GHC.Types . [])))
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
_
i
_
_
) -> i GHC.Classes.== j
)
- inp
+ loopInput
failInp
then
let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show (sr GHC.Types . [])
+ )
+ failInp
else
let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'a' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> (GHC.Types.:) 'a' (v x)
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show (v GHC.Types . [])
- )
- inp
- )
- init
- Data.Map.Internal.Tip
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) 'a' c
+ then do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = \x -> sr ((GHC.Types.:) 'a' x)
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") cs (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop finalRet init Data.Map.Internal.Tip
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'a' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'b' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'c' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'd' c
- then
- let _ = "resume"
- in ok
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types . [])))
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'd'
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) 'a' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'b' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'c' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'd' c
+ then
+ let _ = "resume"
+ in callReturn
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types . [])))
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'd'
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
farExp
- ( let _ = "resume.genCode"
- in \x -> (GHC.Types.:) v (v x)
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show ((GHC.Types.:) v (v GHC.Types . []))
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show ((GHC.Types.:) v (sr GHC.Types . []))
+ )
+ failInp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ loop = \_callReturn callInput callCatchStackByLabel ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = \x -> sr ((GHC.Types.:) v x)
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
)
- inp
- )
- inp
- Data.Map.Internal.Tip
- )
- init
- Data.Map.Internal.Tip
+ callInput
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let _ = "jump"
+ in loop finalRet inp Data.Map.Internal.Tip
+ )
+ init
+ Data.Map.Internal.Tip
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 inp)
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'a' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'b' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'c' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'd' c
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let name = \(!callReturn) (!callInput) (!callCatchStackByLabel) ->
+ let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure callCatchStackByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 3 callInput)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) 'a' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'b' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'c' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'd' c
+ then
+ let _ = "resume"
+ in callReturn
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types . [])))
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'd'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ loopInput
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show ((GHC.Types.:) v (sr GHC.Types . []))
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ failInp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ failInp
+ in let readFail = catchHandler
+ in if readMore failInp
then
- let _ = "resume"
- in ok
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types . [])))
- )
- cs
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
else
- let _ = "checkToken.else"
+ let _ = "checkHorizon.else"
in let failExp =
Data.Set.Internal.Bin
1
( Symantic.Parser.Grammar.Combinators.SomeFailure
( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'd'
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
)
)
Data.Set.Internal.Tip
in let (#
farInp,
farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
GHC.Types.LT ->
(#
- cs,
+ failInp,
failExp
#)
GHC.Types.EQ ->
(#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
+ farInp,
+ failExp GHC.Base.<> farExp
#)
GHC.Types.GT ->
(#
- init,
- Data.Set.Internal.empty
+ farInp,
+ farExp
#)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'c'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 4
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
- else
- let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> (GHC.Types.:) v (v x)
- )
- inp
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- )
- inp
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler Data.Map.Internal.Tip Data.Map.Internal.Tip)
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show ((GHC.Types.:) v (v GHC.Types . []))
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- inp
- Data.Map.Internal.Tip
- )
- init
- Data.Map.Internal.Tip
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ loop = \_callReturn callInput callCatchStackByLabel ->
+ name
+ ( let _ = "suspend"
+ in \farInp farExp v (!inp) -> do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = \x -> sr ((GHC.Types.:) v x)
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") inp (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ )
+ callInput
+ (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (catchHandler callInput) Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ in let _ = "jump"
+ in loop finalRet inp Data.Map.Internal.Tip
+ )
+ init
+ Data.Map.Internal.Tip
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let
- in let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show v
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
)
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- init
- failInp
- then
- let _ = "choicesBranch.then"
- in let readFail = finalRaise
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
- then
- let !(#
- c,
- cs
- #) = readNext failInp
- in if (GHC.Classes.==) 'a' c
- then
- let readFail = finalRaise
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'b' c
- then
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types . [])
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show v
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ init
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let readFail = finalRaise
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) 'a' c
+ then
+ let readFail = finalRaise
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'b' c
+ then
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types . [])
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
- then
- let !(# c, cs #) = readNext init
- in if (GHC.Classes.==) 'a' c
- then
- let readFail = readFail
- in let !(# c, cs #) = readNext cs
- in if (GHC.Classes.==) 'a' c
- then
- let _ = "resume"
- in join
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types . [])
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
+ then
+ let !(# c, cs #) = readNext init
+ in if (GHC.Classes.==) 'a' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'a' c
+ then
+ let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types . [])
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let
- in let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show v
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
)
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- init
- failInp
- then
- let _ = "choicesBranch.then"
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
- then
- let !(#
- c,
- cs
- #) = readNext failInp
- in if (GHC.Classes.==) 'a' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'b' c
- then
- let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types . [])
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show v
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ init
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 failInp)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in if (GHC.Classes.==) 'a' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'b' c
+ then
+ let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types . [])
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'b'
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
- in let readFail = catchHandler
- in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
- then
- let !(# c, cs #) = readNext init
- in if (GHC.Classes.==) 'a' c
- then
- let readFail = readFail
- in let !(#
- c,
- cs
- #) = readNext cs
- in if (GHC.Classes.==) 'a' c
- then
- let _ = "resume"
- in join
- init
- Data.Set.Internal.empty
- ( let _ = "resume.genCode"
- in (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types . [])
- )
- cs
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ in let readFail = catchHandler
+ in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext init
+ in if (GHC.Classes.==) 'a' c
+ then
+ let readFail = readFail
+ in let !(#
+ c,
+ cs
+ #) = readNext cs
+ in if (GHC.Classes.==) 'a' c
+ then
+ let _ = "resume"
+ in join
+ init
+ Data.Set.Internal.empty
+ ( let _ = "resume.genCode"
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types . [])
+ )
+ cs
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
- GHC.Types.LT ->
- (#
- cs,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init cs of
+ GHC.Types.LT ->
+ (#
+ cs,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure cs farInp farExp
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'a'
+ )
)
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 2
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let name = \(!ok) (!inp) (!koByLabel) ->
- let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
+ )
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in do
+ let dupv = \x -> x
+ reg <- GHC.STRef.newSTRef dupv
+ let _ = "iter"
+ in let catchHandler loopInput (!_exn) (!failInp) (!farInp) (!farExp) =
+ if ( \( Data.Text.Internal.Text
_
i
_
_
) -> i GHC.Classes.== j
)
- inp
+ loopInput
failInp
then
let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> x
- )
- failInp
+ in do
+ sr <- GHC.STRef.readSTRef reg
+ let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show (sr GHC.Types . [])
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ failInp
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in let _ = "resume"
+ in join
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ failInp
+ in let readFail = catchHandler
+ in if readMore failInp
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext failInp
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
else
let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in if (GHC.Classes.==) 'r' c
- then
- name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let _ = "resume"
- in ok
- farInp
- farExp
- ( let _ = "resume.genCode"
- in \x -> (GHC.Types.:) 'r' (v x)
- )
- inp
- )
- cs
- (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'r'
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- in name
- ( let _ = "suspend"
- in \farInp farExp v (!inp) ->
- let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show (v GHC.Types . [])
- )
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- inp
- failInp
- then
- let _ = "choicesBranch.then"
- in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
+ 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)
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext callInput
+ in if (GHC.Classes.==) 'r' c
+ then do
+ sr <- GHC.STRef.readSTRef reg
+ do
+ let dupv = \x -> sr ((GHC.Types.:) 'r' x)
+ GHC.STRef.writeSTRef reg dupv
+ let _ = "jump"
+ in loop (GHC.Err.error "invalid return") cs (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail Data.Map.Internal.Tip Data.Map.Internal.Tip)
+ else
+ let _ = "checkToken.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureToken 'r'
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
in let (#
farInp,
farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
GHC.Types.LT ->
(#
- failInp,
+ callInput,
failExp
#)
GHC.Types.EQ ->
(#
- farInp,
- failExp GHC.Base.<> farExp
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
#)
GHC.Types.GT ->
(#
- farInp,
- farExp
+ init,
+ Data.Set.Internal.empty
#)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- inp
- in let readFail = catchHandler
- in if readMore inp
- then
- let !(#
- c,
- cs
- #) = readNext inp
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
- )
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp inp of
- GHC.Types.LT ->
- (#
- inp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
- )
- init
- Data.Map.Internal.Tip
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 3
+ )
+ )
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init callInput of
+ GHC.Types.LT ->
+ (#
+ callInput,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure callInput farInp farExp
+ in let _ = "jump"
+ in loop finalRet init Data.Map.Internal.Tip
+ )
unconsumed
) = unconsumed GHC.Classes.> 0
in (# input, more, next #)
- finalRet = \_farInp _farExp v _inp -> Data.Either.Right v
+ finalRet = \_farInp _farExp v _inp -> Symantic.Parser.Machine.Generate.returnST GHC.Base.$ Data.Either.Right v
finalRaise ::
- forall b.
+ forall st b.
Symantic.Parser.Machine.Generate.Catcher
+ st
inp
b = \(!exn) _failInp (!farInp) (!farExp) ->
- Data.Either.Left
- Symantic.Parser.Machine.Generate.ParsingError
- { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
- if readMore farInp
- then
- GHC.Maybe.Just
- ( let (#
- c,
- _
- #) = readNext farInp
- in c
- )
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
- }
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
- in let
- in let join = \farInp farExp v (!inp) ->
- let _ = "resume"
- in finalRet
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Show.show v
+ Symantic.Parser.Machine.Generate.returnST GHC.Base.$
+ Data.Either.Left
+ Symantic.Parser.Machine.Generate.ParsingError
+ { Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp,
+ Symantic.Parser.Machine.Generate.parsingErrorException = exn,
+ Symantic.Parser.Machine.Generate.parsingErrorUnexpected =
+ if readMore farInp
+ then
+ GHC.Maybe.Just
+ ( let (#
+ c,
+ _
+ #) = readNext farInp
+ in c
)
- inp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in if ( \( Data.Text.Internal.Text
- _
- i
- _
- )
- ( Data.Text.Internal.Text
- _
- j
- _
- ) -> i GHC.Classes.== j
- )
- init
- failInp
- then
- let _ = "choicesBranch.then"
- in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (#
- farInp,
+ else GHC.Maybe.Nothing,
+ Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp
+ }
+ in GHC.ST.runST
+ ( let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp)
+ in let
+ in let join = \farInp farExp v (!inp) ->
+ let _ = "resume"
+ in finalRet
+ farInp
+ farExp
+ ( let _ = "resume.genCode"
+ in GHC.Show.show v
+ )
+ inp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in if ( \( Data.Text.Internal.Text
+ _
+ i
+ _
+ )
+ ( Data.Text.Internal.Text
+ _
+ j
+ _
+ ) -> i GHC.Classes.== j
+ )
+ init
+ failInp
+ then
+ let _ = "choicesBranch.then"
+ in let failExp = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure Symantic.Parser.Grammar.Combinators.FailureEnd) Data.Set.Internal.Tip Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
+ GHC.Types.LT ->
+ (#
+ failInp,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ farInp,
+ failExp GHC.Base.<> farExp
+ #)
+ GHC.Types.GT ->
+ (#
+ farInp,
+ farExp
+ #)
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ else
+ let _ = "choicesBranch.else"
+ in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
+ in let _ = "catch ExceptionFailure"
+ in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
+ let _ = "catch.ko ExceptionFailure"
+ in let _ = "resume"
+ in join
+ farInp
farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) farInp failInp of
- GHC.Types.LT ->
- (#
- failInp,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- farInp,
- failExp GHC.Base.<> farExp
- #)
- GHC.Types.GT ->
- (#
- farInp,
- farExp
- #)
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- else
- let _ = "choicesBranch.else"
- in finalRaise Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp farInp farExp
- in let _ = "catch ExceptionFailure"
- in let catchHandler (!_exn) (!failInp) (!farInp) (!farExp) =
- let _ = "catch.ko ExceptionFailure"
- in let _ = "resume"
- in join
- farInp
- farExp
- ( let _ = "resume.genCode"
- in GHC.Tuple . ()
- )
- init
- in let readFail = catchHandler
- in if readMore init
- then
- let !(# c, cs #) = readNext init
- in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure init init Data.Set.Internal.empty
- else
- let _ = "checkHorizon.else"
- in let failExp =
- Data.Set.Internal.Bin
- 1
- ( Symantic.Parser.Grammar.Combinators.SomeFailure
- ( case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ ( let _ = "resume.genCode"
+ in GHC.Tuple . ()
+ )
+ init
+ in let readFail = catchHandler
+ in if readMore init
+ then
+ let !(#
+ c,
+ cs
+ #) = readNext init
+ in catchHandler Symantic.Parser.Grammar.Combinators.ExceptionFailure init init Data.Set.Internal.empty
+ else
+ let _ = "checkHorizon.else"
+ in let failExp =
+ Data.Set.Internal.Bin
+ 1
+ ( Symantic.Parser.Grammar.Combinators.SomeFailure
+ ( case inputToken of
+ (Data.Proxy.Proxy :: Data.Proxy.Proxy tok') -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok' 1
+ )
)
- )
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip
- in let (#
- farInp,
- farExp
- #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
- GHC.Types.LT ->
- (#
- init,
- failExp
- #)
- GHC.Types.EQ ->
- (#
- init,
- failExp GHC.Base.<> Data.Set.Internal.empty
- #)
- GHC.Types.GT ->
- (#
- init,
- Data.Set.Internal.empty
- #)
- in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ Data.Set.Internal.Tip
+ Data.Set.Internal.Tip
+ in let (#
+ farInp,
+ farExp
+ #) = case (GHC.Classes.compare `Data.Function.on` Symantic.Parser.Machine.Input.offset) init init of
+ GHC.Types.LT ->
+ (#
+ init,
+ failExp
+ #)
+ GHC.Types.EQ ->
+ (#
+ init,
+ failExp GHC.Base.<> Data.Set.Internal.empty
+ #)
+ GHC.Types.GT ->
+ (#
+ init,
+ Data.Set.Internal.empty
+ #)
+ in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure init farInp farExp
+ )
-- except when GHC or executable flags change, like profiling
-- or even --accept unfortunately,
-- in those case the golden tests may fail
--- due to a different numbering of the 'shareable' and 'ref' combinators.
+-- due to a different numbering of the 'ref' combinators.
-- Hence 'ShowLetName' is used with 'False' there.
resetTHNameCounter :: IO ()
resetTHNameCounter = IORef.writeIORef TH.counter 0
{-# OPTIONS_GHC -Wno-missing-signatures #-}
module Grammar where
import Data.Char (Char)
+import Data.Function (($))
import Data.String (String)
import Text.Show (Show(..))
import qualified Data.Functor as Functor
import qualified Parsers.Nandlang
import qualified Parsers.Brainfuck.SymanticParser.Grammar
+import qualified Language.Haskell.TH.Syntax as TH
import Symantic.Parser
-rawGrammars :: Grammarable Char repr => [repr String]
+rawGrammars :: Grammarable Char repr => [ObserveSharing TH.Name repr String]
rawGrammars =
[ production show [||show||] <$> g1
, production show [||show||] <$> g2
, production show [||show||] <$> g14
, production show [||show||] <$> g15
, production show [||show||] <$> g16
+ , production show [||show||] <$> g17
]
grammars :: Grammarable Char repr => [repr String]
-grammars = observeSharing Functor.<$> rawGrammars
+grammars = (Functor.<$> rawGrammars) $ \g ->
+ observeSharing g
g1 = char 'a'
g2 = string "abc"
g14 = Parsers.Nandlang.grammar
g15 = (char 'a' <|> char 'b') <* char 'c'
g16 = (char 'a' <|> char 'b' <|> char 'c') <* char 'd'
+g17 ::
+ CombApplicable repr =>
+ CombSatisfiable Char repr =>
+ CombRegisterableUnscoped repr =>
+ Referenceable TH.Name repr =>
+ ObserveSharing TH.Name repr (Char, Char)
+g17 = bind (item @Char) (\pc -> production (,) [||(,)||] <$> pc <*> pc)