--ghc-options "$(addprefix -opti,+RTS $(RTS_OPTIONS))"
.PHONY: tests
-tests:
+t tests:
cabal test $(CABAL_TEST_FLAGS) \
--test-show-details always --test-options "$(TEST_OPTIONS)"
tests/prof-time: $(project)-test.eventlog.json
--ghc-options "$(addprefix -opti,+RTS $(RTS_OPTIONS))"
tests/repl:
cabal repl --enable-tests $(project)-test
+tests/ghcid:
+ ghcid -c 'cabal repl $(project):tests --test-options "$(TEST_OPTIONS)"' --reverse-errors
%/accept: TEST_OPTIONS += --accept
%/accept: %
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}
--- for Symantic.Parser's TemplateHaskell
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE UnboxedTuples #-}
-{-# OPTIONS_GHC -Wno-unused-matches #-}
-{-# OPTIONS_GHC -Wno-unused-local-binds #-}
module Brainfuck where
--import qualified Data.Text.Lazy as TL
import qualified Symantic.Parser as SP
import qualified Parsers.Brainfuck.Attoparsec as AP.Brainfuck
import qualified Parsers.Brainfuck.Handrolled as HR.Brainfuck
-import qualified Parsers.Brainfuck.SymanticParser.Grammar as SP.Brainfuck
-import qualified Parsers.Brainfuck.SymanticParser.AutoSplice as SP.Brainfuck.AutoSplice
-import qualified Parsers.Brainfuck.SymanticParser.DumpSplice as SP.Brainfuck.DumpSplice
-import qualified Parsers.Brainfuck.SymanticParser.PprSplice as SP.Brainfuck.PprSplice
+import qualified Parsers.Brainfuck.SymanticParser as SP.Brainfuck
import Paths_symantic_parser
inputPath inputName = getDataFileName ("parsers/Parsers/Brainfuck/inputs/"<>inputName<>".bf")
[ env (Text.readFile =<< inputPath inputName) $ \inp ->
bgroup inputName
[ bench "SymanticParser" $
- nf $$(SP.runParser @Text SP.Brainfuck.grammar) inp
+ nf SP.Brainfuck.parserText inp
, bench "Attoparsec" $
nf (AP.Text.parse AP.Brainfuck.parser) inp
, bench "Handrolled" $
[ env (IO.readFile =<< inputPath inputName) $ \inp ->
bgroup inputName
[ bench "SymanticParser" $
- nf $$(SP.runParser @String SP.Brainfuck.grammar) inp
+ nf SP.Brainfuck.parserString inp
]
]
, bgroup "ByteString"
[ env (BS.readFile =<< inputPath inputName) $ \inp ->
bgroup inputName
- [ bench "SymanticParser.PprSplice" $
- nf SP.Brainfuck.PprSplice.parserByteString inp
- , bench "SymanticParser.DumpSplice" $
- nf SP.Brainfuck.DumpSplice.parserByteString inp
- , bench "SymanticParser.AutoSplice" $
- nf SP.Brainfuck.AutoSplice.parserByteString inp
- , bench "SymanticParser" $
- nf $$(SP.runParser @BS.ByteString SP.Brainfuck.grammar) inp
+ [ bench "SymanticParser" $
+ nf SP.Brainfuck.parserByteString inp
, bench "Attoparsec" $
nf (AP.ByteString.parse AP.Brainfuck.parser) inp
, bench "Handrolled" $
[ env (BSL.readFile =<< inputPath inputName) $ \inp ->
bgroup inputName
[ bench "SymanticParser" $
- nf $$(SP.runParser @BSL.ByteString SP.Brainfuck.grammar) inp
+ nf SP.Brainfuck.parserByteStringLazy inp
]
]
]
, benchBrainfuck "compiler"
, benchBrainfuck "hanoi"
]
-
-init =
- SP.Brainfuck.PprSplice.dumpSplice
import qualified Brainfuck
main :: IO ()
-main = do
- Brainfuck.init
- defaultMain $
- [ Brainfuck.benchmark
- ]
+main = defaultMain
+ [ Brainfuck.benchmark
+ ]
eventlog2html = doJailbreak (unmarkBroken hsuper.eventlog2html);
trie-simple = doJailbreak (unmarkBroken hsuper.trie-simple);
symantic-parser = doBenchmark (buildFromSdist (hself.callCabal2nix "symantic-parser" ./. {}));
+ hlint = hsuper.hlint_3_3_1.overrideScope (self: super: {
+ ghc-lib-parser = overrideCabal self.ghc-lib-parser_9_0_1_20210324 {
+ doHaddock = false;
+ };
+ ghc-lib-parser-ex = self.ghc-lib-parser-ex_9_0_0_4;
+ });
}
);
in hs.symantic-parser // {
hs.ghcid
#hs.threadscope
#hs.ghc-events-analyze
+ hs.hlint
#hs.haskell-language-server
#hs.hpc
];
"nodes": {
"flake-utils": {
"locked": {
- "lastModified": 1619345332,
- "narHash": "sha256-qHnQkEp1uklKTpx3MvKtY6xzgcqXDsz5nLilbbuL+3A=",
+ "lastModified": 1623875721,
+ "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=",
"owner": "numtide",
"repo": "flake-utils",
- "rev": "2ebf2558e5bf978c7fb8ea927dfaed8fefab2e28",
+ "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772",
"type": "github"
},
"original": {
},
"nixpkgs": {
"locked": {
- "narHash": "sha256-yQc43UuOdsXUPgYAwEONCfq7JxK9c7uacl91TXkQ8cc=",
- "path": "/nix/store/2fq9al19cn3v4hn35i9l2lhhbg7bvgim-nixpkgs-patched",
+ "narHash": "sha256-3C35/g5bJ3KH67fOpxTkqDpfJ1CHYrO2bbl+fPgqfMQ=",
+ "path": "/nix/store/6g7dgkinzm4rvwmpfp9avklsb4hiqals-nixpkgs-patched",
"type": "path"
},
"original": {
+++ /dev/null
-{-# LANGUAGE AllowAmbiguousTypes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE TypeApplications #-}
-{-# LANGUAGE ViewPatterns #-}
--- for Symantic.Parser's TemplateHaskell
-{-# LANGUAGE MagicHash #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE UnboxedTuples #-}
-{-# OPTIONS_GHC -Wno-unused-matches #-}
-{-# OPTIONS_GHC -Wno-unused-local-binds #-}
-module Parsers.Brainfuck.SymanticParser.AutoSplice where
-
-import Data.Either (Either)
-import qualified Data.ByteString as BS
-import qualified Symantic.Parser as SP
-import qualified GHC.Word
-
-import Parsers.Brainfuck.SymanticParser.Grammar (grammar, reproGrammar)
-import Parsers.Brainfuck.Types (Instruction)
-
-parserByteString :: BS.ByteString -> Either (SP.ParsingError BS.ByteString) [Instruction]
-parserByteString = $$(SP.runParser @BS.ByteString grammar)
-
-{-
-parserByteStringRepro :: BS.ByteString -> Either (SP.ParsingError BS.ByteString) [GHC.Word.Word8]
-parserByteStringRepro = $$(SP.runParser @BS.ByteString reproGrammar)
--}
+++ /dev/null
-{-# LANGUAGE AllowAmbiguousTypes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE TypeApplications #-}
-{-# LANGUAGE ViewPatterns #-}
--- for Symantic.Parser's TemplateHaskell
-{-# LANGUAGE MagicHash #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE UnboxedTuples #-}
-{-# OPTIONS_GHC -Wno-unused-matches #-}
-{-# OPTIONS_GHC -Wno-unused-local-binds #-}
-module Parsers.Brainfuck.SymanticParser.DumpSplice where
-
-import qualified Data.ByteString as BS
-import qualified Data.ByteString.Internal
-import qualified Data.Either
-import qualified Data.Function
-import qualified Data.Map.Internal
-import qualified Data.Map.Strict.Internal
-import qualified Data.Proxy
-import qualified Data.Set.Internal
-import qualified Data.Text.Internal
-import qualified Data.Text.Unsafe
-import qualified GHC.Base
-import qualified GHC.Classes
-import qualified GHC.ForeignPtr
-import qualified GHC.Maybe
-import qualified GHC.Num
-import qualified GHC.Prim
-import qualified GHC.Show
-import qualified GHC.Tuple
-import qualified GHC.Types
-import qualified GHC.Word
-import qualified Language.Haskell.TH as TH
-import qualified Language.Haskell.TH.Syntax as TH
-import qualified Prelude
-import qualified Symantic.Parser as SP
-import qualified Symantic.Parser.Grammar.Combinators
-import qualified Symantic.Univariant.Lang
-import qualified Symantic.Parser.Machine
-import qualified Symantic.Parser.Machine.Generate
-import qualified Symantic.Parser.Machine.Input
-import qualified System.IO as IO
-import Data.Either (Either)
-
-import qualified Parsers.Brainfuck.Types
-import Parsers.Brainfuck.Types (Instruction)
-
--- The splice below has been manually paste with:
--- :r dist-newstyle/build/x86_64-linux/ghc-9.0.1/symantic-parser-*/l/parsers/build/parsers/parsers/Parsers/Brainfuck/SymanticParser/AutoSplice.dump-splices
--- :%s/\%x00//g
--- :%s/#\(_[0-9]\+\)/\1#/g
-parserByteString :: BS.ByteString -> Either (SP.ParsingError BS.ByteString) [Instruction]
-parserByteString =
- \ (input_ama8 :: inp_a1S5K)
- -> let
- !(# init_amaa, readMore_amab, readNext_amac #)
- = let
- !(Data.ByteString.Internal.PS (GHC.ForeignPtr.ForeignPtr addr_amae#
- final_amaf)
- off_amag size_amah)
- = input_ama8
- next_amai i_amaj@(GHC.Types.I# i_amak#)
- = case
- GHC.Prim.readWord8OffAddr#
- (addr_amae# `GHC.Prim.plusAddr#` i_amak#)
- 0#
- GHC.Prim.realWorld#
- of {
- (# s'_amal, x_amam #)
- -> case GHC.Prim.touch# final_amaf s'_amal of {
- _ -> (# GHC.Word.W8# x_amam, (i_amaj GHC.Num.+ 1) #) } }
- in (# off_amag, (GHC.Classes.< size_amah), next_amai #)
- finalRet_ama9
- = \ _farInp_aman _farExp_amao v_amap _inp_amaq
- -> Data.Either.Right v_amap
- finalRaise_amad :: forall b_amar. SP.Catcher inp_a1S5K b_amar
- = \ !exn_amas _failInp_amat !farInp_amau !farExp_amav
- -> Data.Either.Left
- SP.ParsingErrorStandard
- {SP.parsingErrorOffset = SP.offset farInp_amau,
- SP.parsingErrorException = exn_amas,
- SP.parsingErrorUnexpected = if readMore_amab farInp_amau then
- GHC.Maybe.Just
- (let
- (# c_amaw, _ #)
- = readNext_amac farInp_amau
- in c_amaw)
- else
- GHC.Maybe.Nothing,
- SP.parsingErrorExpecting = farExp_amav} in
- let
- inputToken
- = Data.Proxy.Proxy :: Data.Proxy.Proxy (SP.InputToken inp_a1S5K) in
- let
- name_1
- = \ !ok_amcU !inp_amcV !koByLabel_amcW
- -> name_4
- (let _ = "suspend"
- in
- \ farInp_amcX farExp_amcY v_amcZ !inp_amd0
- -> let _ = "resume"
- in
- ok_amcU farInp_amcX farExp_amcY
- (let _ = "resume.genCode" in ())
- inp_amd0)
- inp_amcV
- (Data.Map.Internal.Bin 1 SP.ExceptionFailure
- (Data.Map.Strict.Internal.findWithDefault finalRaise_amad
- SP.ExceptionFailure
- koByLabel_amcW)
- Data.Map.Internal.Tip
- Data.Map.Internal.Tip)
- name_2
- = \ !ok_amcN !inp_amcO !koByLabel_amcP
- -> name_3
- (let _ = "suspend"
- in
- \ farInp_amcQ farExp_amcR v_amcS !inp_amcT
- -> let _ = "resume"
- in
- ok_amcN farInp_amcQ farExp_amcR
- (let _ = "resume.genCode" in v_amcS [])
- inp_amcT)
- inp_amcO
- (Data.Map.Internal.Bin 1 SP.ExceptionFailure
- (Data.Map.Strict.Internal.findWithDefault finalRaise_amad
- SP.ExceptionFailure
- koByLabel_amcP)
- Data.Map.Internal.Tip
- Data.Map.Internal.Tip)
- name_3
- = \ !ok_amaS !inp_amaT !koByLabel_amaU
- -> let _ = "catch ExceptionFailure" in
- let
- catchHandler_amaV
- !_exn_amaW
- !failInp_amaX
- !farInp_amaY
- !farExp_amaZ
- = let _ = "catch.ko ExceptionFailure"
- in
- if (GHC.Classes.==) @GHC.Types.Int inp_amaT failInp_amaX then
- let _ = "choicesBranch.then" in
- let _ = "resume"
- in
- ok_amaS farInp_amaY farExp_amaZ
- (let _ = "resume.genCode" in \ x_amb0 -> x_amb0)
- failInp_amaX
- else
- let _ = "choicesBranch.else"
- in
- Data.Map.Strict.Internal.findWithDefault finalRaise_amad
- SP.ExceptionFailure
- koByLabel_amaU
- SP.ExceptionFailure
- failInp_amaX
- farInp_amaY
- farExp_amaZ in
- let
- join_1s
- = \ farInp_amb1 farExp_amb2 v_amb3 !inp_amb4
- -> name_1
- (let _ = "suspend"
- in
- \ farInp_amb5 farExp_amb6 v_amb7 !inp_amb8
- -> (name_3
- (let _ = "suspend"
- in
- \ farInp_amb9 farExp_amba v_ambb !inp_ambc
- -> let _ = "resume"
- in
- ok_amaS farInp_amb9 farExp_amba
- (let _ = "resume.genCode"
- in
- \ x_ambd
- -> (v_amb3 : v_ambb x_ambd))
- inp_ambc)
- inp_amb8)
- (Data.Map.Internal.Bin 1 SP.ExceptionFailure
- catchHandler_amaV
- Data.Map.Internal.Tip
- Data.Map.Internal.Tip))
- inp_amb4
- (Data.Map.Internal.Bin 1 SP.ExceptionFailure
- catchHandler_amaV
- Data.Map.Internal.Tip
- Data.Map.Internal.Tip) in
- let readFail_ambe = catchHandler_amaV
- in
- if readMore_amab inp_amaT then
- let !(# c_ambf, cs_ambg #) = readNext_amac inp_amaT
- in
- if (\ x_ambh -> GHC.Types.True) c_ambf then
- if (60 GHC.Classes.== c_ambf) then
- let _ = "choicesBranch.then" in
- let readFail_ambi = readFail_ambe
- in
- if readMore_amab inp_amaT then
- let !(# c_ambj, cs_ambk #) = readNext_amac inp_amaT
- in
- if (\ x_ambl -> GHC.Types.True) c_ambj then
- let _ = "resume"
- in
- (((join_1s init_amaa) Data.Set.Internal.empty)
- (let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Backward))
- cs_ambk
- else
- let _ = "checkToken.else" in
- let
- failExp_ambm
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureAny @tok'_aLiK }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_ambn, farExp_ambo #)
- = case
- ((GHC.Classes.compare @GHC.Types.Int)
- init_amaa)
- inp_amaT
- of
- GHC.Types.LT -> (# inp_amaT, failExp_ambm #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_ambm
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_ambi SP.ExceptionFailure inp_amaT
- farInp_ambn
- farExp_ambo
- else
- let _ = "checkHorizon.else" in
- let
- failExp_ambp
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon @tok'_aLiK 1 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_ambq, farExp_ambr #)
- = case
- ((GHC.Classes.compare @GHC.Types.Int) init_amaa)
- inp_amaT
- of
- GHC.Types.LT -> (# inp_amaT, failExp_ambp #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_ambp
- GHC.Base.<> Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa, Data.Set.Internal.empty #)
- in
- readFail_ambi SP.ExceptionFailure inp_amaT
- farInp_ambq
- farExp_ambr
- else
- let _ = "choicesBranch.else"
- in
- if (62 GHC.Classes.== c_ambf) then
- let _ = "choicesBranch.then" in
- let readFail_ambs = readFail_ambe
- in
- if readMore_amab inp_amaT then
- let !(# c_ambt, cs_ambu #) = readNext_amac inp_amaT
- in
- if (\ x_ambv -> GHC.Types.True) c_ambt then
- let _ = "resume"
- in
- join_1s init_amaa
- Data.Set.Internal.empty
- (let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Forward)
- cs_ambu
- else
- let _ = "checkToken.else" in
- let
- failExp_ambw
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureAny
- @tok'_aLiK }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_ambx, farExp_amby #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT, failExp_ambw #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_ambw
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- (((readFail_ambs SP.ExceptionFailure)
- inp_amaT)
- farInp_ambx)
- farExp_amby
- else
- let _ = "checkHorizon.else" in
- let
- failExp_ambz
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon @tok'_aLiK
- 1 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_ambA, farExp_ambB #)
- = case
- GHC.Classes.compare @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT -> (# inp_amaT, failExp_ambz #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_ambz
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_ambs SP.ExceptionFailure inp_amaT
- farInp_ambA
- farExp_ambB
- else
- let _ = "choicesBranch.else"
- in
- if (43 GHC.Classes.== c_ambf) then
- let _ = "choicesBranch.then" in
- let readFail_ambC = readFail_ambe
- in
- if readMore_amab inp_amaT then
- let
- !(# c_ambD, cs_ambE #)
- = readNext_amac inp_amaT
- in
- if (\ x_ambF -> GHC.Types.True) c_ambD then
- let _ = "resume"
- in
- join_1s init_amaa
- Data.Set.Internal.empty
- (let _ = "resume.genCode"
- in
- Parsers.Brainfuck.Types.Increment)
- cs_ambE
- else
- let _ = "checkToken.else" in
- let
- failExp_ambG
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureAny
- @tok'_aLiK }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_ambH, farExp_ambI #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_ambG #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_ambG
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_ambC SP.ExceptionFailure
- inp_amaT
- farInp_ambH
- farExp_ambI
- else
- let _ = "checkHorizon.else" in
- let
- failExp_ambJ
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon
- @tok'_aLiK
- 1 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_ambK, farExp_ambL #)
- = case
- ((GHC.Classes.compare
- @GHC.Types.Int)
- init_amaa)
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT, failExp_ambJ #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_ambJ
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_ambC SP.ExceptionFailure
- inp_amaT
- farInp_ambK
- farExp_ambL
- else
- let _ = "choicesBranch.else"
- in
- if (45 GHC.Classes.== c_ambf) then
- let _ = "choicesBranch.then" in
- let readFail_ambM = readFail_ambe
- in
- if readMore_amab inp_amaT then
- let
- !(# c_ambN, cs_ambO #)
- = readNext_amac inp_amaT
- in
- if (\ x_ambP -> GHC.Types.True)
- c_ambN then
- let _ = "resume"
- in
- join_1s init_amaa
- Data.Set.Internal.empty
- (let _ = "resume.genCode"
- in
- Parsers.Brainfuck.Types.Decrement)
- cs_ambO
- else
- let _ = "checkToken.else" in
- let
- failExp_ambQ
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureAny
- @tok'_aLiK }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_ambR, farExp_ambS #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_ambQ #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_ambQ
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_ambM
- SP.ExceptionFailure
- inp_amaT
- farInp_ambR
- farExp_ambS
- else
- let _ = "checkHorizon.else" in
- let
- failExp_ambT
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon
- @tok'_aLiK
- 1 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_ambU, farExp_ambV #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_ambT #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_ambT
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_ambM SP.ExceptionFailure
- inp_amaT
- farInp_ambU
- farExp_ambV
- else
- let _ = "choicesBranch.else"
- in
- if (44 GHC.Classes.== c_ambf) then
- let _ = "choicesBranch.then" in
- let readFail_ambW = readFail_ambe
- in
- if readMore_amab inp_amaT then
- let
- !(# c_ambX, cs_ambY #)
- = readNext_amac inp_amaT
- in
- if (\ x_ambZ -> GHC.Types.True)
- c_ambX then
- let _ = "resume"
- in
- join_1s init_amaa
- Data.Set.Internal.empty
- (let
- _ = "resume.genCode"
- in
- Parsers.Brainfuck.Types.Input)
- cs_ambY
- else
- let _ = "checkToken.else" in
- let
- failExp_amc0
- = Data.Set.Internal.Bin
- 1
- (SP.SomeFailure
- (case
- inputToken
- of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureAny
- @tok'_aLiK }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amc1,
- farExp_amc2 #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_amc0 #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amc0
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_ambW
- SP.ExceptionFailure
- inp_amaT
- farInp_amc1
- farExp_amc2
- else
- let _ = "checkHorizon.else" in
- let
- failExp_amc3
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon
- @tok'_aLiK
- 1 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amc4, farExp_amc5 #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_amc3 #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amc3
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_ambW
- SP.ExceptionFailure
- inp_amaT
- farInp_amc4
- farExp_amc5
- else
- let _ = "choicesBranch.else"
- in
- if (46 GHC.Classes.== c_ambf) then
- let _ = "choicesBranch.then" in
- let readFail_amc6 = readFail_ambe
- in
- if readMore_amab inp_amaT then
- let
- !(# c_amc7, cs_amc8 #)
- = readNext_amac inp_amaT
- in
- if (\ x_amc9
- -> GHC.Types.True)
- c_amc7 then
- let _ = "resume"
- in
- join_1s
- init_amaa
- Data.Set.Internal.empty
- (let
- _ = "resume.genCode"
- in
- Parsers.Brainfuck.Types.Output)
- cs_amc8
- else
- let
- _ = "checkToken.else" in
- let
- failExp_amca
- = Data.Set.Internal.Bin
- 1
- (SP.SomeFailure
- (case
- inputToken
- of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureAny
- @tok'_aLiK }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amcb,
- farExp_amcc #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_amca #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amca
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_amc6
- SP.ExceptionFailure
- inp_amaT
- farInp_amcb
- farExp_amcc
- else
- let
- _ = "checkHorizon.else" in
- let
- failExp_amcd
- = Data.Set.Internal.Bin
- 1
- (SP.SomeFailure
- (case
- inputToken
- of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon
- @tok'_aLiK
- 1 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amce,
- farExp_amcf #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_amcd #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amcd
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_amc6
- SP.ExceptionFailure
- inp_amaT
- farInp_amce
- farExp_amcf
- else
- let _ = "choicesBranch.else"
- in
- if (91
- GHC.Classes.==
- c_ambf) then
- let
- _ = "choicesBranch.then" in
- let
- readFail_amcg
- = readFail_ambe
- in
- if readMore_amab
- ((GHC.Num.+)
- @GHC.Types.Int
- 1
- inp_amaT) then
- let
- !(# c_amch,
- cs_amci #)
- = readNext_amac
- inp_amaT
- in
- if (\ x_amcj
- -> GHC.Types.True)
- c_amch then
- name_1
- (let
- _ = "suspend"
- in
- \ farInp_amck
- farExp_amcl
- v_amcm
- !inp_amcn
- -> name_2
- (let
- _ = "suspend"
- in
- \ farInp_amco
- farExp_amcp
- v_amcq
- !inp_amcr
- -> let
- readFail_amcs
- = readFail_amcg
- in
- if readMore_amab
- inp_amcr then
- let
- !(# c_amct,
- cs_amcu #)
- = readNext_amac
- inp_amcr
- in
- if (93
- GHC.Classes.==)
- c_amct then
- let
- _ = "resume"
- in
- join_1s
- farInp_amco
- farExp_amcp
- (let
- _ = "resume.genCode"
- in
- Parsers.Brainfuck.Types.Loop
- v_amcq)
- cs_amcu
- else
- let
- _ = "checkToken.else"
- in
- readFail_amcs
- SP.ExceptionFailure
- inp_amcr
- farInp_amco
- farExp_amcp
- else
- let
- _ = "checkHorizon.else" in
- let
- failExp_amcv
- = Data.Set.Internal.Bin
- 1
- (SP.SomeFailure
- (case
- inputToken
- of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon
- @tok'_aLiK
- 1 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amcw,
- farExp_amcx #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- farInp_amco
- inp_amcr
- of
- GHC.Types.LT
- -> (# inp_amcr,
- failExp_amcv #)
- GHC.Types.EQ
- -> (# farInp_amco,
- (failExp_amcv
- GHC.Base.<>
- farExp_amcp) #)
- GHC.Types.GT
- -> (# farInp_amco,
- farExp_amcp #)
- in
- readFail_amcs
- SP.ExceptionFailure
- inp_amcr
- farInp_amcw
- farExp_amcx)
- inp_amcn
- (Data.Map.Internal.Bin
- 1
- SP.ExceptionFailure
- readFail_amcg
- Data.Map.Internal.Tip
- Data.Map.Internal.Tip))
- cs_amci
- (Data.Map.Internal.Bin
- 1
- SP.ExceptionFailure
- readFail_amcg
- Data.Map.Internal.Tip
- Data.Map.Internal.Tip)
- else
- let
- _ = "checkToken.else" in
- let
- failExp_amcy
- = Data.Set.Internal.Bin
- 1
- (SP.SomeFailure
- (case
- inputToken
- of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureAny
- @tok'_aLiK }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amcz,
- farExp_amcA #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_amcy #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amcy
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_amcg
- SP.ExceptionFailure
- inp_amaT
- farInp_amcz
- farExp_amcA
- else
- let
- _ = "checkHorizon.else" in
- let
- failExp_amcB
- = Data.Set.Internal.Bin
- 1
- (SP.SomeFailure
- (case
- inputToken
- of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon
- @tok'_aLiK
- 2 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amcC,
- farExp_amcD #)
- = case
- GHC.Classes.compare
- @GHC.Types.Int
- init_amaa
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_amcB #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amcB
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_amcg
- SP.ExceptionFailure
- inp_amaT
- farInp_amcC
- farExp_amcD
- else
- let
- _ = "choicesBranch.else" in
- let
- failExp_amcE
- = Data.Set.Internal.Bin
- 1
- (SP.SomeFailure
- SP.FailureEmpty)
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amcF,
- farExp_amcG #)
- = case
- ((GHC.Classes.compare
- @GHC.Types.Int)
- init_amaa)
- inp_amaT
- of
- GHC.Types.LT
- -> (# inp_amaT,
- failExp_amcE #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amcE
- GHC.Base.<>
- Data.Set.Internal.empty) #)
- GHC.Types.GT
- -> (# init_amaa,
- Data.Set.Internal.empty #)
- in
- readFail_ambe
- SP.ExceptionFailure
- inp_amaT
- farInp_amcF
- farExp_amcG
- else
- let _ = "checkToken.else" in
- let
- failExp_amcH
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureAny @tok'_aLiK }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amcI, farExp_amcJ #)
- = case
- GHC.Classes.compare @GHC.Types.Int init_amaa inp_amaT
- of
- GHC.Types.LT -> (# inp_amaT, failExp_amcH #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amcH
- GHC.Base.<> Data.Set.Internal.empty) #)
- GHC.Types.GT -> (# init_amaa, Data.Set.Internal.empty #)
- in
- readFail_ambe SP.ExceptionFailure inp_amaT farInp_amcI
- farExp_amcJ
- else
- let _ = "checkHorizon.else" in
- let
- failExp_amcK
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon @tok'_aLiK 1 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amcL, farExp_amcM #)
- = case GHC.Classes.compare @GHC.Types.Int init_amaa inp_amaT of
- GHC.Types.LT -> (# inp_amaT, failExp_amcK #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amcK GHC.Base.<> Data.Set.Internal.empty) #)
- GHC.Types.GT -> (# init_amaa, Data.Set.Internal.empty #)
- in
- readFail_ambe SP.ExceptionFailure inp_amaT farInp_amcL
- farExp_amcM
- name_4
- = \ !ok_amax !inp_amay !koByLabel_amaz
- -> let _ = "catch ExceptionFailure" in
- let
- catchHandler_amaA
- !_exn_amaB
- !failInp_amaC
- !farInp_amaD
- !farExp_amaE
- = let _ = "catch.ko ExceptionFailure"
- in
- if (GHC.Classes.==) @GHC.Types.Int inp_amay failInp_amaC then
- let _ = "choicesBranch.then" in
- let _ = "resume"
- in
- ok_amax farInp_amaD farExp_amaE
- (let _ = "resume.genCode" in \ x_amaF -> x_amaF)
- failInp_amaC
- else
- let _ = "choicesBranch.else"
- in
- Data.Map.Strict.Internal.findWithDefault finalRaise_amad
- SP.ExceptionFailure
- koByLabel_amaz
- SP.ExceptionFailure
- failInp_amaC
- farInp_amaD
- farExp_amaE in
- let readFail_amaG = catchHandler_amaA
- in
- if readMore_amab inp_amay then
- let !(# c_amaH, cs_amaI #) = readNext_amac inp_amay
- in
- if (\ c_amaJ
- -> GHC.Classes.not
- ((60 GHC.Classes.== c_amaJ)
- GHC.Classes.||
- ((62 GHC.Classes.== c_amaJ)
- GHC.Classes.||
- ((43 GHC.Classes.== c_amaJ)
- GHC.Classes.||
- ((45 GHC.Classes.== c_amaJ)
- GHC.Classes.||
- ((44 GHC.Classes.== c_amaJ)
- GHC.Classes.||
- ((46 GHC.Classes.== c_amaJ)
- GHC.Classes.||
- ((91 GHC.Classes.== c_amaJ)
- GHC.Classes.||
- ((93
- GHC.Classes.== c_amaJ)
- GHC.Classes.||
- GHC.Types.False)))))))))
- c_amaH then
- name_4
- (let _ = "suspend"
- in
- \ farInp_amaK farExp_amaL v_amaM !inp_amaN
- -> let _ = "resume"
- in
- ok_amax farInp_amaK farExp_amaL
- (let _ = "resume.genCode"
- in \ x_amaO -> v_amaM x_amaO)
- inp_amaN)
- cs_amaI
- (Data.Map.Internal.Bin 1 SP.ExceptionFailure readFail_amaG
- Data.Map.Internal.Tip
- Data.Map.Internal.Tip)
- else
- let _ = "checkToken.else"
- in
- readFail_amaG SP.ExceptionFailure inp_amay init_amaa
- Data.Set.Internal.empty
- else
- let _ = "checkHorizon.else" in
- let
- failExp_amaP
- = Data.Set.Internal.Bin 1
- (SP.SomeFailure
- (case inputToken of {
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_aLiK)
- -> SP.FailureHorizon @tok'_aLiK 1 }))
- Data.Set.Internal.Tip
- Data.Set.Internal.Tip in
- let
- (# farInp_amaQ, farExp_amaR #)
- = case GHC.Classes.compare @GHC.Types.Int init_amaa inp_amay of
- GHC.Types.LT -> (# inp_amay, failExp_amaP #)
- GHC.Types.EQ
- -> (# init_amaa,
- (failExp_amaP GHC.Base.<> Data.Set.Internal.empty) #)
- GHC.Types.GT -> (# init_amaa, Data.Set.Internal.empty #)
- in
- readFail_amaG SP.ExceptionFailure inp_amay farInp_amaQ
- farExp_amaR
- in
- name_1
- (let _ = "suspend"
- in
- \ farInp_amd1 farExp_amd2 v_amd3 !inp_amd4
- -> name_2
- (let _ = "suspend"
- in
- \ farInp_amd5 farExp_amd6 v_amd7 !inp_amd8
- -> let _ = "resume"
- in
- finalRet_ama9 farInp_amd5 farExp_amd6
- (let _ = "resume.genCode" in v_amd7)
- inp_amd8)
- inp_amd4
- Data.Map.Internal.Tip)
- init_amaa
- Data.Map.Internal.Tip
import Data.Function ((.))
import qualified Language.Haskell.TH.Syntax as TH
import qualified Prelude
+import Data.Functor.Product (Product(..))
import Symantic.Univariant.Trans
import qualified Symantic.Parser as SP
+import qualified Symantic.Univariant.Lang as H
import Parsers.Utils
import Parsers.Brainfuck.Types
'.' -> SP.item @tok SP.$> SP.prod Output
'[' -> SP.between (lexeme (SP.item @tok))
(SP.token (coerceEnum @_ @tok ']'))
- (SP.production Loop [||Loop||] SP.<$> bf)
+ ($(SP.prodCon 'Loop) SP.<$> bf)
_ -> Prelude.undefined
reproGrammar :: forall tok repr.
+++ /dev/null
-{-# LANGUAGE AllowAmbiguousTypes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE TypeApplications #-}
-{-# LANGUAGE ViewPatterns #-}
--- for Symantic.Parser's TemplateHaskell
-{-# LANGUAGE MagicHash #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE UnboxedTuples #-}
-{-# OPTIONS_GHC -Wno-unused-matches #-}
-{-# OPTIONS_GHC -Wno-unused-local-binds #-}
-module Parsers.Brainfuck.SymanticParser.PprSplice where
-
-import Data.Either (Either)
-import Data.Text (Text)
-import System.IO (IO)
-import Text.Show (show)
-import qualified Data.ByteString as BS
-import qualified Data.ByteString.Internal
-import qualified Data.Either
-import qualified Data.Function
-import qualified Data.Map.Internal
-import qualified Data.Map.Strict.Internal
-import qualified Data.Proxy
-import qualified Data.Set.Internal
-import qualified Data.Text.Internal
-import qualified Data.Text.Unsafe
-import qualified GHC.Base
-import qualified GHC.Classes
-import qualified GHC.ForeignPtr
-import qualified GHC.Maybe
-import qualified GHC.Num
-import qualified GHC.Prim
-import qualified GHC.Show
-import qualified GHC.Tuple
-import qualified GHC.Types
-import qualified GHC.Word
-import qualified Language.Haskell.TH as TH
-import qualified Language.Haskell.TH.Syntax as TH
-import qualified Prelude
-import qualified Symantic.Parser as SP
-import qualified Symantic.Parser.Grammar.Combinators
-import qualified Symantic.Parser.Machine
-import qualified Symantic.Parser.Machine.Generate
-import qualified Symantic.Parser.Machine.Input
-import qualified System.IO as IO
-
-import qualified Parsers.Brainfuck.Types
-import Parsers.Brainfuck.Types (Instruction)
-import Parsers.Brainfuck.SymanticParser.Grammar (grammar)
-
-splice :: IO (TH.TExp (BS.ByteString -> Either (SP.ParsingError BS.ByteString) [Instruction]))
-splice = TH.runQ (TH.examineCode (SP.runParser grammar))
-
-dumpSplice :: IO ()
-dumpSplice = do
- tExp <- splice
- IO.writeFile "parsers/Parsers/Brainfuck/SymanticParser/PprSplice.hs.ppr"
- (show (TH.ppr ((TH.unType tExp))))
-
--- The splice below has been manually paste with:
--- :r parsers/Parsers/Brainfuck/SymanticParser/PprSplice.hs.ppr
--- :%s/#\(_[0-9]\+\)/\1# /g
--- :%s/GHC.Tuple.()/()/g
--- :%s/GHC.Types.\[]/[]/g
-parserByteString :: BS.ByteString -> Either (SP.ParsingError BS.ByteString) [Instruction]
-parserByteString =
- \(input_0 :: inp_6989586621679446738) -> let {!(# init_1,
- readMore_2,
- readNext_3 #) = let {!(Data.ByteString.Internal.PS (GHC.ForeignPtr.ForeignPtr addr_4#
- final_5)
- off_6
- size_7) = input_0;
- next_8 (i_9@(GHC.Types.I# i_10# )) = case GHC.Prim.readWord8OffAddr# (addr_4# `GHC.Prim.plusAddr#` i_10# ) 0# GHC.Prim.realWorld# of
- (# s'_11,
- x_12 #) -> case GHC.Prim.touch# final_5 s'_11 of
- _ -> (# GHC.Word.W8# x_12,
- i_9 GHC.Num.+ 1 #)}
- in (# off_6,
- (GHC.Classes.< size_7),
- next_8 #);
- finalRet_13 = \_farInp_14 _farExp_15 v_16 _inp_17 -> Data.Either.Right v_16;
- finalRaise_18 :: forall b_19 .
- Symantic.Parser.Machine.Generate.Catcher inp_6989586621679446738
- b_19 = \(!exn_20) _failInp_21 (!farInp_22) (!farExp_23) -> Data.Either.Left Symantic.Parser.Machine.Generate.ParsingErrorStandard{Symantic.Parser.Machine.Generate.parsingErrorOffset = Symantic.Parser.Machine.Input.offset farInp_22,
- Symantic.Parser.Machine.Generate.parsingErrorException = exn_20,
- Symantic.Parser.Machine.Generate.parsingErrorUnexpected = if readMore_2 farInp_22
- then GHC.Maybe.Just (let (# c_24,
- _ #) = readNext_3 farInp_22
- in c_24)
- else GHC.Maybe.Nothing,
- Symantic.Parser.Machine.Generate.parsingErrorExpecting = farExp_23}}
- in let inputToken = Data.Proxy.Proxy :: Data.Proxy.Proxy (Symantic.Parser.Machine.Input.InputToken inp_6989586621679446738)
- in let {name_25 = \(!ok_26) (!inp_27) (!koByLabel_28) -> name_29 (let _ = "suspend"
- in \farInp_30 farExp_31 v_32 (!inp_33) -> let _ = "resume"
- in ok_26 farInp_30 farExp_31 (let _ = "resume.genCode"
- in ()) inp_33) inp_27 (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise_18 Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel_28) Data.Map.Internal.Tip Data.Map.Internal.Tip);
- name_34 = \(!ok_35) (!inp_36) (!koByLabel_37) -> name_38 (let _ = "suspend"
- in \farInp_39 farExp_40 v_41 (!inp_42) -> let _ = "resume"
- in ok_35 farInp_39 farExp_40 (let _ = "resume.genCode"
- in v_41 []) inp_42) inp_36 (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure (Data.Map.Strict.Internal.findWithDefault finalRaise_18 Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel_37) Data.Map.Internal.Tip Data.Map.Internal.Tip);
- name_38 = \(!ok_43) (!inp_44) (!koByLabel_45) -> let _ = "catch ExceptionFailure"
- in let catchHandler_46 (!_exn_47) (!failInp_48) (!farInp_49) (!farExp_50) = let _ = "catch.ko ExceptionFailure"
- in if (GHC.Classes.==) @GHC.Types.Int inp_44 failInp_48
- then let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok_43 farInp_49 farExp_50 (let _ = "resume.genCode"
- in \x_51 -> x_51) failInp_48
- else let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise_18 Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel_45 Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp_48 farInp_49 farExp_50
- in let join_52 = \farInp_53 farExp_54 v_55 (!inp_56) -> name_25 (let _ = "suspend"
- in \farInp_57 farExp_58 v_59 (!inp_60) -> name_38 (let _ = "suspend"
- in \farInp_61 farExp_62 v_63 (!inp_64) -> let _ = "resume"
- in ok_43 farInp_61 farExp_62 (let _ = "resume.genCode"
- in \x_65 -> v_55 : v_63 x_65) inp_64) inp_60 (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler_46 Data.Map.Internal.Tip Data.Map.Internal.Tip)) inp_56 (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure catchHandler_46 Data.Map.Internal.Tip Data.Map.Internal.Tip)
- in let readFail_66 = catchHandler_46
- in if readMore_2 inp_44
- then let !(# c_67,
- cs_68 #) = readNext_3 inp_44
- in if (\x_69 -> GHC.Types.True) c_67
- then if 60 GHC.Classes.== c_67
- then let _ = "choicesBranch.then"
- in let readFail_70 = readFail_66
- in if readMore_2 inp_44
- then let !(# c_71,
- cs_72 #) = readNext_3 inp_44
- in if (\x_73 -> GHC.Types.True) c_71
- then let _ = "resume"
- in join_52 init_1 Data.Set.Internal.empty (let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Backward) cs_72
- else let _ = "checkToken.else"
- in let failExp_74 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureAny @tok'_6989586621679198986)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_75,
- farExp_76 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_74 #)
- GHC.Types.EQ -> (# init_1,
- failExp_74 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_70 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_75 farExp_76
- else let _ = "checkHorizon.else"
- in let failExp_77 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 1)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_78,
- farExp_79 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_77 #)
- GHC.Types.EQ -> (# init_1,
- failExp_77 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_70 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_78 farExp_79
- else let _ = "choicesBranch.else"
- in if 62 GHC.Classes.== c_67
- then let _ = "choicesBranch.then"
- in let readFail_80 = readFail_66
- in if readMore_2 inp_44
- then let !(# c_81,
- cs_82 #) = readNext_3 inp_44
- in if (\x_83 -> GHC.Types.True) c_81
- then let _ = "resume"
- in join_52 init_1 Data.Set.Internal.empty (let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Forward) cs_82
- else let _ = "checkToken.else"
- in let failExp_84 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureAny @tok'_6989586621679198986)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_85,
- farExp_86 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_84 #)
- GHC.Types.EQ -> (# init_1,
- failExp_84 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_80 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_85 farExp_86
- else let _ = "checkHorizon.else"
- in let failExp_87 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 1)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_88,
- farExp_89 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_87 #)
- GHC.Types.EQ -> (# init_1,
- failExp_87 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_80 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_88 farExp_89
- else let _ = "choicesBranch.else"
- in if 43 GHC.Classes.== c_67
- then let _ = "choicesBranch.then"
- in let readFail_90 = readFail_66
- in if readMore_2 inp_44
- then let !(# c_91,
- cs_92 #) = readNext_3 inp_44
- in if (\x_93 -> GHC.Types.True) c_91
- then let _ = "resume"
- in join_52 init_1 Data.Set.Internal.empty (let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Increment) cs_92
- else let _ = "checkToken.else"
- in let failExp_94 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureAny @tok'_6989586621679198986)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_95,
- farExp_96 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_94 #)
- GHC.Types.EQ -> (# init_1,
- failExp_94 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_90 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_95 farExp_96
- else let _ = "checkHorizon.else"
- in let failExp_97 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 1)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_98,
- farExp_99 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_97 #)
- GHC.Types.EQ -> (# init_1,
- failExp_97 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_90 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_98 farExp_99
- else let _ = "choicesBranch.else"
- in if 45 GHC.Classes.== c_67
- then let _ = "choicesBranch.then"
- in let readFail_100 = readFail_66
- in if readMore_2 inp_44
- then let !(# c_101,
- cs_102 #) = readNext_3 inp_44
- in if (\x_103 -> GHC.Types.True) c_101
- then let _ = "resume"
- in join_52 init_1 Data.Set.Internal.empty (let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Decrement) cs_102
- else let _ = "checkToken.else"
- in let failExp_104 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureAny @tok'_6989586621679198986)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_105,
- farExp_106 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_104 #)
- GHC.Types.EQ -> (# init_1,
- failExp_104 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_100 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_105 farExp_106
- else let _ = "checkHorizon.else"
- in let failExp_107 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 1)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_108,
- farExp_109 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_107 #)
- GHC.Types.EQ -> (# init_1,
- failExp_107 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_100 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_108 farExp_109
- else let _ = "choicesBranch.else"
- in if 44 GHC.Classes.== c_67
- then let _ = "choicesBranch.then"
- in let readFail_110 = readFail_66
- in if readMore_2 inp_44
- then let !(# c_111,
- cs_112 #) = readNext_3 inp_44
- in if (\x_113 -> GHC.Types.True) c_111
- then let _ = "resume"
- in join_52 init_1 Data.Set.Internal.empty (let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Input) cs_112
- else let _ = "checkToken.else"
- in let failExp_114 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureAny @tok'_6989586621679198986)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_115,
- farExp_116 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_114 #)
- GHC.Types.EQ -> (# init_1,
- failExp_114 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_110 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_115 farExp_116
- else let _ = "checkHorizon.else"
- in let failExp_117 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 1)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_118,
- farExp_119 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_117 #)
- GHC.Types.EQ -> (# init_1,
- failExp_117 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_110 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_118 farExp_119
- else let _ = "choicesBranch.else"
- in if 46 GHC.Classes.== c_67
- then let _ = "choicesBranch.then"
- in let readFail_120 = readFail_66
- in if readMore_2 inp_44
- then let !(# c_121,
- cs_122 #) = readNext_3 inp_44
- in if (\x_123 -> GHC.Types.True) c_121
- then let _ = "resume"
- in join_52 init_1 Data.Set.Internal.empty (let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Output) cs_122
- else let _ = "checkToken.else"
- in let failExp_124 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureAny @tok'_6989586621679198986)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_125,
- farExp_126 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_124 #)
- GHC.Types.EQ -> (# init_1,
- failExp_124 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_120 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_125 farExp_126
- else let _ = "checkHorizon.else"
- in let failExp_127 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 1)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_128,
- farExp_129 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_127 #)
- GHC.Types.EQ -> (# init_1,
- failExp_127 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_120 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_128 farExp_129
- else let _ = "choicesBranch.else"
- in if 91 GHC.Classes.== c_67
- then let _ = "choicesBranch.then"
- in let readFail_130 = readFail_66
- in if readMore_2 ((GHC.Num.+) @GHC.Types.Int 1 inp_44)
- then let !(# c_131,
- cs_132 #) = readNext_3 inp_44
- in if (\x_133 -> GHC.Types.True) c_131
- then name_25 (let _ = "suspend"
- in \farInp_134 farExp_135 v_136 (!inp_137) -> name_34 (let _ = "suspend"
- in \farInp_138 farExp_139 v_140 (!inp_141) -> let readFail_142 = readFail_130
- in if readMore_2 inp_141
- then let !(# c_143,
- cs_144 #) = readNext_3 inp_141
- in if (93 GHC.Classes.==) c_143
- then let _ = "resume"
- in join_52 farInp_138 farExp_139 (let _ = "resume.genCode"
- in Parsers.Brainfuck.Types.Loop v_140) cs_144
- else let _ = "checkToken.else"
- in readFail_142 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_141 farInp_138 farExp_139
- else let _ = "checkHorizon.else"
- in let failExp_145 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 1)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_146,
- farExp_147 #) = case GHC.Classes.compare @GHC.Types.Int farInp_138 inp_141 of
- GHC.Types.LT -> (# inp_141,
- failExp_145 #)
- GHC.Types.EQ -> (# farInp_138,
- failExp_145 GHC.Base.<> farExp_139 #)
- GHC.Types.GT -> (# farInp_138,
- farExp_139 #)
- in readFail_142 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_141 farInp_146 farExp_147) inp_137 (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail_130 Data.Map.Internal.Tip Data.Map.Internal.Tip)) cs_132 (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail_130 Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else let _ = "checkToken.else"
- in let failExp_148 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureAny @tok'_6989586621679198986)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_149,
- farExp_150 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_148 #)
- GHC.Types.EQ -> (# init_1,
- failExp_148 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_130 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_149 farExp_150
- else let _ = "checkHorizon.else"
- in let failExp_151 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 2)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_152,
- farExp_153 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_151 #)
- GHC.Types.EQ -> (# init_1,
- failExp_151 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_130 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_152 farExp_153
- else let _ = "choicesBranch.else"
- in let failExp_154 = 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_155,
- farExp_156 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_154 #)
- GHC.Types.EQ -> (# init_1,
- failExp_154 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_66 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_155 farExp_156
- else let _ = "checkToken.else"
- in let failExp_157 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureAny @tok'_6989586621679198986)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_158,
- farExp_159 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_157 #)
- GHC.Types.EQ -> (# init_1,
- failExp_157 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_66 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_158 farExp_159
- else let _ = "checkHorizon.else"
- in let failExp_160 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 1)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_161,
- farExp_162 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_44 of
- GHC.Types.LT -> (# inp_44,
- failExp_160 #)
- GHC.Types.EQ -> (# init_1,
- failExp_160 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_66 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_44 farInp_161 farExp_162;
- name_29 = \(!ok_163) (!inp_164) (!koByLabel_165) -> let _ = "catch ExceptionFailure"
- in let catchHandler_166 (!_exn_167) (!failInp_168) (!farInp_169) (!farExp_170) = let _ = "catch.ko ExceptionFailure"
- in if (GHC.Classes.==) @GHC.Types.Int inp_164 failInp_168
- then let _ = "choicesBranch.then"
- in let _ = "resume"
- in ok_163 farInp_169 farExp_170 (let _ = "resume.genCode"
- in \x_171 -> x_171) failInp_168
- else let _ = "choicesBranch.else"
- in Data.Map.Strict.Internal.findWithDefault finalRaise_18 Symantic.Parser.Grammar.Combinators.ExceptionFailure koByLabel_165 Symantic.Parser.Grammar.Combinators.ExceptionFailure failInp_168 farInp_169 farExp_170
- in let readFail_172 = catchHandler_166
- in if readMore_2 inp_164
- then let !(# c_173,
- cs_174 #) = readNext_3 inp_164
- in if (\c_175 -> GHC.Classes.not ((60 GHC.Classes.== c_175) GHC.Classes.|| ((62 GHC.Classes.== c_175) GHC.Classes.|| ((43 GHC.Classes.== c_175) GHC.Classes.|| ((45 GHC.Classes.== c_175) GHC.Classes.|| ((44 GHC.Classes.== c_175) GHC.Classes.|| ((46 GHC.Classes.== c_175) GHC.Classes.|| ((91 GHC.Classes.== c_175) GHC.Classes.|| ((93 GHC.Classes.== c_175) GHC.Classes.|| GHC.Types.False))))))))) c_173
- then name_29 (let _ = "suspend"
- in \farInp_176 farExp_177 v_178 (!inp_179) -> let _ = "resume"
- in ok_163 farInp_176 farExp_177 (let _ = "resume.genCode"
- in \x_180 -> v_178 x_180) inp_179) cs_174 (Data.Map.Internal.Bin 1 Symantic.Parser.Grammar.Combinators.ExceptionFailure readFail_172 Data.Map.Internal.Tip Data.Map.Internal.Tip)
- else let _ = "checkToken.else"
- in readFail_172 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_164 init_1 Data.Set.Internal.empty
- else let _ = "checkHorizon.else"
- in let failExp_181 = Data.Set.Internal.Bin 1 (Symantic.Parser.Grammar.Combinators.SomeFailure (case inputToken of
- (Data.Proxy.Proxy :: Data.Proxy.Proxy tok'_6989586621679198986) -> Symantic.Parser.Grammar.Combinators.FailureHorizon @tok'_6989586621679198986 1)) Data.Set.Internal.Tip Data.Set.Internal.Tip
- in let (# farInp_182,
- farExp_183 #) = case GHC.Classes.compare @GHC.Types.Int init_1 inp_164 of
- GHC.Types.LT -> (# inp_164,
- failExp_181 #)
- GHC.Types.EQ -> (# init_1,
- failExp_181 GHC.Base.<> Data.Set.Internal.empty #)
- GHC.Types.GT -> (# init_1,
- Data.Set.Internal.empty #)
- in readFail_172 Symantic.Parser.Grammar.Combinators.ExceptionFailure inp_164 farInp_182 farExp_183}
- in name_25 (let _ = "suspend"
- in \farInp_184 farExp_185 v_186 (!inp_187) -> name_34 (let _ = "suspend"
- in \farInp_188 farExp_189 v_190 (!inp_191) -> let _ = "resume"
- in finalRet_13 farInp_188 farExp_189 (let _ = "resume.genCode"
- in v_190) inp_191) inp_187 Data.Map.Internal.Tip) init_1 Data.Map.Internal.Tip
import Control.DeepSeq (NFData)
import Data.Eq (Eq(..))
+import Data.Function (($), (.))
+import Data.Functor.Identity (Identity(..))
import GHC.Generics (Generic)
import Text.Show (Show(..))
+import qualified Language.Haskell.TH as TH
import qualified Language.Haskell.TH.Syntax as TH
+import Symantic.Univariant.Reify
+import qualified Symantic.Univariant.Lang as H
+import Symantic.Parser
+import qualified System.IO as IO
+import Control.Monad (Monad(..))
data Instruction
= Forward
+-- | This module enables to 'hideName'
+-- to get reproductible dumps of TemplateHaskell slices.
module Language.Haskell.TH.HideName where
import Data.Functor ((<$>))
--- /dev/null
+-- | This module enables to 'showCode'
+-- without requiring to be in 'IO'.
+module Language.Haskell.TH.Show where
+
+import Data.Function (($), (.))
+import Data.String (String, IsString(..))
+import Prelude (Integer, error, succ)
+import Control.Applicative (Applicative(..))
+import Control.Monad (Monad(..))
+import Data.Functor (Functor)
+import qualified Control.Monad as CM
+import qualified Control.Monad.IO.Class as CM
+import qualified Control.Monad.Trans.State as MT
+import qualified Language.Haskell.TH as TH
+import qualified Language.Haskell.TH.Syntax as TH
+
+newtype ShowQ a = ShowQ { unShowQ :: MT.State Integer a }
+ deriving (Functor, Applicative, Monad)
+
+runShowQ :: ShowQ a -> a
+runShowQ = (`MT.evalState` 0) . unShowQ
+
+showCode :: TH.CodeQ a -> String
+showCode q = runShowQ $ do
+ TH.runQ (TH.examineCode q) >>= return . TH.pprint . TH.unType
+
+-- | The whole point of ShowQ is to remove the need for IO,
+-- but GHC's 'TH.Quasi' class forces it...
+instance CM.MonadIO ShowQ
+instance CM.MonadFail ShowQ where
+ fail = error
+-- | Only 'TH.qNewName' is needed and thus implemented.
+instance TH.Quasi ShowQ where
+ qNewName n = ShowQ $ do
+ i <- MT.get
+ MT.put (succ i)
+ return (TH.mkNameU n i)
import Data.Either (Either(..))
import Data.Eq (Eq(..))
import Data.Ord (Ord(..))
-import Data.Function ((.), flip, const)
+import Data.Functor (Functor)
+import Data.Functor.Identity (Identity(..))
+import Data.Functor.Product (Product(..))
+import Data.Function ((.), flip, id, const)
import Data.Int (Int)
import Data.Kind (Type, Constraint)
import Data.Maybe (Maybe(..))
import qualified Data.Set as Set
import qualified Language.Haskell.TH as TH
import qualified Language.Haskell.TH.Syntax as TH
+import qualified Prelude
import qualified Symantic.Univariant.Trans as Sym
import qualified Symantic.Univariant.Lang as H
import qualified Symantic.Univariant.Data as Prod
+import qualified Symantic.Univariant.Reify as Reify
import qualified Symantic.Univariant.View
import Symantic.Parser.Grammar.Production
manyTill :: CombApplicable repr => CombAlternable repr => repr a -> repr b -> repr [a]
manyTill p end = let go = end $> H.nil <|> p <:> go in go
-{-
-class CombProductionable repr where
-infixl 4 <$>, <&>, <$, $>
-data instance Failure CombProductionable
--}
-
-
-- * Class 'CombApplicable'
-- | This is like the usual 'Functor' and 'Applicative' type classes
-- from the @base@ package, but using @('Production' a)@ instead of just @(a)@
-- | @(a2b '<$>' ra)@ parses like @(ra)@ but maps its returned value with @(a2b)@.
(<$>) :: Production (a -> b) -> repr a -> repr b
(<$>) f = (pure f <*>)
+ (<$>%) :: (Production a -> Production b) -> repr a -> repr b
+ a2b <$>% ma = H.lam a2b <$> ma
-- | Like '<$>' but with its arguments 'flip'-ped.
(<&>) :: repr a -> Production (a -> b) -> repr b
infixl 4 <*>, <*, *>, <**>
data instance Failure CombApplicable
+
{-# INLINE (<:>) #-}
infixl 4 <:>
(<:>) :: CombApplicable repr => repr a -> repr [a] -> repr [a]
import Data.Maybe (Maybe(..))
import Data.Set (Set)
import Data.Functor.Identity (Identity(..))
+import Data.Functor.Product (Product(..))
import Type.Reflection (Typeable, typeRep, eqTypeRep, (:~~:)(..))
import qualified Data.Foldable as Foldable
import qualified Data.Functor as Functor
import qualified Data.List as List
import Symantic.Parser.Grammar.Combinators hiding (code)
-import qualified Symantic.Parser.Grammar.Production as Prod
import Symantic.Parser.Grammar.Production
import Symantic.Univariant.Letable
import Symantic.Univariant.Trans
-import qualified Symantic.Univariant.Lang as H
+import qualified Symantic.Parser.Grammar.Production as Prod
import qualified Symantic.Univariant.Data as H
+import qualified Symantic.Univariant.Lang as H
{-
import Data.Function (($), flip)
-- & trace "Branch Weakening Law"
branch (Comb (Pure lr)) l r =
case runValue lr of
- Left value -> l <*> pure Production{..}
+ Left value -> l <*> pure (Pair v c)
where
- prodValue = H.SomeData $ H.Var $ Identity value
- prodCode = H.SomeData $ H.Var
+ v = H.SomeData $ H.Var $ Identity value
+ c = H.SomeData $ H.Var
[|| case $$(runCode lr) of Left x -> x ||]
- Right value -> r <*> pure Production{..}
+ Right value -> r <*> pure (Pair v c)
where
- prodValue = H.SomeData $ H.Var $ Identity value
- prodCode = H.SomeData $ H.Var
+ v = H.SomeData $ H.Var $ Identity value
+ c = H.SomeData $ H.Var
[|| case $$(runCode lr) of Right x -> x ||]
-- & trace "Branch Pure Either Law"
branch b (Comb (Pure l)) (Comb (Pure r)) =
- Production{..} <$> b
+ Pair v c <$> b
-- & trace "Branch Generalised Identity Law"
where
- prodValue = H.SomeData $ H.Var $ Identity $ either (runValue l) (runValue r)
- prodCode = H.SomeData $ H.Var [|| either $$(runCode l) $$(runCode r) ||]
+ v = H.SomeData $ H.Var $ Identity $ either (runValue l) (runValue r)
+ c = H.SomeData $ H.Var [|| either $$(runCode l) $$(runCode r) ||]
branch (Comb (x :*>: y)) p q = x *> branch y p q
-- & trace "Interchange Law"
branch b l (Comb Empty) =
- branch (pure Production{..} <*> b) empty l
+ branch (pure (Pair v c) <*> b) empty l
-- & trace "Negated Branch Law"
where
- prodValue = H.SomeData $ H.Var $ Identity $ either Right Left
- prodCode = H.SomeData $ H.Var $ [||either Right Left||]
+ v = H.SomeData $ H.Var $ Identity $ either Right Left
+ c = H.SomeData $ H.Var $ [||either Right Left||]
branch (Comb (Branch b (Comb Empty) (Comb (Pure lr)))) (Comb Empty) br =
- branch (pure Production{..} <*> b) empty br
+ branch (pure (Pair v c) <*> b) empty br
-- & trace "Branch Fusion Law"
where
- prodValue = H.SomeData $ H.Var $ Identity $ \case
+ v = H.SomeData $ H.Var $ Identity $ \case
Left{} -> Left ()
Right r ->
case runValue lr r of
Left{} -> Left ()
Right rr -> Right rr
- prodCode = H.SomeData $ H.Var
+ c = H.SomeData $ H.Var
[|| \case Left{} -> Left ()
Right r -> case $$(runCode lr) r of
Left{} -> Left ()
{-# LANGUAGE DefaultSignatures #-}
+{-# LANGUAGE StandaloneDeriving #-} -- For prodCon
{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE UndecidableInstances #-}
module Symantic.Parser.Grammar.Production where
+import Control.Monad (Monad(..))
import Data.Bool (Bool(..))
import Data.Char (Char)
import Data.Eq (Eq)
import Data.Functor.Identity (Identity(..))
-import Prelude (undefined)
+import Data.Functor.Product (Product(..))
+import Prelude (Num(..), undefined)
import Text.Show (Show(..), showString)
+import Type.Reflection (Typeable)
import qualified Data.Either as Either
import qualified Data.Eq as Eq
import qualified Data.Function as Fun
import qualified Data.Maybe as Maybe
import qualified Language.Haskell.TH as TH
import qualified Language.Haskell.TH.Syntax as TH
-import Type.Reflection (Typeable)
import Symantic.Univariant.Data
import Symantic.Univariant.Lang
import Symantic.Univariant.Optim
+import Symantic.Univariant.Reify
import Symantic.Univariant.Trans
import Symantic.Univariant.View
import Debug.Trace
--- * Type 'Production'
-data Production a
- = Production
- { prodValue :: SomeData Identity a
- , prodCode :: SomeData TH.CodeQ a
- --, prodView :: SomeData View a
- }
+type Production = Product
+ (SomeData Identity)
+ (SomeData TH.CodeQ)
+
+{-# INLINE prodValue #-}
+prodValue :: Production a -> SomeData Identity a
+prodValue (Pair v _) = v
+{-# INLINE prodCode #-}
+prodCode :: Production a -> SomeData TH.CodeQ a
+prodCode (Pair _ c) = c
+{-# INLINE production #-}
production :: a -> TH.CodeQ a -> Production a
-production v c = Production
- { prodValue = SomeData (Var (Identity v))
- , prodCode = SomeData (Var c)
- }
+production v c = Pair
+ (SomeData (Var (Identity v)))
+ (SomeData (Var c))
+{-# INLINE prod #-}
prod :: TH.Lift a => a -> Production a
prod x = production x [||x||]
+{-# INLINE runValue #-}
runValue :: Production a -> a
runValue x = runIdentity (trans x)
+{-# INLINE runCode #-}
runCode :: Production a -> TH.CodeQ a
runCode = trans
+-- Missing instances in Language.Haskell.TH
+deriving instance TH.Lift TH.OccName
+deriving instance TH.Lift TH.NameFlavour
+deriving instance TH.Lift TH.ModName
+deriving instance TH.Lift TH.PkgName
+deriving instance TH.Lift TH.NameSpace
+deriving instance TH.Lift TH.Name
+
+-- | @$(prodCon 'SomeConstructor)@ generates the 'Production' for @SomeConstructor@.
+prodCon :: TH.Name -> TH.Q TH.Exp
+prodCon name = do
+ info <- TH.reify name
+ case info of
+ TH.DataConI n ty _pn ->
+ [| production $(return (TH.ConE n))
+ (TH.unsafeCodeCoerce (return (TH.ConE $(TH.lift n)))) |]
+
instance Trans Production Identity where
- trans Production{prodValue = SomeData x} = trans x
+ trans (Pair (SomeData v) _c) = trans v
instance Trans Production TH.CodeQ where
- trans Production{prodCode = SomeData x} = trans x
+ trans (Pair _v (SomeData c)) = trans c
-instance Abstractable Production where
+instance (Abstractable f, Abstractable g) => Abstractable (Product f g) where
+ -- Those 'undefined' are not unreachables by 'f'
+ -- but this is the cost to pay for defining this instance.
+ -- In particular, 'f' must not define the 'TH.CodeQ' part
+ -- using the 'Identity' part.
+ lam f = Pair
+ (lam (\x -> let Pair fx _ = f (Pair x undefined) in fx))
+ (lam (\y -> let Pair _ fy = f (Pair undefined y) in fy))
+ lam1 f = Pair
+ (lam1 (\x -> let Pair fx _ = f (Pair x undefined) in fx))
+ (lam1 (\y -> let Pair _ fy = f (Pair undefined y) in fy))
+ const = Pair const const
var = Fun.id
- f .@ x = Production
- { prodValue = prodValue f .@ prodValue x
- , prodCode = prodCode f .@ prodCode x
- }
- lam f = Production
- { prodValue = lam (\x -> prodValue (f Production{prodValue = x}))
- , prodCode = lam (\x -> prodCode (f Production{prodCode = x}))
- }
- lam1 f = Production
- { prodValue = lam1 (\x -> prodValue (f Production{prodValue = x}))
- , prodCode = lam1 (\x -> prodCode (f Production{prodCode = x}))
- }
- const = Production const const
- ($) = Production ($) ($)
- (.) = Production (.) (.)
- flip = Production flip flip
- id = Production id id
-instance Eitherable Production where
- left = Production left left
- right = Production right right
+ id = Pair id id
+ flip = Pair flip flip
+ Pair f1 f2 .@ Pair x1 x2 = Pair (f1 .@x1) (f2 .@x2)
+ (.) = Pair (.) (.)
+ ($) = Pair ($) ($)
+instance (Num (f a), Num (g a)) => Num (Product f g a) where
+ Pair x1 x2 + Pair y1 y2 = Pair (x1 + y1) (x2 + y2)
+instance (Eitherable f, Eitherable g) => Eitherable (Product f g) where
+ left = Pair left left
+ right = Pair right right
instance (TH.Lift c, Typeable c) => Constantable c Production where
- constant c = Production (constant c) (constant c)
+ constant c = Pair (constant c) (constant c)
instance Maybeable Production where
- nothing = Production nothing nothing
- just = Production just just
+ nothing = Pair nothing nothing
+ just = Pair just just
instance Listable Production where
- nil = Production nil nil
- cons = Production cons cons
+ nil = Pair nil nil
+ cons = Pair cons cons
instance Equalable Production where
- equal = Production equal equal
+ equal = Pair equal equal
optimizeProduction :: Production a -> Production a
-optimizeProduction p = Production
- { prodValue = normalOrderReduction (prodValue p)
- , prodCode = normalOrderReduction (prodCode p)
- }
-
-{-
-class Tokenable repr where
- token :: tok -> repr tok
- default token ::
- Liftable repr => Tokenable (Output repr) =>
- tok -> repr tok
- token = lift Fun.. token
-
-instance Show (SomeData ValueCode a) where
- showsPrec p (SomeData x) = showsPrec p (trans @_ @View x)
--}
-
-{-
--- * Type 'ValueCode'
-data ValueCode a = ValueCode
- { value :: a
- , code :: TH.CodeQ a
- }
-instance Trans ValueCode ValueCode where
- trans = Fun.id
-instance Abstractable ValueCode where
- f .@ x = ValueCode
- { value = runIdentity (Identity (value f) .@ (Identity (value x)))
- , code = code f .@ code x
- }
- lam f = ValueCode
- { value = runIdentity (lam (Identity Fun.. value Fun.. f Fun.. (`ValueCode` undefined) Fun.. runIdentity))
- , code = lam (code Fun.. f Fun.. ValueCode undefined)
- }
- lam1 = lam
- const = ValueCode (runIdentity const) const
- flip = ValueCode (runIdentity flip) flip
- id = ValueCode (runIdentity id) id
- ($) = ValueCode (runIdentity ($)) ($)
- (.) = ValueCode (runIdentity (.)) (.)
-instance Anythingable ValueCode
-instance TH.Lift c => Constantable c ValueCode where
- constant c = ValueCode (runIdentity (constant c)) (constant c)
-instance Listable ValueCode where
- cons = ValueCode (runIdentity cons) cons
- nil = ValueCode (runIdentity nil) nil
-instance Equalable ValueCode where
- equal = ValueCode (runIdentity equal) equal
-instance Eitherable ValueCode where
- left = ValueCode (runIdentity left) left
- right = ValueCode (runIdentity right) right
-instance Maybeable ValueCode where
- nothing = ValueCode (runIdentity nothing) nothing
- just = ValueCode (runIdentity just) just
--}
+optimizeProduction (Pair v c) = Pair (normalOrderReduction v) (normalOrderReduction c)
-- Identity
instance Anythingable Identity
instance Maybeable TH.CodeQ where
nothing = [|| Maybe.Nothing ||]
just = [|| Maybe.Just ||]
+instance Num a => Num (TH.CodeQ a) where
+ x + y = [|| $$x + $$y||]
+{-# LANGUAGE OverloadedStrings #-}
module Symantic.Parser.Grammar.View where
import Data.Bool (Bool)
import Data.Semigroup (Semigroup(..))
import Data.String (String)
import Data.Tuple (fst)
+import System.IO (IO)
import Text.Show (Show(..))
import qualified Data.Functor as Functor
import qualified Data.HashMap.Strict as HM
import qualified Data.List as List
import qualified Data.Tree as Tree
+import qualified Language.Haskell.TH as TH
+import qualified Language.Haskell.TH.Show as TH
+import qualified Language.Haskell.TH.Syntax as TH
import Symantic.Univariant.Letable
import qualified Symantic.Univariant.Trans as Sym
try x = ViewGrammar $ Tree.Node ("try", "") [unViewGrammar x]
instance CombApplicable (ViewGrammar sN) where
_f <$> x = ViewGrammar $ Tree.Node ("<$>", "") [unViewGrammar x]
- pure a = ViewGrammar $ Tree.Node ("pure "{-FIXME: <>showsPrec 10 a ""-}, "") []
+ pure a = ViewGrammar $ Tree.Node ("pure " <> TH.showCode (Sym.trans (Prod.prodCode a)), "") []
x <*> y = ViewGrammar $ Tree.Node ("<*>", "") [unViewGrammar x, unViewGrammar y]
x <* y = ViewGrammar $ Tree.Node ("<*", "") [unViewGrammar x, unViewGrammar y]
x *> y = ViewGrammar $ Tree.Node ("*>", "") [unViewGrammar x, unViewGrammar y]
+++ /dev/null
-{-# LANGUAGE NoMonomorphismRestriction #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE ViewPatterns #-}
-module Symantic.Parser.Haskell.Optimize where
-
-import Data.Bool (Bool(..))
-import Data.Functor.Identity (Identity(..))
-import Data.String (String)
-import Prelude (undefined)
-import Text.Show (Show(..))
-import qualified Data.Eq as Eq
-import qualified Data.Function as Fun
-import qualified Language.Haskell.TH as TH
-import qualified Language.Haskell.TH.Syntax as TH
-
-import Symantic.Univariant.Trans
-import Symantic.Parser.Haskell.Term
-
--- * Type 'Term'
--- | Initial encoding of some 'Termable' symantics,
--- useful for some optimizations in 'optimizeTerm'.
-data Term repr a where
- -- | Black-box for all terms neither interpreted nor pattern-matched.
- Term :: { unTerm :: repr a } -> Term repr a
-
- -- Terms useful for 'optimizeTerm'.
- (:@) :: Term repr (a->b) -> Term repr a -> Term repr b
- Lam :: (Term repr a -> Term repr b) -> Term repr (a->b)
- Lam1 :: (Term repr a -> Term repr b) -> Term repr (a->b)
- Var :: String -> Term repr a
-
- -- Terms useful for prettier dumps.
- Char :: (TH.Lift tok, Show tok) => tok -> Term repr tok
- Cons :: Term repr (a -> [a] -> [a])
- Eq :: Eq.Eq a => Term repr (a -> a -> Bool)
- {-
- Const :: Term repr (a -> b -> a)
- Flip :: Term repr ((a -> b -> c) -> b -> a -> c)
- Id :: Term repr (a->a)
- (:$) :: Term repr ((a->b) -> a -> b)
- -- (:.) :: Term repr ((b->c) -> (a->b) -> a -> c)
--- infixr 0 :$
--- infixr 9 :.
- -}
-infixl 9 :@
-
-type instance Output (Term repr) = repr
-instance Trans repr (Term repr) where
- trans = Term
-
-instance Termable repr => Termable (Term repr) where
- lam = Lam
- lam1 = Lam1
- (.@) = (:@)
- cons = Cons
- eq = Eq
- unit = Term unit
- bool b = Term (bool b)
- char = Char
- nil = Term nil
- left = Term left
- right = Term right
- nothing = Term nothing
- just = Term just
- const = Lam1 (\x -> Lam1 (\_y -> x))
- flip = Lam1 (\f -> Lam1 (\x -> Lam1 (\y -> f .@ y .@ x)))
- id = Lam1 (\x -> x)
- ($) = Lam1 (\f -> Lam1 (\x -> f .@ x))
- (.) = Lam1 (\f -> Lam1 (\g -> Lam1 (\x -> f .@ (g .@ x))))
-
--- | Beta-reduce the left-most outer-most lambda abstraction (aka. normal-order reduction),
--- but to avoid duplication of work, only those manually marked
--- as using their variable at most once.
--- This is mainly to get prettier splices.
---
--- DOC: Demonstrating Lambda Calculus Reduction, Peter Sestoft, 2001,
--- https://www.itu.dk/people/sestoft/papers/sestoft-lamreduce.pdf
-optimizeTerm :: Term repr a -> Term repr a
-optimizeTerm = nor
- where
- -- | normal-order reduction
- nor :: Term repr a -> Term repr a
- nor = \case
- Lam f -> Lam (nor Fun.. f)
- Lam1 f -> Lam1 (nor Fun.. f)
- x :@ y -> case whnf x of
- Lam1 f -> nor (f y)
- x' -> nor x' :@ nor y
- x -> x
- -- | weak-head normal-form
- whnf :: Term repr a -> Term repr a
- whnf = \case
- x :@ y -> case whnf x of
- Lam1 f -> whnf (f y)
- x' -> x' :@ y
- x -> x
+++ /dev/null
-{-# LANGUAGE DefaultSignatures #-}
-{-# LANGUAGE TemplateHaskell #-}
--- | Haskell terms which are interesting
--- to pattern-match when optimizing.
-module Symantic.Parser.Haskell.Term where
-
-import Data.Bool (Bool(..))
-import Data.Char (Char)
-import Data.Either (Either(..))
-import Data.Eq (Eq)
-import Data.Maybe (Maybe(..))
-import Data.Functor.Identity (Identity(..))
-import Prelude (undefined)
-import Text.Show (Show(..))
-import qualified Data.Eq as Eq
-import qualified Data.Function as Fun
-import qualified Language.Haskell.TH as TH
-import qualified Language.Haskell.TH.Syntax as TH
-
-import Symantic.Univariant.Trans
-{-
-class Abstractable repr where
- -- | Application, aka. unabstract.
- (.@) :: repr (a->b) -> repr a -> repr b; infixl 9 .@
- -- | Lambda term abstraction, in HOAS (Higher-Order Abstract Syntax) style.
- lam :: (repr a -> repr b) -> repr (a->b)
- -- | Like 'lam' but whose argument is used only once,
- -- hence safe to beta-reduce (inline) without duplicating work.
- lam1 :: (repr a -> repr b) -> repr (a->b)
- const :: repr (a -> b -> a)
- flip :: repr ((a -> b -> c) -> b -> a -> c)
- id :: repr (a->a)
- (.) :: repr ((b->c) -> (a->b) -> a -> c); infixr 9 .
- ($) :: repr ((a->b) -> a -> b); infixr 0 $
- default (.@) ::
- Liftable2 repr => Abstractable (Output repr) =>
- repr (a->b) -> repr a -> repr b
- default lam ::
- Liftable repr => Unliftable repr => Abstractable (Output repr) =>
- (repr a -> repr b) -> repr (a->b)
- default lam1 ::
- Liftable repr => Unliftable repr => Abstractable (Output repr) =>
- (repr a -> repr b) -> repr (a->b)
- default const ::
- Liftable repr => Abstractable (Output repr) =>
- repr (a -> b -> a)
- default flip ::
- Liftable repr => Abstractable (Output repr) =>
- repr ((a -> b -> c) -> b -> a -> c)
- default id ::
- Liftable repr => Abstractable (Output repr) =>
- repr (a->a)
- default (.) ::
- Liftable repr => Abstractable (Output repr) =>
- repr ((b->c) -> (a->b) -> a -> c)
- default ($) ::
- Liftable repr => Abstractable (Output repr) =>
- repr ((a->b) -> a -> b)
- (.@) = lift2 (.@)
- lam f = lift (lam (trans Fun.. f Fun.. trans))
- lam1 f = lift (lam1 (trans Fun.. f Fun.. trans))
- const = lift const
- flip = lift flip
- id = lift id
- (.) = lift (.)
- ($) = lift ($)
-class Boolable repr where
- bool :: Bool -> repr Bool
- default bool ::
- Liftable repr => Boolable (Output repr) =>
- Bool -> repr Bool
- bool = lift Fun.. bool
-class Charable repr where
- char :: Char -> repr Char
- default char ::
- Liftable repr => Charable (Output repr) =>
- Char -> repr Char
- char = lift Fun.. char
-class Eitherable repr where
- left :: repr (l -> Either l r)
- right :: repr (r -> Either l r)
- default left ::
- Liftable repr => Eitherable (Output repr) =>
- repr (l -> Either l r)
- default right ::
- Liftable repr => Eitherable (Output repr) =>
- repr (r -> Either l r)
- left = lift left
- right = lift right
-class Equalable repr where
- eq :: Eq a => repr (a -> a -> Bool)
- default eq ::
- Liftable repr => Equalable (Output repr) =>
- Eq a => repr (a -> a -> Bool)
- eq = lift eq
-class Listable repr where
- cons :: repr (a -> [a] -> [a])
- nil :: repr [a]
- default cons ::
- Liftable repr => Listable (Output repr) =>
- repr (a -> [a] -> [a])
- default nil ::
- Liftable repr => Listable (Output repr) =>
- repr [a]
- cons = lift cons
- nil = lift nil
-class Maybeable repr where
- nothing :: repr (Maybe a)
- just :: repr (a -> Maybe a)
- default nothing ::
- Liftable repr => Maybeable (Output repr) =>
- repr (Maybe a)
- default just ::
- Liftable repr => Maybeable (Output repr) =>
- repr (a -> Maybe a)
- nothing = lift nothing
- just = lift just
-class Unitable repr where
- unit :: repr ()
- default unit ::
- Liftable repr => Unitable (Output repr) =>
- repr ()
- unit = lift unit
-
--}
}
) ||]
}
-
--- ** Type 'Catcher'
-type Catcher inp a =
- Exception ->
- {-failInp-}Cursor inp ->
- {-farInp-}Cursor inp ->
- {-farExp-}(Set SomeFailure) ->
- Either (ParsingError inp) a
instance InstrInputable Gen where
pushInput k = k
{ unGen = \ctx ->
||]
}
+-- ** Type 'Catcher'
+type Catcher inp a =
+ Exception ->
+ {-failInp-}Cursor inp ->
+ {-farInp-}Cursor inp ->
+ {-farExp-}(Set SomeFailure) ->
+ Either (ParsingError inp) a
+
instance InstrJoinable Gen where
defJoin (LetName n) sub k = k
{ unGen =
import Data.Eq (Eq(..))
import Data.Function ((.))
import Data.Kind (Type)
+import Data.Ord (Ord(..))
import Data.Set (Set)
-import Text.Show (Show(..), showString)
+import Text.Show (Show(..), showParen, showString)
import qualified Language.Haskell.TH as TH
+import qualified Language.Haskell.TH.Show as TH
import Symantic.Parser.Grammar
import Symantic.Parser.Machine.Input
import qualified Symantic.Univariant.Lang as H
+import qualified Symantic.Univariant.Trans as Sym
import qualified Symantic.Univariant.Data as Sym
-- * Type 'Splice'
type Splice = Sym.SomeData TH.CodeQ
+
instance Show (Splice a) where
- showsPrec _p _ = showString "<hidden>"
+ showsPrec p = showParen (p >= 0) . showString . TH.showCode . Sym.trans
splice :: TH.CodeQ a -> Splice a
splice x = Sym.SomeData (Sym.Var x)
import Symantic.Parser.Machine.Instructions
import Symantic.Univariant.Trans
-import Debug.Trace
-
-- * Data family 'Instr'
-- | 'Instr'uctions of the 'Machine'.
-- This is an extensible data-type.
Instr InstrValuable repr inp (y ': x ': vs) a
instance InstrValuable repr => Trans (Instr InstrValuable repr inp vs) (repr inp vs) where
trans = \case
- PushValue x k -> trace "trans.pushValue" (pushValue x (trans k))
+ PushValue x k -> pushValue x (trans k)
PopValue k -> popValue (trans k)
Lift2Value f k -> lift2Value f (trans k)
SwapValue k -> swapValue (trans k)
import Symantic.Parser.Machine.Instructions
import Symantic.Parser.Machine.Optimize
import Symantic.Univariant.Trans
-import Debug.Trace
-- * Type 'Program'
-- | A 'Program' is a tree of 'Instr'uctions,
Alt ExceptionFailure
(Comb (SatisfyOrFail _fs p :: Comb (CombSatisfiable (InputToken inp)) (Program repr inp) a))
(Comb (Failure sf)) ->
- Program $ return . trace "trans.read" . read (Set.singleton sf) (trace "read.prodCode" (prodCode p))
+ Program $ return . read (Set.singleton sf) (prodCode p)
Alt exn x y -> alt exn (trans x) (trans y)
Empty -> empty
Failure sf -> failure sf
instance
InstrValuable repr =>
CombApplicable (Program repr inp) where
- pure x = Program $ return . pushValue (prodCode (trace "pushValue.prodCode" x))
+ pure x = Program $ return . pushValue (prodCode x)
Program f <*> Program x = Program $ (f <=< x) . applyValue
liftA2 f (Program x) (Program y) = Program $ (x <=< y) . lift2Value (prodCode f)
Program x *> Program y = Program (x <=< return . popValue <=< y)
, InstrReadable tok repr
, Typeable tok
) => CombSatisfiable tok (Program repr inp) where
- satisfyOrFail fs p = Program $ return . read fs (trace "satisfyOrFail.read.prodCode" (prodCode p))
+ satisfyOrFail fs p = Program $ return . read fs (prodCode p)
instance
( InstrBranchable repr
, InstrJoinable repr
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-} -- For Show (SomeData a)
module Symantic.Univariant.View where
-
+{-
import Data.Int (Int)
import Data.Semigroup (Semigroup(..))
import Data.String
instance Maybeable View where
nothing = "Nothing"
just = "Just"
+-}
hs-source-dirs: src
exposed-modules:
Language.Haskell.TH.HideName
+ Language.Haskell.TH.Show
Symantic.Parser
Symantic.Parser.Grammar
Symantic.Parser.Grammar.Combinators
Symantic.Univariant.Lang
Symantic.Univariant.Letable
Symantic.Univariant.Optim
+ Symantic.Univariant.Reify
Symantic.Univariant.Trans
Symantic.Univariant.View
default-extensions:
exposed-modules:
Parsers.Brainfuck.Attoparsec
Parsers.Brainfuck.Handrolled
- Parsers.Brainfuck.SymanticParser.AutoSplice
- Parsers.Brainfuck.SymanticParser.DumpSplice
+ Parsers.Brainfuck.SymanticParser
Parsers.Brainfuck.SymanticParser.Grammar
- Parsers.Brainfuck.SymanticParser.PprSplice
Parsers.Brainfuck.Types
Parsers.Nandlang
Parsers.Playground
lets
` <*>
- + pure (\u1 -> Term 'a')
+ + pure \x_0 -> GHC.Show.show 'a'
` satisfy
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` <|>
+ <*>
- | + pure (\u1 -> 'a')
+ | + pure \x_0 -> 'a'
| ` satisfy
` <*>
- + pure (\u1 -> 'b')
+ + pure \x_0 -> 'b'
` satisfy
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> 'a' : u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'a' (x_1 x_2)
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> Term (u1 Term)))
+ | + pure \x_0 -> \x_1 -> GHC.Show.show (x_0 GHC.Types.[])
| ` ref <hidden>
` satisfy
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 : u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) x_0 (x_1 x_2)
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> Term (u1 Term)))
+ | + pure \x_0 -> \x_1 -> GHC.Show.show (x_0 GHC.Types.[])
| ` ref <hidden>
` eof
lets
+ let <hidden>
| ` <*>
-| + pure (\u1 -> Term)
+| + pure \x_0 -> GHC.Tuple.()
| ` ref <hidden>
+ let <hidden>
| ` <*>
-| + pure (\u1 -> u1 Term)
+| + pure \x_0 -> x_0 GHC.Types.[]
| ` ref <hidden>
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> u1 : u3 u4))))
+| | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> (GHC.Types.:) x_0 (x_2 x_3)
| | | | ` conditional
| | | | + look
| | | | | ` satisfy
| | | | + branches
| | | | | + <*>
-| | | | | | + pure (\u1 -> Term)
+| | | | | | + pure \x_0 -> Parsers.Brainfuck.Types.Backward
| | | | | | ` satisfy
| | | | | + <*>
-| | | | | | + pure (\u1 -> Term)
+| | | | | | + pure \x_0 -> Parsers.Brainfuck.Types.Forward
| | | | | | ` satisfy
| | | | | + <*>
-| | | | | | + pure (\u1 -> Term)
+| | | | | | + pure \x_0 -> Parsers.Brainfuck.Types.Increment
| | | | | | ` satisfy
| | | | | + <*>
-| | | | | | + pure (\u1 -> Term)
+| | | | | | + pure \x_0 -> Parsers.Brainfuck.Types.Decrement
| | | | | | ` satisfy
| | | | | + <*>
-| | | | | | + pure (\u1 -> Term)
+| | | | | | + pure \x_0 -> Parsers.Brainfuck.Types.Input
| | | | | | ` satisfy
| | | | | + <*>
-| | | | | | + pure (\u1 -> Term)
+| | | | | | + pure \x_0 -> Parsers.Brainfuck.Types.Output
| | | | | | ` satisfy
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> Term u3))))
+| | | | | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> Parsers.Brainfuck.Types.Loop x_2
| | | | | | | | ` satisfy
| | | | | | | ` ref <hidden>
| | | | | | ` rec <hidden>
| | | | ` failure
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_1 x_2
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> Term u2))
+ | + pure \x_0 -> \x_1 -> GHC.Show.show x_1
| ` ref <hidden>
` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u2))
+| | + pure \x_0 -> \x_1 -> x_1
| | ` ref <hidden>
| ` <|>
| + <*>
-| | + pure (\u1 -> Term)
+| | + pure \x_0 -> GHC.Tuple.()
| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
| + <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> u4))))
+| | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` ref <hidden>
| | | | + <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> (\u6 -> (\u7 -> u5)))))))
+| | | | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> \x_6 -> x_4
| | | | | | | ` satisfy
| | | | | | ` ref <hidden>
| | | | | ` ref <hidden>
| | | + <*>
| | | | + <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> (\u6 -> Term))))))
+| | | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> \x_5 -> GHC.Tuple.()
| | | | | | ` satisfy
| | | | | ` ref <hidden>
| | | | ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> '('))
+| | + pure \x_0 -> \x_1 -> '('
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> ')'))
+| | + pure \x_0 -> \x_1 -> ')'
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> ','))
+| | + pure \x_0 -> \x_1 -> ','
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> ';'))
+| | + pure \x_0 -> \x_1 -> ';'
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> Term))
+| | + pure \x_0 -> \x_1 -> GHC.Tuple.()
| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u2))
+| | + pure \x_0 -> \x_1 -> x_1
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u2))
+| | + pure \x_0 -> \x_1 -> x_1
| | ` try
| | ` <*>
| | + <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> u4))))
+| | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3
| | | | | ` satisfy
| | | | ` ref <hidden>
| | | ` ref <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u2))
+| | | + pure \x_0 -> \x_1 -> x_1
| | | ` <|>
| | | + <*>
-| | | | + pure (\u1 -> '0')
+| | | | + pure \x_0 -> '0'
| | | | ` satisfy
| | | ` <*>
-| | | + pure (\u1 -> '1')
+| | | + pure \x_0 -> '1'
| | | ` satisfy
| | ` ref <hidden>
| ` <|>
| | + <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> u2))))
+| | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> x_1
| | | | | ` satisfy
| | | | ` <|>
| | | | + <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> u2))
+| | | | | | + pure \x_0 -> \x_1 -> x_1
| | | | | | ` satisfy
| | | | | ` ref <hidden>
| | | | ` <*>
| | | | + <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> (\u3 -> u3)))
+| | | | | | + pure \x_0 -> \x_1 -> \x_2 -> x_2
| | | | | | ` satisfy
| | | | | ` satisfy
| | | | ` ref <hidden>
| | ` ref <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u2))
+| | + pure \x_0 -> \x_1 -> x_1
| | ` ref <hidden>
| ` <|>
| + <*>
-| | + pure (\u1 -> Term)
+| | + pure \x_0 -> GHC.Tuple.()
| | ` <|>
| | + <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> (\u3 -> u2)))
+| | | | | + pure \x_0 -> \x_1 -> \x_2 -> x_1
| | | | | ` ref <hidden>
| | | | ` <|>
| | | | + <*>
| | | | | + <*>
| | | | | | + <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> Term))))
+| | | | | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> GHC.Tuple.()
| | | | | | | | ` rec <hidden>
| | | | | | | ` ref <hidden>
| | | | | | ` ref <hidden>
| | + <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> (u1 u3) (u4 u5))))))
+| | | | | + 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 (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | | | | | | + <*>
| | | | | | | | + <*>
| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> (\u6 -> (\u7 -> (\u8 -> (\u9 -> (\u10 -> u9 u10))))))))))
+| | | | | | | | | | + 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 (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> (\u6 -> (\u7 -> (\u8 -> 'f' : ('u' : ('n' : ('c' : ('t' : ('i' : ('o' : ('n' : Term)))))))))))))))
+| | | | | | | | | | | | | | | | | + 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
| | | | | + <*>
| | | | | | + <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> (\u3 -> Term)))
+| | | | | | | | + pure \x_0 -> \x_1 -> \x_2 -> GHC.Tuple.()
| | | | | | | | ` satisfy
| | | | | | | ` ref <hidden>
| | | | | | ` ref <hidden>
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> (u1 u3) (u4 u5))))))
+| | | | | + 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 (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> (u1 u3) (u4 u5))))))
+| | | | | + 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 (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> (u1 u3) (u4 u5))))))
+| | | | | + 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 (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> u4 u5)))))
+| | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> x_3 x_4
| | | | | ` satisfy
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_1 x_2
| | | ` <|>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u2))
+| | | | | + pure \x_0 -> \x_1 -> x_1
| | | | | ` try
| | | | | ` <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> 'i' : ('f' : Term)))
+| | | | | | + pure \x_0 -> \x_1 -> (GHC.Types.:) 'i' ((GHC.Types.:) 'f' GHC.Types.[])
| | | | | | ` satisfy
| | | | | ` satisfy
| | | | ` ref <hidden>
| | | | + <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> u4))))
+| | | | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> x_3
| | | | | | | ` try
| | | | | | | ` <*>
| | | | | | | + <*>
| | | | | | | | + <*>
| | | | | | | | | + <*>
| | | | | | | | | | + <*>
-| | | | | | | | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> 'w' : ('h' : ('i' : ('l' : ('e' : Term)))))))))
+| | | | | | | | | | | + 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
| | | | | | | | | | | | + <*>
| | | | | | | | | | | | | + <*>
| | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> (\u6 -> (\u7 -> (\u8 -> (\u9 -> (\u10 -> (\u11 -> (\u12 -> u11))))))))))))
+| | | | | | | | | | | | | | | + 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 (\u1 -> (\u2 -> Term))
+| | | | | | | | | | | | | | | | | + pure \x_0 -> \x_1 -> GHC.Tuple.()
| | | | | | | | | | | | | | | | | ` try
| | | | | | | | | | | | | | | | | ` <*>
| | | | | | | | | | | | | | | | | + <*>
| | | | | | | | | | | | | | | | | | + <*>
-| | | | | | | | | | | | | | | | | | | + pure (\u1 -> (\u2 -> (\u3 -> 'v' : ('a' : ('r' : Term)))))
+| | | | | | | | | | | | | | | | | | | + pure \x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'v' ((GHC.Types.:) 'a' ((GHC.Types.:) 'r' GHC.Types.[]))
| | | | | | | | | | | | | | | | | | | ` satisfy
| | | | | | | | | | | | | | | | | | ` satisfy
| | | | | | | | | | | | | | | | | ` satisfy
| | | | ` ref <hidden>
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_1 x_2
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_1 x_2
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_1 x_2
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> Term))))
+| | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> GHC.Tuple.()
| | | | | ` ref <hidden>
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
-| ` pure (\u1 -> (\u2 -> u2))
+| ` pure GHC.Tuple.()
+ let <hidden>
-| ` pure Term
+| ` pure GHC.Tuple.()
+ let <hidden>
-| ` pure Term
+| ` pure \x_0 -> \x_1 -> x_1
+ let <hidden>
| ` satisfy
` <*>
| + <*>
| | + <*>
| | | + <*>
- | | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> (\u5 -> Term u4)))))
+ | | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> \x_4 -> GHC.Show.show x_3
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` ref <hidden>
lets
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> Term u1))
+ | + pure \x_0 -> \x_1 -> GHC.Show.show x_0
| ` <|>
| + <*>
- | | + pure (\u1 -> 'a')
+ | | + pure \x_0 -> 'a'
| | ` satisfy
| ` <*>
- | + pure (\u1 -> 'b')
+ | + pure \x_0 -> 'b'
| ` satisfy
` satisfy
lets
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> Term u1))
+ | + pure \x_0 -> \x_1 -> GHC.Show.show x_0
| ` <|>
| + <*>
- | | + pure (\u1 -> 'a')
+ | | + pure \x_0 -> 'a'
| | ` satisfy
| ` <|>
| + <*>
- | | + pure (\u1 -> 'b')
+ | | + pure \x_0 -> 'b'
| | ` satisfy
| ` <*>
- | + pure (\u1 -> 'c')
+ | + pure \x_0 -> 'c'
| ` satisfy
` satisfy
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` try
` <*>
+ <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> (\u3 -> 'a' : ('b' : ('c' : Term)))))
+ | | + pure \x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' GHC.Types.[]))
| | ` satisfy
| ` satisfy
` satisfy
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> 'a' : u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'a' (x_1 x_2)
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
- + pure (\u1 -> Term (u1 Term))
+ + pure \x_0 -> GHC.Show.show (x_0 GHC.Types.[])
` ref <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 : u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) x_0 (x_1 x_2)
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` try
| ` <*>
| + <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> 'a' : ('b' : ('c' : ('d' : Term)))))))
+| | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types.[])))
| | | | ` satisfy
| | | ` satisfy
| | ` satisfy
| ` satisfy
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> Term (u1 : u2 Term)))
+ | + pure \x_0 -> \x_1 -> GHC.Show.show ((GHC.Types.:) x_0 (x_1 GHC.Types.[]))
| ` ref <hidden>
` ref <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 : u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) x_0 (x_1 x_2)
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` try
| ` <*>
| + <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (\u4 -> 'a' : ('b' : ('c' : ('d' : Term)))))))
+| | | | + pure \x_0 -> \x_1 -> \x_2 -> \x_3 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types.[])))
| | | | ` satisfy
| | | ` satisfy
| | ` satisfy
` <*>
+ <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> (\u3 -> Term (u1 : u2 Term))))
+ | | + pure \x_0 -> \x_1 -> \x_2 -> GHC.Show.show ((GHC.Types.:) x_0 (x_1 GHC.Types.[]))
| | ` ref <hidden>
| ` ref <hidden>
` eof
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` <|>
+ <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> 'a' : ('a' : Term)))
+ | | + pure \x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types.[])
| | ` satisfy
| ` satisfy
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> 'a' : ('b' : Term)))
+ | + pure \x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types.[])
| ` satisfy
` satisfy
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` <|>
+ try
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> 'a' : ('a' : Term)))
+ | | + pure \x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types.[])
| | ` satisfy
| ` satisfy
` try
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> 'a' : ('b' : Term)))
+ | + pure \x_0 -> \x_1 -> (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types.[])
| ` satisfy
` satisfy
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> 'r' : u2 u3)))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> (GHC.Types.:) 'r' (x_1 x_2)
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> Term (u1 Term)))
+ | + pure \x_0 -> \x_1 -> GHC.Show.show (x_0 GHC.Types.[])
| ` ref <hidden>
` eof
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` eof
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` pure 'a'
` satisfy
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` <|>
+ <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'a'
| ` satisfy
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` pure 'b'
` satisfy
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
-| | | + pure cons
+| | | + pure (GHC.Types.:)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` pure 'a'
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` <*>
| + ref <hidden>
- | ` pure Term
+ | ` pure GHC.Types.[]
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` pure 'b'
` satisfy
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
-| | | + pure cons
+| | | + pure (GHC.Types.:)
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` <*>
| + ref <hidden>
- | ` pure Term
+ | ` pure GHC.Types.[]
` eof
| ` <*>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure (\u1 -> u1)
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure \x_0 -> x_0
| | ` <*>
| | + <*>
-| | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
-| | | ` pure Term
+| | | + 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>
-| ` pure Term
+| ` pure GHC.Tuple.()
+ let <hidden>
| ` <*>
| + ref <hidden>
-| ` pure Term
+| ` pure GHC.Types.[]
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
-| | | | ` pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1
+| | | | ` pure \x_0 -> \x_1 -> x_0
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
-| | | + pure cons
+| | | + pure (GHC.Types.:)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` conditional
| | | | + look
| | | | | ` satisfy
| | | | + branches
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure Term
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure Parsers.Brainfuck.Types.Backward
| | | | | | ` satisfy
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure Term
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure Parsers.Brainfuck.Types.Forward
| | | | | | ` satisfy
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure Term
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure Parsers.Brainfuck.Types.Increment
| | | | | | ` satisfy
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure Term
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure Parsers.Brainfuck.Types.Decrement
| | | | | | ` satisfy
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure Term
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure Parsers.Brainfuck.Types.Input
| | | | | | ` satisfy
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure Term
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure Parsers.Brainfuck.Types.Output
| | | | | | ` satisfy
| | | | | ` <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | ` <*>
| | | | | | + <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | ` pure \x_0 -> x_0
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | ` satisfy
| | | | | | | ` ref <hidden>
| | | | | | ` <*>
-| | | | | | + pure Term
+| | | | | | + pure Parsers.Brainfuck.Types.Loop
| | | | | | ` rec <hidden>
| | | | | ` <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | ` pure ']'
| | | | | ` satisfy
| | | | ` failure
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
- | | ` pure (\u1 -> u1)
+ | | + pure \x_0 -> \x_1 -> x_0
+ | | ` pure \x_0 -> x_0
| ` ref <hidden>
` ref <hidden>
| ` <*>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure (\u1 -> u1)
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure \x_0 -> x_0
| | ` ref <hidden>
| ` <*>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure (\u1 -> u1)
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure \x_0 -> x_0
| | ` <*>
| | + <*>
-| | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
-| | | ` pure Term
+| | | + 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>
-| ` pure Term
+| ` pure GHC.Tuple.()
+ let <hidden>
| ` <*>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure (\u1 -> u1)
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure \x_0 -> x_0
| | ` ref <hidden>
| ` <*>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure (\u1 -> u1)
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure \x_0 -> x_0
| | ` <*>
| | + <*>
-| | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | + 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>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u1))
+| | + pure \x_0 -> \x_1 -> x_0
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
-| | | | ` pure (\u1 -> u1)
+| | | | + pure \x_0 -> \x_1 -> x_0
+| | | | ` pure \x_0 -> x_0
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | ` pure '['
| | | | ` satisfy
| | | ` ref <hidden>
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
-| | | | ` pure (\u1 -> u1)
+| | | | + pure \x_0 -> \x_1 -> x_0
+| | | | ` pure \x_0 -> x_0
| | | ` ref <hidden>
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
-| | | | ` pure (\u1 -> u1)
+| | | | + pure \x_0 -> \x_1 -> x_0
+| | | | ` pure \x_0 -> x_0
| | | ` <*>
| | | + <*>
-| | | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
-| | | | ` pure Term
+| | | | + 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>
-| | ` pure Term
+| | ` pure GHC.Tuple.()
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u1))
+| | + pure \x_0 -> \x_1 -> x_0
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure ']'
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u1))
+| | + pure \x_0 -> \x_1 -> x_0
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
-| | | | ` pure (\u1 -> u1)
+| | | | + pure \x_0 -> \x_1 -> x_0
+| | | | ` pure \x_0 -> x_0
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | ` pure '{'
| | | | ` satisfy
| | | ` ref <hidden>
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
-| | | | ` pure (\u1 -> u1)
+| | | | + pure \x_0 -> \x_1 -> x_0
+| | | | ` pure \x_0 -> x_0
| | | ` <*>
| | | + <*>
-| | | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | | + 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 (\u1 -> (\u2 -> u1))
+| | + pure \x_0 -> \x_1 -> x_0
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure '}'
| | ` satisfy
| ` ref <hidden>
| ` <*>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure (\u1 -> u1)
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure \x_0 -> x_0
| | ` ref <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure Term
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure GHC.Tuple.()
| | ` ref <hidden>
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure (\u1 -> u1)
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure \x_0 -> x_0
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure (\u1 -> u1)
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure \x_0 -> x_0
| | ` try
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
-| | | | ` pure (\u1 -> u1)
+| | | | + pure \x_0 -> \x_1 -> x_0
+| | | | ` pure \x_0 -> x_0
| | | ` satisfy
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
-| | | | ` pure (\u1 -> u1)
+| | | | + pure \x_0 -> \x_1 -> x_0
+| | | | ` pure \x_0 -> x_0
| | | ` <*>
| | | + <*>
-| | | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | | + 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>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u1))
+| | + pure \x_0 -> \x_1 -> x_0
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure '('
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u1))
+| | + pure \x_0 -> \x_1 -> x_0
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure ')'
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u1))
+| | + pure \x_0 -> \x_1 -> x_0
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure ','
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
| + <*>
-| | + pure (\u1 -> (\u2 -> u1))
+| | + pure \x_0 -> \x_1 -> x_0
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure ';'
| | ` satisfy
| ` ref <hidden>
+ let <hidden>
| ` <*>
-| + pure (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
-| ` pure (\u1 -> (\u2 -> u1))
+| + pure \x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1
+| ` pure \x_0 -> \x_1 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
-| | | | ` pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1
+| | | | ` pure \x_0 -> \x_1 -> x_0
| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` <*>
| | | | + <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | ` pure (\u1 -> u1)
+| | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | ` pure \x_0 -> x_0
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure (\u1 -> u1)
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure \x_0 -> x_0
| | | | | | ` <*>
| | | | | | + <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | ` pure \x_0 -> x_0
| | | | | | | ` try
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 'f'
| | | | | | | | ` satisfy
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 'u'
| | | | | | | | ` satisfy
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 'n'
| | | | | | | | ` satisfy
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 'c'
| | | | | | | | ` satisfy
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 't'
| | | | | | | | ` satisfy
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 'i'
| | | | | | | | ` satisfy
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 'o'
| | | | | | | | ` satisfy
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 'n'
| | | | | | | | ` satisfy
-| | | | | | | ` pure Term
+| | | | | | | ` pure GHC.Types.[]
| | | | | | ` ref <hidden>
| | | | | ` ref <hidden>
| | | | ` <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure (\u1 -> u1)
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure \x_0 -> x_0
| | | | | | ` ref <hidden>
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure (\u1 -> u1)
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure \x_0 -> x_0
| | | | | | ` ref <hidden>
| | | | | ` <|>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure Term
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure GHC.Tuple.()
| | | | | | ` <*>
| | | | | | + <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | ` pure \x_0 -> x_0
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure ':'
| | | | | | | | ` satisfy
| | | | | | | ` ref <hidden>
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
-| | | | ` pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1
+| | | | ` pure \x_0 -> \x_1 -> x_0
| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | ` <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | ` pure '!'
| | | | | ` satisfy
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
-| | | | ` pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1
+| | | | ` pure \x_0 -> \x_1 -> x_0
| | | ` <|>
| | | + <|>
| | | | + <|>
| | | | | + <*>
| | | | | | + <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | ` pure \x_0 -> x_0
| | | | | | | ` try
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 'i'
| | | | | | | | ` satisfy
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure cons
+| | | | | | | | + pure (GHC.Types.:)
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | ` pure 'f'
| | | | | | | | ` satisfy
-| | | | | | | ` pure Term
+| | | | | | | ` pure GHC.Types.[]
| | | | | | ` ref <hidden>
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure (\u1 -> u1)
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure \x_0 -> x_0
| | | | | | ` <*>
| | | | | | + <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | ` pure \x_0 -> x_0
| | | | | | | ` <*>
| | | | | | | + <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | | ` pure \x_0 -> x_0
| | | | | | | | ` try
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure cons
+| | | | | | | | | + pure (GHC.Types.:)
| | | | | | | | | ` <*>
| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | | ` pure 'w'
| | | | | | | | | ` satisfy
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure cons
+| | | | | | | | | + pure (GHC.Types.:)
| | | | | | | | | ` <*>
| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | | ` pure 'h'
| | | | | | | | | ` satisfy
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure cons
+| | | | | | | | | + pure (GHC.Types.:)
| | | | | | | | | ` <*>
| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | | ` pure 'i'
| | | | | | | | | ` satisfy
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure cons
+| | | | | | | | | + pure (GHC.Types.:)
| | | | | | | | | ` <*>
| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | | ` pure 'l'
| | | | | | | | | ` satisfy
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure cons
+| | | | | | | | | + pure (GHC.Types.:)
| | | | | | | | | ` <*>
| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | | ` pure 'e'
| | | | | | | | | ` satisfy
-| | | | | | | | ` pure Term
+| | | | | | | | ` pure GHC.Types.[]
| | | | | | | ` ref <hidden>
| | | | | | ` ref <hidden>
| | | | | ` rec <hidden>
| | | | ` try
| | | | ` <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure (\u1 -> u1)
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure \x_0 -> x_0
| | | | | | ` <*>
| | | | | | + <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | ` pure \x_0 -> x_0
| | | | | | | ` <*>
| | | | | | | + <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | | ` pure \x_0 -> x_0
| | | | | | | | ` <|>
| | | | | | | | + <*>
| | | | | | | | | + <*>
-| | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | | | ` pure Term
+| | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | | | ` pure GHC.Tuple.()
| | | | | | | | | ` <*>
| | | | | | | | | + <*>
| | | | | | | | | | + <*>
-| | | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | | | | ` pure \x_0 -> x_0
| | | | | | | | | | ` try
| | | | | | | | | | ` <*>
| | | | | | | | | | + <*>
-| | | | | | | | | | | + pure cons
+| | | | | | | | | | | + pure (GHC.Types.:)
| | | | | | | | | | | ` <*>
| | | | | | | | | | | + <*>
-| | | | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | | | | ` pure 'v'
| | | | | | | | | | | ` satisfy
| | | | | | | | | | ` <*>
| | | | | | | | | | + <*>
-| | | | | | | | | | | + pure cons
+| | | | | | | | | | | + pure (GHC.Types.:)
| | | | | | | | | | | ` <*>
| | | | | | | | | | | + <*>
-| | | | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | | | | ` pure 'a'
| | | | | | | | | | | ` satisfy
| | | | | | | | | | ` <*>
| | | | | | | | | | + <*>
-| | | | | | | | | | | + pure cons
+| | | | | | | | | | | + pure (GHC.Types.:)
| | | | | | | | | | | ` <*>
| | | | | | | | | | | + <*>
-| | | | | | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | | | | | ` pure 'r'
| | | | | | | | | | | ` satisfy
-| | | | | | | | | | ` pure Term
+| | | | | | | | | | ` pure GHC.Types.[]
| | | | | | | | | ` ref <hidden>
| | | | | | | | ` ref <hidden>
| | | | | | | ` <*>
| | | | | | | + <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | | ` pure \x_0 -> x_0
| | | | | | | | ` ref <hidden>
| | | | | | | ` <*>
| | | | | | | + <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | | | ` pure (\u1 -> u1)
+| | | | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | | | ` pure \x_0 -> x_0
| | | | | | | | ` <*>
| | | | | | | | + <*>
-| | | | | | | | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | | | | | | | + 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 (\u1 -> (\u2 -> u1))
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | ` <*>
| | | | | | | + <*>
-| | | | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | | | ` pure '='
| | | | | | | ` satisfy
| | | | | | ` ref <hidden>
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure (\u1 -> u1)
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure \x_0 -> x_0
| | | | | | ` ref <hidden>
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure (\u1 -> u1)
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure \x_0 -> x_0
| | | | | | ` <*>
| | | | | | + <*>
-| | | | | | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | | | | | + 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 (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
-| | | | ` pure (\u1 -> (\u2 -> u1))
+| | | | + 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 (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
-| | | | ` pure (\u1 -> (\u2 -> u1))
+| | | | + 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 (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
-| | | | ` pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1
+| | | | ` pure \x_0 -> \x_1 -> x_0
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + ref <hidden>
| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` ref <hidden>
| | | ` rec <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + ref <hidden>
| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + ref <hidden>
| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
| | | + ref <hidden>
| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` ref <hidden>
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure Term
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure GHC.Tuple.()
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
-| | | | ` pure (\u1 -> u1)
+| | | | + pure \x_0 -> \x_1 -> x_0
+| | | | ` pure \x_0 -> x_0
| | | ` ref <hidden>
| | ` <*>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
-| | | | ` pure (\u1 -> u1)
+| | | | + pure \x_0 -> \x_1 -> x_0
+| | | | ` pure \x_0 -> x_0
| | | ` <*>
| | | + <*>
-| | | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | | + 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 (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` <|>
| | | | + <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | | ` pure '0'
| | | | | ` satisfy
| | | | ` <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | ` pure '1'
| | | | ` satisfy
| | | ` ref <hidden>
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | ` pure '\''
| | | | ` satisfy
| | | ` <|>
| | | + <*>
| | | | + <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | ` pure (\u1 -> u1)
+| | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | ` pure \x_0 -> x_0
| | | | | ` satisfy
| | | | ` ref <hidden>
| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
+| | | | | + pure \x_0 -> \x_1 -> x_0
| | | | | ` pure '\\'
| | | | ` satisfy
| | | ` <*>
| | | + <*>
| | | | + <*>
-| | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | ` pure (\u1 -> u1)
+| | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | ` pure \x_0 -> x_0
| | | | ` satisfy
| | | ` ref <hidden>
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` pure '\''
| | | ` satisfy
| | ` ref <hidden>
| ` <*>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure (\u1 -> u1)
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure \x_0 -> x_0
| | ` ref <hidden>
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
-| | | ` pure Term
+| | | + pure \x_0 -> \x_1 -> x_0
+| | | ` pure GHC.Tuple.()
| | ` <|>
| | + <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` <*>
| | | | + <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | ` pure (\u1 -> u1)
+| | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | ` pure \x_0 -> x_0
| | | | | ` ref <hidden>
| | | | ` <|>
| | | | + <*>
| | | | | + <*>
-| | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | ` pure Term
+| | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | ` pure GHC.Tuple.()
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure (\u1 -> u1)
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure \x_0 -> x_0
| | | | | | ` rec <hidden>
| | | | | ` <*>
| | | | | + <*>
| | | | | | + <*>
-| | | | | | | + pure (\u1 -> (\u2 -> u1))
-| | | | | | | ` pure (\u1 -> u1)
+| | | | | | | + pure \x_0 -> \x_1 -> x_0
+| | | | | | | ` pure \x_0 -> x_0
| | | | | | ` <*>
| | | | | | + <*>
-| | | | | | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | | | | | + 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>
| ` ref <hidden>
+ let <hidden>
-| ` pure Term
+| ` pure GHC.Tuple.()
+ let <hidden>
-| ` pure Term
+| ` pure GHC.Tuple.()
+ let <hidden>
| ` satisfy
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` <*>
| + <*>
| | + <*>
- | | | + pure (\u1 -> (\u2 -> u1))
- | | | ` pure (\u1 -> u1)
+ | | | + pure \x_0 -> \x_1 -> x_0
+ | | | ` pure \x_0 -> x_0
| | ` ref <hidden>
| ` <*>
| + <*>
| | + <*>
- | | | + pure (\u1 -> (\u2 -> u1))
- | | | ` pure (\u1 -> u1)
+ | | | + pure \x_0 -> \x_1 -> x_0
+ | | | ` pure \x_0 -> x_0
| | ` <*>
| | + <*>
- | | | + pure ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+ | | | + 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>
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` <|>
| + <*>
| | + <*>
- | | | + pure (\u1 -> (\u2 -> u1))
+ | | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'a'
| | ` satisfy
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'b'
| ` satisfy
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` pure 'c'
` satisfy
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` <|>
| + <|>
| | + <*>
| | | + <*>
- | | | | + pure (\u1 -> (\u2 -> u1))
+ | | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` pure 'a'
| | | ` satisfy
| | ` <*>
| | + <*>
- | | | + pure (\u1 -> (\u2 -> u1))
+ | | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'b'
| | ` satisfy
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'c'
| ` satisfy
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` pure 'd'
` satisfy
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` try
` <*>
+ <*>
- | + pure cons
+ | + pure (GHC.Types.:)
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'a'
| ` satisfy
` <*>
+ <*>
- | + pure cons
+ | + pure (GHC.Types.:)
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'b'
| ` satisfy
` <*>
+ <*>
- | + pure cons
+ | + pure (GHC.Types.:)
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'c'
| ` satisfy
- ` pure Term
+ ` pure GHC.Types.[]
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
-| | | + pure cons
+| | | + pure (GHC.Types.:)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` pure 'a'
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ ref <hidden>
- ` pure Term
+ ` pure GHC.Types.[]
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
-| | | + pure cons
+| | | + pure (GHC.Types.:)
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` try
| ` <*>
| + <*>
-| | + pure cons
+| | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'a'
| | ` satisfy
| ` <*>
| + <*>
-| | + pure cons
+| | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'b'
| | ` satisfy
| ` <*>
| + <*>
-| | + pure cons
+| | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'c'
| | ` satisfy
| ` <*>
| + <*>
-| | + pure cons
+| | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'd'
| | ` satisfy
-| ` pure Term
+| ` pure GHC.Types.[]
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
- | + pure cons
+ | + pure (GHC.Types.:)
| ` ref <hidden>
` <*>
+ ref <hidden>
- ` pure Term
+ ` pure GHC.Types.[]
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
-| | | + pure cons
+| | | + pure (GHC.Types.:)
| | | ` ref <hidden>
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
+ let <hidden>
| ` try
| ` <*>
| + <*>
-| | + pure cons
+| | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'a'
| | ` satisfy
| ` <*>
| + <*>
-| | + pure cons
+| | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'b'
| | ` satisfy
| ` <*>
| + <*>
-| | + pure cons
+| | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'c'
| | ` satisfy
| ` <*>
| + <*>
-| | + pure cons
+| | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> u1))
+| | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'd'
| | ` satisfy
-| ` pure Term
+| ` pure GHC.Types.[]
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` <*>
| + <*>
- | | + pure cons
+ | | + pure (GHC.Types.:)
| | ` ref <hidden>
| ` <*>
| + ref <hidden>
- | ` pure Term
+ | ` pure GHC.Types.[]
` eof
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` <|>
+ <*>
| + <*>
- | | + pure cons
+ | | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
- | | | + pure (\u1 -> (\u2 -> u1))
+ | | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'a'
| | ` satisfy
| ` <*>
| + <*>
- | | + pure cons
+ | | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
- | | | + pure (\u1 -> (\u2 -> u1))
+ | | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'a'
| | ` satisfy
- | ` pure Term
+ | ` pure GHC.Types.[]
` <*>
+ <*>
- | + pure cons
+ | + pure (GHC.Types.:)
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'a'
| ` satisfy
` <*>
+ <*>
- | + pure cons
+ | + pure (GHC.Types.:)
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'b'
| ` satisfy
- ` pure Term
+ ` pure GHC.Types.[]
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` <|>
+ try
| ` <*>
| + <*>
- | | + pure cons
+ | | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
- | | | + pure (\u1 -> (\u2 -> u1))
+ | | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'a'
| | ` satisfy
| ` <*>
| + <*>
- | | + pure cons
+ | | + pure (GHC.Types.:)
| | ` <*>
| | + <*>
- | | | + pure (\u1 -> (\u2 -> u1))
+ | | | + pure \x_0 -> \x_1 -> x_0
| | | ` pure 'a'
| | ` satisfy
- | ` pure Term
+ | ` pure GHC.Types.[]
` try
` <*>
+ <*>
- | + pure cons
+ | + pure (GHC.Types.:)
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'a'
| ` satisfy
` <*>
+ <*>
- | + pure cons
+ | + pure (GHC.Types.:)
| ` <*>
| + <*>
- | | + pure (\u1 -> (\u2 -> u1))
+ | | + pure \x_0 -> \x_1 -> x_0
| | ` pure 'b'
| ` satisfy
- ` pure Term
+ ` pure GHC.Types.[]
| ` <|>
| + <*>
| | + <*>
-| | | + pure (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | + pure \x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2)
| | | ` <*>
-| | | + pure cons
+| | | + pure (GHC.Types.:)
| | | ` <*>
| | | + <*>
-| | | | + pure (\u1 -> (\u2 -> u1))
+| | | | + pure \x_0 -> \x_1 -> x_0
| | | | ` pure 'r'
| | | ` satisfy
| | ` rec <hidden>
-| ` pure (\u1 -> u1)
+| ` pure \x_0 -> x_0
` <*>
- + pure Term
+ + pure GHC.Show.show
` <*>
+ <*>
- | + pure (\u1 -> (\u2 -> u1))
+ | + pure \x_0 -> \x_1 -> x_0
| ` <*>
| + ref <hidden>
- | ` pure Term
+ | ` pure GHC.Types.[]
` eof
lets
` <*>
- + pure Term
+ + pure GHC.Show.show
` eof
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue 'a'
+pushValue ('a')
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-read ('a' ==)
+read ((GHC.Classes.==) 'a')
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
ret
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 0)
mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
minReads=(Right 1)
mayRaise=[ExceptionFailure]
| <ok>
-| | pushValue (\u1 -> (\u2 -> u1))
+| | pushValue (\x_0 -> \x_1 -> x_0)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
+| | pushValue ('a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | read ('a' ==)
+| | read ((GHC.Classes.==) 'a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
| | commit ExceptionFailure
| | pushInput
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
| | | <branch>
-| | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'b'
+| | | | pushValue ('b')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | read ('b' ==)
+| | | | read ((GHC.Classes.==) 'b')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | refJoin <hidden>
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'a'
+| | | pushValue ('a')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | read ('a' ==)
+| | | read ((GHC.Classes.==) 'a')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| | | | | fail []
| | | | | minReads=(Left ExceptionFailure)
| | | | | mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Types.[])
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue 'b'
+pushValue ('b')
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-read ('b' ==)
+read ((GHC.Classes.==) 'b')
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | read Term
+| | | 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 (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| | | | | fail []
| | | | | minReads=(Left ExceptionFailure)
| | | | | mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Types.[])
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 0)
mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| | | | pushInput
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
-| | | | read (\u1 -> Term)
+| | | | read (\x_0 -> GHC.Types.True)
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
| | | | popValue
| | | | loadInput
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | pushValue Term
+| | | | pushValue (GHC.Tuple.())
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | pushInput
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
| | | <branch>
| call <hidden>
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue Term
+| pushValue (GHC.Types.[])
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | read Term
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | call <hidden>
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | commit ExceptionFailure
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | | ret
-| | | minReads=(Right 0)
-| | | mayRaise=[]
-| | <ko>
-| | | pushInput
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [(\u1 -> u1)]
-| | | minReads=(Right 0)
-| | | mayRaise=[ExceptionFailure]
-| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
-| | | | | 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 (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
-| | | minReads=(Right 1)
-| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | join <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
| | | | call <hidden>
| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
| | | | call <hidden>
| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | read ((\u1 -> (\u2 -> u1)) Term)
+| | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | swapValue
| | | loadInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | choicesBranch [(Term ==),(Term ==),(Term ==),(Term ==),(Term ==),(Term ==),(Term ==)]
+| | | choicesBranch [((GHC.Classes.==) '<'),((GHC.Classes.==) '>'),((GHC.Classes.==) '+'),((GHC.Classes.==) '-'),((GHC.Classes.==) ','),((GHC.Classes.==) '.'),((GHC.Classes.==) '[')]
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Term
+| | | | | pushValue (Parsers.Brainfuck.Types.Backward)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\u1 -> (\u2 -> u1)) Term)
+| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | <branch>
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Term
+| | | | | pushValue (Parsers.Brainfuck.Types.Forward)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\u1 -> (\u2 -> u1)) Term)
+| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | <branch>
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Term
+| | | | | pushValue (Parsers.Brainfuck.Types.Increment)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\u1 -> (\u2 -> u1)) Term)
+| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | <branch>
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Term
+| | | | | pushValue (Parsers.Brainfuck.Types.Decrement)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\u1 -> (\u2 -> u1)) Term)
+| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | <branch>
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Term
+| | | | | pushValue (Parsers.Brainfuck.Types.Input)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\u1 -> (\u2 -> u1)) Term)
+| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | <branch>
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Term
+| | | | | pushValue (Parsers.Brainfuck.Types.Output)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\u1 -> (\u2 -> u1)) Term)
+| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | refJoin <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | <branch>
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ((\u1 -> (\u2 -> u1)) Term)
+| | | | | read ((\x_0 -> \x_1 -> x_0) GHC.Types.True)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | call <hidden>
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Term
+| | | | | pushValue (Parsers.Brainfuck.Types.Loop)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | call <hidden>
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue ']'
+| | | | | pushValue (']')
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read (']' ==)
+| | | | | read ((GHC.Classes.==) ']')
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | refJoin <hidden>
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
let <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| 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 Term
+| pushValue (GHC.Tuple.())
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| pushValue Term
+| pushValue (GHC.Tuple.())
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| minReads=(Right 0)
| mayRaise=[]
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> u1)
+pushValue (\x_0 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | read Term
+| | | read (Parsers.Nandlang.nandIdentLetter)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
| | | catch ExceptionFailure
| | | minReads=(Right 18)
| | | mayRaise=[ExceptionFailure]
| | | | <ok>
-| | | | | pushValue cons
+| | | | | pushValue ((GHC.Types.:))
| | | | | minReads=(Right 18)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 18)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'f'
+| | | | | pushValue ('f')
| | | | | minReads=(Right 18)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 18)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ('f' ==)
+| | | | | read ((GHC.Classes.==) 'f')
| | | | | minReads=(Right 18)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 17)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 17)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue cons
+| | | | | pushValue ((GHC.Types.:))
| | | | | minReads=(Right 17)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 17)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'u'
+| | | | | pushValue ('u')
| | | | | minReads=(Right 17)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 17)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ('u' ==)
+| | | | | read ((GHC.Classes.==) 'u')
| | | | | minReads=(Right 17)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 16)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 16)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue cons
+| | | | | pushValue ((GHC.Types.:))
| | | | | minReads=(Right 16)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 16)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'n'
+| | | | | pushValue ('n')
| | | | | minReads=(Right 16)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 16)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ('n' ==)
+| | | | | read ((GHC.Classes.==) 'n')
| | | | | minReads=(Right 16)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 15)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 15)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue cons
+| | | | | pushValue ((GHC.Types.:))
| | | | | minReads=(Right 15)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 15)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'c'
+| | | | | pushValue ('c')
| | | | | minReads=(Right 15)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 15)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ('c' ==)
+| | | | | read ((GHC.Classes.==) 'c')
| | | | | minReads=(Right 15)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 14)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 14)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue cons
+| | | | | pushValue ((GHC.Types.:))
| | | | | minReads=(Right 14)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 14)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 't'
+| | | | | pushValue ('t')
| | | | | minReads=(Right 14)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 14)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ('t' ==)
+| | | | | read ((GHC.Classes.==) 't')
| | | | | minReads=(Right 14)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 13)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 13)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue cons
+| | | | | pushValue ((GHC.Types.:))
| | | | | minReads=(Right 13)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 13)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'i'
+| | | | | pushValue ('i')
| | | | | minReads=(Right 13)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 13)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ('i' ==)
+| | | | | read ((GHC.Classes.==) 'i')
| | | | | minReads=(Right 13)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 12)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 12)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue cons
+| | | | | pushValue ((GHC.Types.:))
| | | | | minReads=(Right 12)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 12)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'o'
+| | | | | pushValue ('o')
| | | | | minReads=(Right 12)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 12)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ('o' ==)
+| | | | | read ((GHC.Classes.==) 'o')
| | | | | minReads=(Right 12)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 11)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 11)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue cons
+| | | | | pushValue ((GHC.Types.:))
| | | | | minReads=(Right 11)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 11)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue 'n'
+| | | | | pushValue ('n')
| | | | | minReads=(Right 11)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 11)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | read ('n' ==)
+| | | | | read ((GHC.Classes.==) 'n')
| | | | | minReads=(Right 11)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue Term
+| | | | | pushValue (GHC.Types.[])
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
| | | | | commit ExceptionFailure
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
| | | | | call <hidden>
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
| | | | | call <hidden>
| | | | | minReads=(Right 10)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 8)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 8)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 8)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 8)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 8)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 8)
| | | | | mayRaise=[ExceptionFailure]
| | | | | call <hidden>
| | | | | minReads=(Right 8)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 6)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 6)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 6)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 6)
| | | | | mayRaise=[ExceptionFailure]
| | | | | call <hidden>
| | | | | minReads=(Right 6)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
| | | | | join <hidden>
| | | | | minReads=(Right 6)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 6)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 6)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 6)
| | | | | | mayRaise=[ExceptionFailure]
| | | | | | call <hidden>
| | | | | | minReads=(Right 6)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 4)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 4)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 4)
| | | | | | mayRaise=[ExceptionFailure]
| | | | | | call <hidden>
| | | | | | minReads=(Right 4)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[ExceptionFailure]
| | | | | | call <hidden>
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
| | | | | | commit ExceptionFailure
| | | | | minReads=(Right 0)
| | | | | mayRaise=[ExceptionFailure]
| | | | | | <ok>
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue Term
+| | | | | | | pushValue (GHC.Tuple.())
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\u1 -> u1)
+| | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue ':'
+| | | | | | | pushValue (':')
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | read (':' ==)
+| | | | | | | read ((GHC.Classes.==) ':')
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | call <hidden>
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
| | | | | | | call <hidden>
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
| | | | | | | commit ExceptionFailure
| | | | | | | pushInput
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value Term
+| | | | | | | 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 [(\u1 -> u1)]
+| | | | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | <branch>
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | join <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
| | | | call <hidden>
| | | | minReads=(Right 0)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | <ok>
-| | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | catch ExceptionFailure
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | <ok>
-| | | | | | | | | | | pushValue cons
+| | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue 'i'
+| | | | | | | | | | | pushValue ('i')
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | read ('i' ==)
+| | | | | | | | | | | read ((GHC.Classes.==) 'i')
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue cons
+| | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue 'f'
+| | | | | | | | | | | pushValue ('f')
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | read ('f' ==)
+| | | | | | | | | | | read ((GHC.Classes.==) 'f')
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | pushValue Term
+| | | | | | | | | | | pushValue (GHC.Types.[])
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | commit ExceptionFailure
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | call <hidden>
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | commit ExceptionFailure
| | | | | | | | | pushInput
| | | | | | | | | minReads=(Right 11)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value Term
+| | | | | | | | | 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 [(\u1 -> u1)]
+| | | | | | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | | | | | minReads=(Right 11)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | <branch>
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | catch ExceptionFailure
| | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | <ok>
-| | | | | | | | | | | | | pushValue cons
+| | | | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'w'
+| | | | | | | | | | | | | pushValue ('w')
| | | | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ('w' ==)
+| | | | | | | | | | | | | read ((GHC.Classes.==) 'w')
| | | | | | | | | | | | | minReads=(Right 11)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 10)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 10)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue cons
+| | | | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | | | minReads=(Right 10)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | minReads=(Right 10)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'h'
+| | | | | | | | | | | | | pushValue ('h')
| | | | | | | | | | | | | minReads=(Right 10)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 10)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ('h' ==)
+| | | | | | | | | | | | | read ((GHC.Classes.==) 'h')
| | | | | | | | | | | | | minReads=(Right 10)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 9)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 9)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue cons
+| | | | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | | | minReads=(Right 9)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | minReads=(Right 9)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'i'
+| | | | | | | | | | | | | pushValue ('i')
| | | | | | | | | | | | | minReads=(Right 9)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 9)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ('i' ==)
+| | | | | | | | | | | | | read ((GHC.Classes.==) 'i')
| | | | | | | | | | | | | minReads=(Right 9)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue cons
+| | | | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'l'
+| | | | | | | | | | | | | pushValue ('l')
| | | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ('l' ==)
+| | | | | | | | | | | | | read ((GHC.Classes.==) 'l')
| | | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 7)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 7)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue cons
+| | | | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | | | minReads=(Right 7)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | minReads=(Right 7)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue 'e'
+| | | | | | | | | | | | | pushValue ('e')
| | | | | | | | | | | | | minReads=(Right 7)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 7)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | read ('e' ==)
+| | | | | | | | | | | | | read ((GHC.Classes.==) 'e')
| | | | | | | | | | | | | minReads=(Right 7)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue Term
+| | | | | | | | | | | | | pushValue (GHC.Types.[])
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | | commit ExceptionFailure
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | | | refJoin <hidden>
| | | | | | | pushInput
| | | | | | | minReads=(Right 8)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value Term
+| | | | | | | 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 [(\u1 -> u1)]
+| | | | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | | | minReads=(Right 8)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | <branch>
| | | | | | | | | minReads=(Right 8)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | <ok>
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | join <hidden>
| | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | minReads=(Right 8)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 6)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | | | | | | | | | | 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 (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue '='
+| | | | | | | | | | | | pushValue ('=')
| | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | read ('=' ==)
+| | | | | | | | | | | | read ((GHC.Classes.==) '=')
| | | | | | | | | | | | minReads=(Right 4)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | | | | | | | | | | 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 (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | | commit ExceptionFailure
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | <ok>
-| | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue Term
+| | | | | | | | | | | | | pushValue (GHC.Tuple.())
| | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | | catch ExceptionFailure
| | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | | | <ok>
-| | | | | | | | | | | | | | | pushValue cons
+| | | | | | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue 'v'
+| | | | | | | | | | | | | | | pushValue ('v')
| | | | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | read ('v' ==)
+| | | | | | | | | | | | | | | read ((GHC.Classes.==) 'v')
| | | | | | | | | | | | | | | minReads=(Right 3)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue cons
+| | | | | | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue 'a'
+| | | | | | | | | | | | | | | pushValue ('a')
| | | | | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | read ('a' ==)
+| | | | | | | | | | | | | | | read ((GHC.Classes.==) 'a')
| | | | | | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue cons
+| | | | | | | | | | | | | | | pushValue ((GHC.Types.:))
| | | | | | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | pushValue 'r'
+| | | | | | | | | | | | | | | pushValue ('r')
| | | | | | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | read ('r' ==)
+| | | | | | | | | | | | | | | read ((GHC.Classes.==) 'r')
| | | | | | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | pushValue Term
+| | | | | | | | | | | | | | | pushValue (GHC.Types.[])
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | | | | | commit ExceptionFailure
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | | | | | call <hidden>
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | | | | | commit ExceptionFailure
| | | | | | | | | | | | | pushInput
| | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | | | lift2Value Term
+| | | | | | | | | | | | | 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 [(\u1 -> u1)]
+| | | | | | | | | | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | | | <branch>
| | | | | pushInput
| | | | | minReads=(Right 4)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value Term
+| | | | | 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 [(\u1 -> u1)]
+| | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | minReads=(Right 4)
| | | | | mayRaise=[ExceptionFailure]
| | | | | | <branch>
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | call <hidden>
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | call <hidden>
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
| | | | | | | refJoin <hidden>
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | 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 (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | 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 (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | 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 (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | 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 (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 x_2 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue '!'
+| | | pushValue ('!')
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | read ('!' ==)
+| | | read ((GHC.Classes.==) '!')
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue Term
+| | | pushValue (GHC.Tuple.())
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | 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 (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
let <hidden>
minReads=(Right 0)
mayRaise=[]
-| pushValue (\u1 -> (\u2 -> (\u3 -> (u1 u3) u2)))
-| minReads=(Right 0)
-| mayRaise=[]
-| pushValue (\u1 -> (\u2 -> u1))
-| minReads=(Right 0)
-| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| pushValue (GHC.Tuple.())
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 0)
mayRaise=[]
-| pushValue Term
+| pushValue (GHC.Tuple.())
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 0)
mayRaise=[]
-| pushValue Term
+| 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
let <hidden>
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| 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 Term
+| pushValue (GHC.Tuple.())
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| pushValue Term
+| pushValue (GHC.Tuple.())
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| read Term
+| read (GHC.Unicode.isSpace)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-| read Term
+| 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 2)
| | | mayRaise=[ExceptionFailure]
| | | | <ok>
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
| | | | | join <hidden>
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
| | | | | | call <hidden>
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
| | | | | | commit ExceptionFailure
| | | | | minReads=(Right 1)
| | | | | mayRaise=[ExceptionFailure]
| | | | | | <ok>
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue '0'
+| | | | | | | pushValue ('0')
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | read ('0' ==)
+| | | | | | | read ((GHC.Classes.==) '0')
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
| | | | | | | commit ExceptionFailure
| | | | | | | pushInput
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value Term
+| | | | | | | 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 [(\u1 -> u1)]
+| | | | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | <branch>
-| | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | minReads=(Right 1)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue '1'
+| | | | | | | | | pushValue ('1')
| | | | | | | | | minReads=(Right 1)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | minReads=(Right 1)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | read ('1' ==)
+| | | | | | | | | read ((GHC.Classes.==) '1')
| | | | | | | | | minReads=(Right 1)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | minReads=(Right 0)
| | | | | | | | | mayRaise=[]
| | | | | | | | | refJoin <hidden>
| | | | | pushInput
| | | | | minReads=(Right 4)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value Term
+| | | | | 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 [(\u1 -> u1)]
+| | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | minReads=(Right 4)
| | | | | mayRaise=[ExceptionFailure]
| | | | | | <branch>
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\u1 -> u1)
+| | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue '\''
+| | | | | | | pushValue ('\'')
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | read ('\'' ==)
+| | | | | | | read ((GHC.Classes.==) '\'')
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 3)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 3)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | join <hidden>
| | | | | | | minReads=(Right 2)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 2)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 2)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | minReads=(Right 2)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | minReads=(Right 2)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | pushValue '\''
+| | | | | | | | pushValue ('\'')
| | | | | | | | minReads=(Right 2)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 2)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | read ('\'' ==)
+| | | | | | | | read ((GHC.Classes.==) '\'')
| | | | | | | | minReads=(Right 2)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 1)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 1)
| | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | call <hidden>
| | | | | | | | minReads=(Right 1)
| | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 0)
| | | | | | | | mayRaise=[]
-| | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 0)
| | | | | | | | mayRaise=[]
| | | | | | | | refJoin <hidden>
| | | | | | | minReads=(Right 1)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | <ok>
-| | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | minReads=(Right 1)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | minReads=(Right 1)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | minReads=(Right 1)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | read Term
+| | | | | | | | | read (Parsers.Nandlang.nandStringLetter)
| | | | | | | | | minReads=(Right 1)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | minReads=(Right 0)
| | | | | | | | | mayRaise=[]
| | | | | | | | | call <hidden>
| | | | | | | | | minReads=(Right 0)
| | | | | | | | | mayRaise=[]
-| | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | minReads=(Right 0)
| | | | | | | | | mayRaise=[]
| | | | | | | | | commit ExceptionFailure
| | | | | | | | | pushInput
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value Term
+| | | | | | | | | 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 [(\u1 -> u1)]
+| | | | | | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | <branch>
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue '\\'
+| | | | | | | | | | | pushValue ('\\')
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | read ('\\' ==)
+| | | | | | | | | | | read ((GHC.Classes.==) '\\')
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 1)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | read Term
+| | | | | | | | | | | 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 (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | call <hidden>
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | refJoin <hidden>
| | | pushInput
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
| | | | | call <hidden>
| | | | | minReads=(Right 2)
| | | | | mayRaise=[ExceptionFailure]
-| | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[ExceptionFailure]
| | | | | join <hidden>
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
| | | | | | ret
| | | | | minReads=(Right 0)
| | | | | mayRaise=[ExceptionFailure]
| | | | | | <ok>
-| | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | pushValue Term
+| | | | | | | pushValue (GHC.Tuple.())
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | join <hidden>
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[]
-| | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | minReads=(Right 0)
| | | | | | | | mayRaise=[]
| | | | | | | | commit ExceptionFailure
| | | | | | | minReads=(Right 4)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | <ok>
-| | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | minReads=(Right 4)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | minReads=(Right 4)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | minReads=(Right 4)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | minReads=(Right 4)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | call <hidden>
| | | | | | | | | minReads=(Right 4)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | join <hidden>
| | | | | | | | | minReads=(Right 2)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | call <hidden>
| | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | mayRaise=[]
| | | | | | | | | | commit ExceptionFailure
| | | | | | | | | minReads=(Right 0)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | <ok>
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue Term
+| | | | | | | | | | | pushValue (GHC.Tuple.())
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | call <hidden>
| | | | | | | | | | | minReads=(Right 2)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue (\u1 -> u1)
+| | | | | | | | | | | pushValue (\x_0 -> x_0)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | | | | | | | | | 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 (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | call <hidden>
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | call <hidden>
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
-| | | | | | | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[]
| | | | | | | | | | | commit ExceptionFailure
| | | | | | | | | | | pushInput
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | | | lift2Value Term
+| | | | | | | | | | | 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 [(\u1 -> u1)]
+| | | | | | | | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | | | | | | | minReads=(Right 0)
| | | | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | | | <branch>
| | | | | | | | | pushInput
| | | | | | | | | minReads=(Right 5)
| | | | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | | | lift2Value Term
+| | | | | | | | | 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 [(\u1 -> u1)]
+| | | | | | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | | | | | minReads=(Right 5)
| | | | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | | | <branch>
| | | | | | | pushInput
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[ExceptionFailure]
-| | | | | | | lift2Value Term
+| | | | | | | 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 [(\u1 -> u1)]
+| | | | | | | choicesBranch [(\x_0 -> x_0)]
| | | | | | | minReads=(Right 0)
| | | | | | | mayRaise=[ExceptionFailure]
| | | | | | | | <branch>
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue '('
+| pushValue ('(')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| read ('(' ==)
+| read ((GHC.Classes.==) '(')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue ')'
+| pushValue (')')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| read (')' ==)
+| read ((GHC.Classes.==) ')')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue ','
+| pushValue (',')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| read (',' ==)
+| read ((GHC.Classes.==) ',')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue ';'
+| pushValue (';')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| read (';' ==)
+| read ((GHC.Classes.==) ';')
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| join <hidden>
| minReads=(Right 0)
| mayRaise=[]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
| | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 5)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue Term
+| | | pushValue (GHC.Tuple.())
| | | minReads=(Right 5)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 5)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 5)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| 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 (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| catch ExceptionFailure
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | read Term
+| | | read (Parsers.Nandlang.nandIdentStart)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> u1)
+| | | pushValue (\x_0 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| | | 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 (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | commit ExceptionFailure
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | ret
let <hidden>
minReads=(Right 4)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| pushValue '{'
+| pushValue ('{')
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| read ('{' ==)
+| read ((GHC.Classes.==) '{')
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 3)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 3)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 3)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| 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 (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue '}'
+| pushValue ('}')
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| read ('}' ==)
+| read ((GHC.Classes.==) '}')
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
let <hidden>
minReads=(Right 5)
mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
-| pushValue '['
+| pushValue ('[')
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
-| read ('[' ==)
+| read ((GHC.Classes.==) '[')
| minReads=(Right 5)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 2)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> u1)
+| pushValue (\x_0 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+| 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 Term
+| pushValue (GHC.Tuple.())
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
| call <hidden>
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue Term
+| pushValue (GHC.Tuple.())
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue ']'
+| pushValue (']')
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| read (']' ==)
+| read ((GHC.Classes.==) ']')
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| call <hidden>
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| minReads=(Right 0)
| mayRaise=[]
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> u1)
+pushValue (\x_0 -> x_0)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 1)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> u1)
+pushValue (\x_0 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue ((\u1 -> (\u2 -> (\u3 -> (u1 u3) u2))) (\u1 -> (\u2 -> u1 u2)))
+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 (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
call <hidden>
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 0)
mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| | | | pushInput
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
-| | | | read (\u1 -> Term)
+| | | | read (\x_0 -> GHC.Types.True)
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
| | | | popValue
| | | | loadInput
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | pushValue Term
+| | | | pushValue (GHC.Tuple.())
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | pushInput
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
| | | <branch>
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 2)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue 'c'
+| pushValue ('c')
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| read ('c' ==)
+| read ((GHC.Classes.==) 'c')
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
minReads=(Right 1)
mayRaise=[ExceptionFailure]
| <ok>
-| | pushValue (\u1 -> (\u2 -> u1))
+| | pushValue (\x_0 -> \x_1 -> x_0)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
+| | pushValue ('a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | read ('a' ==)
+| | read ((GHC.Classes.==) 'a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
| | commit ExceptionFailure
| | pushInput
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
| | | <branch>
-| | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'b'
+| | | | pushValue ('b')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | read ('b' ==)
+| | | | read ((GHC.Classes.==) 'b')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | refJoin <hidden>
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 2)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 2)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 1)
mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue (\u1 -> (\u2 -> u1))
+| pushValue (\x_0 -> \x_1 -> x_0)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| pushValue 'd'
+| pushValue ('d')
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| read ('d' ==)
+| read ((GHC.Classes.==) 'd')
| minReads=(Right 1)
| mayRaise=[ExceptionFailure]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
| | | <ok>
-| | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'a'
+| | | | pushValue ('a')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | read ('a' ==)
+| | | | read ((GHC.Classes.==) 'a')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | | | pushInput
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value Term
+| | | | 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 [(\u1 -> u1)]
+| | | | choicesBranch [(\x_0 -> x_0)]
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
| | | | | <branch>
-| | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue 'b'
+| | | | | | pushValue ('b')
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | read ('b' ==)
+| | | | | | read ((GHC.Classes.==) 'b')
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
| | | | | | refJoin <hidden>
| | pushInput
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
| | | <branch>
-| | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'c'
+| | | | pushValue ('c')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | read ('c' ==)
+| | | | read ((GHC.Classes.==) 'c')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | refJoin <hidden>
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 3)
mayRaise=[ExceptionFailure]
catch ExceptionFailure
minReads=(Right 3)
mayRaise=[ExceptionFailure]
| <ok>
-| | pushValue cons
+| | pushValue ((GHC.Types.:))
| | minReads=(Right 3)
| | mayRaise=[ExceptionFailure]
-| | pushValue (\u1 -> (\u2 -> u1))
+| | pushValue (\x_0 -> \x_1 -> x_0)
| | minReads=(Right 3)
| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
+| | pushValue ('a')
| | minReads=(Right 3)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 3)
| | mayRaise=[ExceptionFailure]
-| | read ('a' ==)
+| | read ((GHC.Classes.==) 'a')
| | minReads=(Right 3)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | pushValue cons
+| | pushValue ((GHC.Types.:))
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | pushValue (\u1 -> (\u2 -> u1))
+| | pushValue (\x_0 -> \x_1 -> x_0)
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | pushValue 'b'
+| | pushValue ('b')
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | read ('b' ==)
+| | read ((GHC.Classes.==) 'b')
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | pushValue cons
+| | pushValue ((GHC.Types.:))
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | pushValue (\u1 -> (\u2 -> u1))
+| | pushValue (\x_0 -> \x_1 -> x_0)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | pushValue 'c'
+| | pushValue ('c')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | read ('c' ==)
+| | read ((GHC.Classes.==) 'c')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
-| | pushValue Term
+| | pushValue (GHC.Types.[])
| | minReads=(Right 0)
| | mayRaise=[]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
| | commit ExceptionFailure
| | minReads=(Right 0)
| | mayRaise=[]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
| | ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'a'
+| | | pushValue ('a')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | read ('a' ==)
+| | | read ((GHC.Classes.==) 'a')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| | | | | fail []
| | | | | minReads=(Left ExceptionFailure)
| | | | | mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Types.[])
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'a'
+| | | pushValue ('a')
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | read ('a' ==)
+| | | read ((GHC.Classes.==) 'a')
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'b'
+| | | pushValue ('b')
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | read ('b' ==)
+| | | read ((GHC.Classes.==) 'b')
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'c'
+| | | pushValue ('c')
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | read ('c' ==)
+| | | read ((GHC.Classes.==) 'c')
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'd'
+| | | pushValue ('d')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | read ('d' ==)
+| | | read ((GHC.Classes.==) 'd')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | pushValue Term
+| | | pushValue (GHC.Types.[])
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | fail []
| | | minReads=(Left ExceptionFailure)
| | | mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 4)
mayRaise=[ExceptionFailure]
-pushValue cons
+pushValue ((GHC.Types.:))
minReads=(Right 4)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 4)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Types.[])
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[]
ret
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| minReads=(Right 4)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'a'
+| | | pushValue ('a')
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | read ('a' ==)
+| | | read ((GHC.Classes.==) 'a')
| | | minReads=(Right 4)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'b'
+| | | pushValue ('b')
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | read ('b' ==)
+| | | read ((GHC.Classes.==) 'b')
| | | minReads=(Right 3)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'c'
+| | | pushValue ('c')
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | read ('c' ==)
+| | | read ((GHC.Classes.==) 'c')
| | | minReads=(Right 2)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'd'
+| | | pushValue ('d')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | read ('d' ==)
+| | | read ((GHC.Classes.==) 'd')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | pushValue Term
+| | | pushValue (GHC.Types.[])
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | fail []
| | | minReads=(Left ExceptionFailure)
| | | mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 4)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 4)
mayRaise=[ExceptionFailure]
-pushValue cons
+pushValue ((GHC.Types.:))
minReads=(Right 4)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 4)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Types.[])
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 0)
mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| | | | pushInput
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
-| | | | read (\u1 -> Term)
+| | | | read (\x_0 -> GHC.Types.True)
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
| | | | popValue
| | | | loadInput
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | pushValue Term
+| | | | pushValue (GHC.Tuple.())
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | pushInput
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
| | | <branch>
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 2)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 0)
mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
minReads=(Right 2)
mayRaise=[ExceptionFailure]
| <ok>
-| | pushValue cons
+| | pushValue ((GHC.Types.:))
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | pushValue (\u1 -> (\u2 -> u1))
+| | pushValue (\x_0 -> \x_1 -> x_0)
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
+| | pushValue ('a')
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | read ('a' ==)
+| | read ((GHC.Classes.==) 'a')
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | pushValue cons
+| | pushValue ((GHC.Types.:))
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | pushValue (\u1 -> (\u2 -> u1))
+| | pushValue (\x_0 -> \x_1 -> x_0)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | pushValue 'a'
+| | pushValue ('a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | read ('a' ==)
+| | read ((GHC.Classes.==) 'a')
| | minReads=(Right 1)
| | mayRaise=[ExceptionFailure]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
-| | pushValue Term
+| | pushValue (GHC.Types.[])
| | minReads=(Right 0)
| | mayRaise=[]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
-| | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | minReads=(Right 0)
| | mayRaise=[]
| | commit ExceptionFailure
| | pushInput
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
| | | <branch>
-| | | | pushValue cons
+| | | | pushValue ((GHC.Types.:))
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'a'
+| | | | pushValue ('a')
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | read ('a' ==)
+| | | | read ((GHC.Classes.==) 'a')
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue cons
+| | | | pushValue ((GHC.Types.:))
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'b'
+| | | | pushValue ('b')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | read ('b' ==)
+| | | | read ((GHC.Classes.==) 'b')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | pushValue Term
+| | | | pushValue (GHC.Types.[])
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | refJoin <hidden>
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 2)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 0)
mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
| | | <ok>
-| | | | pushValue cons
+| | | | pushValue ((GHC.Types.:))
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'a'
+| | | | pushValue ('a')
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | read ('a' ==)
+| | | | read ((GHC.Classes.==) 'a')
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue cons
+| | | | pushValue ((GHC.Types.:))
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | pushValue 'a'
+| | | | pushValue ('a')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | read ('a' ==)
+| | | | read ((GHC.Classes.==) 'a')
| | | | minReads=(Right 1)
| | | | mayRaise=[ExceptionFailure]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | pushValue Term
+| | | | pushValue (GHC.Types.[])
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | pushInput
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Right 2)
| | mayRaise=[ExceptionFailure]
| | | <branch>
| | | | minReads=(Right 2)
| | | | mayRaise=[ExceptionFailure]
| | | | | <ok>
-| | | | | | pushValue cons
+| | | | | | pushValue ((GHC.Types.:))
| | | | | | minReads=(Right 2)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | minReads=(Right 2)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue 'a'
+| | | | | | pushValue ('a')
| | | | | | minReads=(Right 2)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 2)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | read ('a' ==)
+| | | | | | read ((GHC.Classes.==) 'a')
| | | | | | minReads=(Right 2)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue cons
+| | | | | | pushValue ((GHC.Types.:))
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue (\u1 -> (\u2 -> u1))
+| | | | | | pushValue (\x_0 -> \x_1 -> x_0)
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | pushValue 'b'
+| | | | | | pushValue ('b')
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | read ('b' ==)
+| | | | | | read ((GHC.Classes.==) 'b')
| | | | | | minReads=(Right 1)
| | | | | | mayRaise=[ExceptionFailure]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
-| | | | | | pushValue Term
+| | | | | | pushValue (GHC.Types.[])
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
-| | | | | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | | | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | | | | minReads=(Right 0)
| | | | | | mayRaise=[]
| | | | | | commit ExceptionFailure
| minReads=(Right 0)
| mayRaise=[ExceptionFailure]
| | <ok>
-| | | pushValue (\u1 -> (\u2 -> (\u3 -> u1 (u2 u3))))
+| | | pushValue (\x_0 -> \x_1 -> \x_2 -> x_0 (x_1 x_2))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue cons
+| | | pushValue ((GHC.Types.:))
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue (\u1 -> (\u2 -> u1))
+| | | pushValue (\x_0 -> \x_1 -> x_0)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | pushValue 'r'
+| | | pushValue ('r')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | read ('r' ==)
+| | | read ((GHC.Classes.==) 'r')
| | | minReads=(Right 1)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | call <hidden>
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value (\u1 -> (\u2 -> u1 u2))
+| | | lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| | | minReads=(Right 0)
| | | mayRaise=[]
| | | commit ExceptionFailure
| | | pushInput
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
-| | | lift2Value Term
+| | | 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 [(\u1 -> u1)]
+| | | choicesBranch [(\x_0 -> x_0)]
| | | minReads=(Right 0)
| | | mayRaise=[ExceptionFailure]
| | | | <branch>
-| | | | | pushValue (\u1 -> u1)
+| | | | | pushValue (\x_0 -> x_0)
| | | | | minReads=(Right 0)
| | | | | mayRaise=[]
| | | | | ret
| | | | | fail []
| | | | | minReads=(Left ExceptionFailure)
| | | | | mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue (\u1 -> (\u2 -> u1))
+pushValue (\x_0 -> \x_1 -> x_0)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
call <hidden>
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-pushValue Term
+pushValue (GHC.Types.[])
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
-lift2Value (\u1 -> (\u2 -> u1 u2))
+lift2Value (\x_0 -> \x_1 -> x_0 x_1)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 0)
mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| | | | pushInput
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
-| | | | read (\u1 -> Term)
+| | | | read (\x_0 -> GHC.Types.True)
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
| | | | popValue
| | | | loadInput
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | pushValue Term
+| | | | pushValue (GHC.Tuple.())
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | pushInput
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
| | | <branch>
-pushValue Term
+pushValue (GHC.Show.show)
minReads=(Right 0)
mayRaise=[ExceptionFailure]
join <hidden>
minReads=(Right 0)
mayRaise=[]
-| lift2Value (\u1 -> (\u2 -> u1 u2))
+| lift2Value (\x_0 -> \x_1 -> x_0 x_1)
| minReads=(Right 0)
| mayRaise=[]
| ret
| | | | pushInput
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
-| | | | read (\u1 -> Term)
+| | | | read (\x_0 -> GHC.Types.True)
| | | | minReads=(Left ExceptionFailure)
| | | | mayRaise=[ExceptionFailure]
| | | | popValue
| | | | loadInput
| | | | minReads=(Right 0)
| | | | mayRaise=[]
-| | | | pushValue Term
+| | | | pushValue (GHC.Tuple.())
| | | | minReads=(Right 0)
| | | | mayRaise=[]
| | | | commit ExceptionFailure
| | pushInput
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
-| | lift2Value Term
+| | 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 [(\u1 -> u1)]
+| | choicesBranch [(\x_0 -> x_0)]
| | minReads=(Left ExceptionFailure)
| | mayRaise=[ExceptionFailure]
| | | <branch>
in if readMore init
then
let !(# c, cs #) = readNext init
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let _ = "resume"
in finalRet
c,
cs
#) = readNext failInp
- in if ('b' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'b' c
then
let _ = "resume"
in join
in if readMore init
then
let !(# c, cs #) = readNext init
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let _ = "resume"
in join
c,
cs
#) = readNext inp
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
name
( let _ = "suspend"
farInp
farExp
( let _ = "resume.genCode"
- in \x -> 'a' GHC.Types.: v x
+ in \x -> (GHC.Types.:) 'a' (v x)
)
inp
)
c,
cs
#) = readNext inp
- in if ('b' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'b' c
then
let _ = "resume"
in finalRet
farInp
farExp
( let _ = "resume.genCode"
- in \x -> c GHC.Types.: v x
+ in \x -> (GHC.Types.:) c (v x)
)
inp
)
farInp
farExp
( let _ = "resume.genCode"
- in \x -> v GHC.Types.: v x
+ in \x -> (GHC.Types.:) v (v x)
)
inp
)
#) = readNext inp
in if (\x -> \x -> x) GHC.Types.True c
then
- if '<' GHC.Classes.== c
+ if (GHC.Classes.==) '<' c
then
let _ = "choicesBranch.then"
in let readFail = readFail
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
else
let _ = "choicesBranch.else"
- in if '>' GHC.Classes.== c
+ in if (GHC.Classes.==) '>' c
then
let _ = "choicesBranch.then"
in let readFail = readFail
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
else
let _ = "choicesBranch.else"
- in if '+' GHC.Classes.== c
+ in if (GHC.Classes.==) '+' c
then
let _ = "choicesBranch.then"
in let readFail = readFail
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
else
let _ = "choicesBranch.else"
- in if '-' GHC.Classes.== c
+ in if (GHC.Classes.==) '-' c
then
let _ = "choicesBranch.then"
in let readFail = readFail
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
else
let _ = "choicesBranch.else"
- in if ',' GHC.Classes.== c
+ in if (GHC.Classes.==) ',' c
then
let _ = "choicesBranch.then"
in let readFail = readFail
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
else
let _ = "choicesBranch.else"
- in if '.' GHC.Classes.== c
+ in if (GHC.Classes.==) '.' c
then
let _ = "choicesBranch.then"
in let readFail = readFail
in readFail Symantic.Parser.Grammar.Combinators.ExceptionFailure inp farInp farExp
else
let _ = "choicesBranch.else"
- in if '[' GHC.Classes.== c
+ in if (GHC.Classes.==) '[' c
then
let _ = "choicesBranch.then"
in let readFail = readFail
c,
cs
#) = readNext inp
- in if (']' GHC.Classes.==) c
+ in if (GHC.Classes.==) ']' c
then
let _ = "resume"
in join
c,
cs
#) = readNext inp
- in if ('(' GHC.Classes.==) c
+ in if (GHC.Classes.==) '(' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if (')' GHC.Classes.==) c
+ in if (GHC.Classes.==) ')' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if (',' GHC.Classes.==) c
+ in if (GHC.Classes.==) ',' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if (';' GHC.Classes.==) c
+ in if (GHC.Classes.==) ';' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if ('{' GHC.Classes.==) c
+ in if (GHC.Classes.==) '{' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if ('}' GHC.Classes.==) c
+ in if (GHC.Classes.==) '}' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if ('[' GHC.Classes.==) c
+ in if (GHC.Classes.==) '[' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if (']' GHC.Classes.==) c
+ in if (GHC.Classes.==) ']' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext failInp
- in if ('\'' GHC.Classes.==) c
+ in if (GHC.Classes.==) '\'' c
then
let join = \farInp farExp v (!inp) ->
let readFail = readFail
c,
cs
#) = readNext inp
- in if ('\'' GHC.Classes.==) c
+ in if (GHC.Classes.==) '\'' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext failInp
- in if ('\\' GHC.Classes.==) c
+ in if (GHC.Classes.==) '\\' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext failInp
- in if ('1' GHC.Classes.==) c
+ in if (GHC.Classes.==) '1' c
then
let _ = "resume"
in join
c,
cs
#) = readNext inp
- in if ('0' GHC.Classes.==) c
+ in if (GHC.Classes.==) '0' c
then
let _ = "resume"
in join
c,
cs
#) = readNext inp
- in if ('=' GHC.Classes.==) c
+ in if (GHC.Classes.==) '=' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext failInp
- in if ('v' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'v' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('r' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'r' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext failInp
- in if ('w' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'w' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('h' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'h' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('i' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'i' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('l' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'l' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('e' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'e' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if ('i' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'i' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('f' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'f' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if ('!' GHC.Classes.==) c
+ in if (GHC.Classes.==) '!' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if ('f' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'f' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('u' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'u' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('n' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'n' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('c' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'c' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('t' GHC.Classes.==) c
+ in if (GHC.Classes.==) 't' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('i' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'i' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('o' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'o' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('n' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'n' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if (':' GHC.Classes.==) c
+ in if (GHC.Classes.==) ':' c
then
name
( let _ = "suspend"
c,
cs
#) = readNext inp
- in if ('c' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'c' c
then
let _ = "resume"
in finalRet
c,
cs
#) = readNext failInp
- in if ('b' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'b' c
then
let _ = "resume"
in join
in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
then
let !(# c, cs #) = readNext init
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let _ = "resume"
in join
c,
cs
#) = readNext inp
- in if ('d' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'd' c
then
let _ = "resume"
in finalRet
c,
cs
#) = readNext failInp
- in if ('c' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'c' c
then
let _ = "resume"
in join
c,
cs
#) = readNext failInp
- in if ('b' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'b' c
then
let _ = "resume"
in join
in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
then
let !(# c, cs #) = readNext init
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let _ = "resume"
in join
in if readMore (Symantic.Parser.Machine.Input.shiftRightText 2 init)
then
let !(# c, cs #) = readNext init
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let readFail = readFail
in let !(# c, cs #) = readNext cs
- in if ('b' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'b' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('c' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'c' c
then
let _ = "resume"
in finalRet
init
Data.Set.Internal.empty
( let _ = "resume.genCode"
- in GHC.Show.show ('a' GHC.Types.: ('b' GHC.Types.: ('c' GHC.Types.: GHC.Types . [])))
+ in GHC.Show.show ((GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' GHC.Types . [])))
)
cs
else
c,
cs
#) = readNext inp
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
name
( let _ = "suspend"
farInp
farExp
( let _ = "resume.genCode"
- in \x -> 'a' GHC.Types.: v x
+ in \x -> (GHC.Types.:) 'a' (v x)
)
inp
)
c,
cs
#) = readNext inp
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('b' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'b' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('c' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'c' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('d' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'd' c
then
let _ = "resume"
in ok
init
Data.Set.Internal.empty
( let _ = "resume.genCode"
- in 'a' GHC.Types.: ('b' GHC.Types.: ('c' GHC.Types.: ('d' GHC.Types.: GHC.Types . [])))
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types . [])))
)
cs
else
farInp
farExp
( let _ = "resume.genCode"
- in \x -> v GHC.Types.: v x
+ in \x -> (GHC.Types.:) v (v x)
)
inp
)
farInp
farExp
( let _ = "resume.genCode"
- in GHC.Show.show (v GHC.Types.: v GHC.Types . [])
+ in GHC.Show.show ((GHC.Types.:) v (v GHC.Types . []))
)
inp
)
c,
cs
#) = readNext inp
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('b' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'b' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('c' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'c' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('d' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'd' c
then
let _ = "resume"
in ok
init
Data.Set.Internal.empty
( let _ = "resume.genCode"
- in 'a' GHC.Types.: ('b' GHC.Types.: ('c' GHC.Types.: ('d' GHC.Types.: GHC.Types . [])))
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' ((GHC.Types.:) 'c' ((GHC.Types.:) 'd' GHC.Types . [])))
)
cs
else
farInp
farExp
( let _ = "resume.genCode"
- in \x -> v GHC.Types.: v x
+ in \x -> (GHC.Types.:) v (v x)
)
inp
)
farInp
farExp
( let _ = "resume.genCode"
- in GHC.Show.show (v GHC.Types.: v GHC.Types . [])
+ in GHC.Show.show ((GHC.Types.:) v (v GHC.Types . []))
)
inp
in let _ = "catch ExceptionFailure"
c,
cs
#) = readNext failInp
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let readFail = finalRaise
in let !(#
c,
cs
#) = readNext cs
- in if ('b' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'b' c
then
let _ = "resume"
in join
farInp
farExp
( let _ = "resume.genCode"
- in 'a' GHC.Types.: ('b' GHC.Types.: GHC.Types . [])
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types . [])
)
cs
else
in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
then
let !(# c, cs #) = readNext init
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let readFail = readFail
in let !(# c, cs #) = readNext cs
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let _ = "resume"
in join
init
Data.Set.Internal.empty
( let _ = "resume.genCode"
- in 'a' GHC.Types.: ('a' GHC.Types.: GHC.Types . [])
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types . [])
)
cs
else
c,
cs
#) = readNext failInp
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('b' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'b' c
then
let _ = "resume"
in join
farInp
farExp
( let _ = "resume.genCode"
- in 'a' GHC.Types.: ('b' GHC.Types.: GHC.Types . [])
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'b' GHC.Types . [])
)
cs
else
in if readMore (Symantic.Parser.Machine.Input.shiftRightText 1 init)
then
let !(# c, cs #) = readNext init
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let readFail = readFail
in let !(#
c,
cs
#) = readNext cs
- in if ('a' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'a' c
then
let _ = "resume"
in join
init
Data.Set.Internal.empty
( let _ = "resume.genCode"
- in 'a' GHC.Types.: ('a' GHC.Types.: GHC.Types . [])
+ in (GHC.Types.:) 'a' ((GHC.Types.:) 'a' GHC.Types . [])
)
cs
else
c,
cs
#) = readNext inp
- in if ('r' GHC.Classes.==) c
+ in if (GHC.Classes.==) 'r' c
then
name
( let _ = "suspend"
farInp
farExp
( let _ = "resume.genCode"
- in \x -> 'r' GHC.Types.: v x
+ in \x -> (GHC.Types.:) 'r' (v x)
)
inp
)
import Text.Show (Show(..))
import qualified Data.Functor as Functor
import qualified Parsers.Nandlang
-import qualified Parsers.Brainfuck.SymanticParser
+import qualified Parsers.Brainfuck.SymanticParser.Grammar
import Symantic.Parser
-import qualified Symantic.Parser.Haskell as H
+import qualified Symantic.Univariant.Lang as H
rawGrammars :: Grammarable Char repr => [repr String]
rawGrammars =
- [ H.Term (H.ValueCode show [||show||]) <$> g1
- , H.Term (H.ValueCode show [||show||]) <$> g2
- , H.Term (H.ValueCode show [||show||]) <$> g3
- , H.Term (H.ValueCode show [||show||]) <$> g4
- , H.Term (H.ValueCode show [||show||]) <$> g5
- , H.Term (H.ValueCode show [||show||]) <$> g6
- , H.Term (H.ValueCode show [||show||]) <$> g7
- , H.Term (H.ValueCode show [||show||]) <$> g8
- , H.Term (H.ValueCode show [||show||]) <$> g9
- , H.Term (H.ValueCode show [||show||]) <$> g10
- , H.Term (H.ValueCode show [||show||]) <$> g11
- , H.Term (H.ValueCode show [||show||]) <$> g12
- , H.Term (H.ValueCode show [||show||]) <$> g13
- , H.Term (H.ValueCode show [||show||]) <$> g14
- , H.Term (H.ValueCode show [||show||]) <$> g15
- , H.Term (H.ValueCode show [||show||]) <$> g16
+ [ production show [||show||] <$> g1
+ , production show [||show||] <$> g2
+ , production show [||show||] <$> g3
+ , production show [||show||] <$> g4
+ , production show [||show||] <$> g5
+ , production show [||show||] <$> g6
+ , production show [||show||] <$> g7
+ , production show [||show||] <$> g8
+ , production show [||show||] <$> g9
+ , production show [||show||] <$> g10
+ , production show [||show||] <$> g11
+ , production show [||show||] <$> g12
+ , production show [||show||] <$> g13
+ , production show [||show||] <$> g14
+ , production show [||show||] <$> g15
+ , production show [||show||] <$> g16
]
grammars :: Grammarable Char repr => [repr String]
grammars = observeSharing Functor.<$> rawGrammars
g10 = char 'a' <|> char 'b'
g11 = many (char 'a') <* char 'b'
g12 = many (oneOf ['a', 'b', 'c', 'd']) <* eof
-g13 = Parsers.Brainfuck.SymanticParser.grammar @Char @_
+g13 = Parsers.Brainfuck.SymanticParser.Grammar.grammar @Char @_
g14 = Parsers.Nandlang.grammar
g15 = (char 'a' <|> char 'b') <* char 'c'
g16 = (char 'a' <|> char 'b' <|> char 'c') <* char 'd'