ghc-9.10: The impossible happened, coreToStgExpr - Invalid app head:
Summary
Our code hits an error in the compiler:
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.10.1:
coreToStgExpr - Invalid app head:
((join {
$j2_svnc [Occ=Once2!T[1], Dmd=1C(1,L)]
:: StateT Int (Decoder RealWorld) ()
-> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto))
[LclId[JoinId(1)(Just [!])],
Arity=1,
Str=<1C(1,C(1,C(1,L)))>,
Unf=OtherCon []]
$j2_svnc (eta4_svnd [Occ=Once1, OS=OneShot]
:: StateT Int (Decoder RealWorld) ())
= case -# len_sv47 1# of lvl57_svne { __DEFAULT ->
...
Steps to reproduce
This happens every single time I try to compile this code.
However, the code started off as about 500k lines of code and after spending several days on this I have it down to just under 100k lines of code. I would assume that an acceptable mininal reproduction case is under 1k lines of code. The error output (which I have only given the start of above) is over 6k lines long.
I would love to produce a mininal reproduction case but getting it from 500k to just under 100k already took several days and from here on, it seems to be getting more and more difficult to reduce the size. I would not be surprised if getting it down to 1k lines would take several weeks.
Expected behavior
The compiler should not abort even if the code is invalid. However, this code compiles and works
correctly with ghc-8.10
, ghc-9.6.5
, ghc-9.8.2
and probably others.
What do you expect the reproducer described above to do?
Environment
- GHC version used: 9.10.1 release
Optional:
- Operating System: Linux
- System Architecture: x86_86
- Show closed items
Activity
-
Newest first Oldest first
-
Show all activity Show comments only Show history only
- Erik de Castro Lopo added needs triage label
added needs triage label
- Author Developer
The full error output:
Build profile: -w ghc-9.10.1 -O1 In order, the following will be built (use -v for more details): - ledger-state-9.9.9.9 (bench:address) (first run) Preprocessing benchmark 'address' for ledger-state-9.9.9.9.. Building benchmark 'address' for ledger-state-9.9.9.9.. [1 of 1] Compiling Main ( bench/Address.hs, /home/erikd/IOHK/NewCodeBase/cardano-ledger-min-reproducer/dist-newstyle/build/x86_64-linux/ghc-9.10.1/ledger-state-9.9.9.9/b/address/build/address/address-tmp/Main.o ) <no location info>: error: panic! (the 'impossible' happened) GHC version 9.10.1: coreToStgExpr - Invalid app head: ((join { $j2_svnc [Occ=Once2!T[1], Dmd=1C(1,L)] :: StateT Int (Decoder RealWorld) () -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId[JoinId(1)(Just [!])], Arity=1, Str=<1C(1,C(1,C(1,L)))>, Unf=OtherCon []] $j2_svnc (eta4_svnd [Occ=Once1, OS=OneShot] :: StateT Int (Decoder RealWorld) ()) = case -# len_sv47 1# of lvl57_svne { __DEFAULT -> let { m1_svnf :: ByteArray [LclId, Unf=OtherCon []] m1_svnf = ByteArray ww_sv46 } in let { $s$wd7_svng [Occ=OnceL1!] :: Int# -> Word16# -> (Word16 -> StateT Int (Decoder RealWorld) Word16) -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r) [LclId, Arity=5, Str=<L><L><LC(S,C(1,C(1,C(1,L))))><L><L>, Unf=OtherCon []] $s$wd7_svng = \ (sc_svnh :: Int#) (sc1_svni [Occ=OnceL2] :: Word16#) (sc2_svnj [Occ=OnceL1!] :: Word16 -> StateT Int (Decoder RealWorld) Word16) (eta_svnk :: Version) (@r_suJ3) (eta1_svnl [Occ=OnceL2!] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_suJ3)) -> let { $wkarg1_svnm [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld r_suJ3) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svnm = \ (ww1_svnn :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww1_svnn of ww3_svno { __DEFAULT -> case word8ToWord# ww3_svno of sat_svnp [Occ=Once1] { __DEFAULT -> case and# 128## sat_svnp of { __DEFAULT -> case +# ww1_svnn 1# of sat_svnz [Occ=Once1] { __DEFAULT -> let { sat_svnA [Occ=Once1] :: Int [LclId] sat_svnA = I# sat_svnz } in case word8ToWord# ww3_svno of sat_svnu [Occ=Once1] { __DEFAULT -> case and# 127## sat_svnu of sat_svnv [Occ=Once1] { __DEFAULT -> case word16ToWord# sc1_svni of sat_svnr [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svnr 7# of sat_svns [Occ=Once1] { __DEFAULT -> case and# sat_svns 65535## of sat_svnt [Occ=Once1] { __DEFAULT -> case or# sat_svnt sat_svnv of sat_svnw [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svnw of sat_svnx [Occ=Once1] { __DEFAULT -> let { sat_svny [Occ=Once1] :: Word16 [LclId] sat_svny = W16# sat_svnx } in ((((((sc2_svnj sat_svny) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N :: StateT Int (Decoder RealWorld) Word16 ~R# (Int -> Decoder RealWorld (Word16, Int)))) sat_svnA) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (Version -> Decoder RealWorld (Word16, Int)))) eta_svnk) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_suJ3 eta1_svnl } } } } } } } }; 0## -> case +# ww1_svnn 1# of sat_svnJ [Occ=Once1] { __DEFAULT -> let { sat_svnK [Occ=Once1] :: Int [LclId] sat_svnK = I# sat_svnJ } in case word8ToWord# ww3_svno of sat_svnE [Occ=Once1] { __DEFAULT -> case and# sat_svnE 65535## of sat_svnF [Occ=Once1] { __DEFAULT -> case word16ToWord# sc1_svni of sat_svnB [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svnB 7# of sat_svnC [Occ=Once1] { __DEFAULT -> case and# sat_svnC 65535## of sat_svnD [Occ=Once1] { __DEFAULT -> case or# sat_svnD sat_svnF of sat_svnG [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svnG of sat_svnH [Occ=Once1] { __DEFAULT -> let { sat_svnI [Occ=Once1] :: Word16 [LclId] sat_svnI = W16# sat_svnH } in let { sat_svnL [Occ=Once1] :: (Word16, Int) [LclId] sat_svnL = (sat_svnI, sat_svnK) } in eta1_svnl sat_svnL } } } } } } } } } } } } in case ># sc_svnh lvl57_svne of { __DEFAULT -> $wkarg1_svnm sc_svnh; 1# -> let { sat_svnU [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_suJ3) [LclId] sat_svnU = \ (m6_svnO [Occ=Once1!] :: ((), Int)) -> case m6_svnO of { (_ [Occ=Dead], ww3_svnR [Occ=Once1!]) -> case ww3_svnR of { I# ww4_svnT [Occ=Once1] -> $wkarg1_svnm ww4_svnT } } } in let { sat_svnN [Occ=Once1] :: Int [LclId] sat_svnN = I# sc_svnh } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name2_ruZA lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svnN) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta_svnk) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_suJ3 sat_svnU } } in let { $wd7_svnV [InlPrag=[2], Dmd=LC(L,C(1,C(1,C(1,C(1,L)))))] :: (Word16 -> StateT Int (Decoder RealWorld) Word16) -> Word16# -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r) [LclId[StrictWorker([~, ~, !])], Arity=5, Str=<LC(S,C(1,C(1,C(1,L))))><L><1L><L><L>, Unf=OtherCon []] $wd7_svnV = \ (cont_svnW [Occ=OnceL1!] :: Word16 -> StateT Int (Decoder RealWorld) Word16) (ww1_svnX [Occ=OnceL2, OS=OneShot] :: Word16#) (eta_svnY [Occ=Once1!, OS=OneShot] :: Int) (eta1_svnZ [OS=OneShot] :: Version) (@r_suJ3) (eta2_svo0 [Occ=OnceL2!, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_suJ3)) -> case eta_svnY of wild1_svo1 [Occ=Once1] { I# x_svo2 -> let { $wkarg1_svo3 [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld r_suJ3) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svo3 = \ (ww3_svo4 :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww3_svo4 of ww4_svo5 { __DEFAULT -> case word8ToWord# ww4_svo5 of sat_svo6 [Occ=Once1] { __DEFAULT -> case and# 128## sat_svo6 of { __DEFAULT -> case +# ww3_svo4 1# of sat_svog [Occ=Once1] { __DEFAULT -> let { sat_svoh [Occ=Once1] :: Int [LclId] sat_svoh = I# sat_svog } in case word8ToWord# ww4_svo5 of sat_svob [Occ=Once1] { __DEFAULT -> case and# 127## sat_svob of sat_svoc [Occ=Once1] { __DEFAULT -> case word16ToWord# ww1_svnX of sat_svo8 [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svo8 7# of sat_svo9 [Occ=Once1] { __DEFAULT -> case and# sat_svo9 65535## of sat_svoa [Occ=Once1] { __DEFAULT -> case or# sat_svoa sat_svoc of sat_svod [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svod of sat_svoe [Occ=Once1] { __DEFAULT -> let { sat_svof [Occ=Once1] :: Word16 [LclId] sat_svof = W16# sat_svoe } in ((((((cont_svnW sat_svof) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N :: StateT Int (Decoder RealWorld) Word16 ~R# (Int -> Decoder RealWorld (Word16, Int)))) sat_svoh) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (Version -> Decoder RealWorld (Word16, Int)))) eta1_svnZ) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_suJ3 eta2_svo0 } } } } } } } }; 0## -> case +# ww3_svo4 1# of sat_svoq [Occ=Once1] { __DEFAULT -> let { sat_svor [Occ=Once1] :: Int [LclId] sat_svor = I# sat_svoq } in case word8ToWord# ww4_svo5 of sat_svol [Occ=Once1] { __DEFAULT -> case and# sat_svol 65535## of sat_svom [Occ=Once1] { __DEFAULT -> case word16ToWord# ww1_svnX of sat_svoi [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svoi 7# of sat_svoj [Occ=Once1] { __DEFAULT -> case and# sat_svoj 65535## of sat_svok [Occ=Once1] { __DEFAULT -> case or# sat_svok sat_svom of sat_svon [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svon of sat_svoo [Occ=Once1] { __DEFAULT -> let { sat_svop [Occ=Once1] :: Word16 [LclId] sat_svop = W16# sat_svoo } in let { sat_svos [Occ=Once1] :: (Word16, Int) [LclId] sat_svos = (sat_svop, sat_svor) } in eta2_svo0 sat_svos } } } } } } } } } } } } in case ># x_svo2 lvl57_svne of { __DEFAULT -> $wkarg1_svo3 x_svo2; 1# -> let { sat_svoA [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_suJ3) [LclId] sat_svoA = \ (m6_svou [Occ=Once1!] :: ((), Int)) -> case m6_svou of { (_ [Occ=Dead], ww4_svox [Occ=Once1!]) -> case ww4_svox of { I# ww5_svoz [Occ=Once1] -> $wkarg1_svo3 ww5_svoz } } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name2_ruZA lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) wild1_svo1) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta1_svnZ) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_suJ3 sat_svoA } } } in let { $wd1_svoB [InlPrag=[2], Dmd=LC(L,C(1,C(1,C(1,C(1,L)))))] :: (Word16 -> StateT Int (Decoder RealWorld) Word16) -> Word16# -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r) [LclId[StrictWorker([~, ~, !])], Arity=5, Str=<LC(S,C(1,C(1,C(1,L))))><L><1L><L><L>, Unf=OtherCon []] $wd1_svoB = \ (cont_svoC [Occ=OnceL1!] :: Word16 -> StateT Int (Decoder RealWorld) Word16) (ww1_svoD [Occ=OnceL2, OS=OneShot] :: Word16#) (eta_svoE [Occ=Once1!, OS=OneShot] :: Int) (eta1_svoF [OS=OneShot] :: Version) (@r_suIG) (eta2_svoG [Occ=OnceL2!, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_suIG)) -> case eta_svoE of wild1_svoH [Occ=Once1] { I# x_svoI -> let { $wkarg1_svoJ [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld r_suIG) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svoJ = \ (ww3_svoK :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww3_svoK of ww4_svoL { __DEFAULT -> case word8ToWord# ww4_svoL of sat_svoM [Occ=Once1] { __DEFAULT -> case and# 128## sat_svoM of { __DEFAULT -> case +# ww3_svoK 1# of sat_svoW [Occ=Once1] { __DEFAULT -> let { sat_svoX [Occ=Once1] :: Int [LclId] sat_svoX = I# sat_svoW } in case word8ToWord# ww4_svoL of sat_svoR [Occ=Once1] { __DEFAULT -> case and# 127## sat_svoR of sat_svoS [Occ=Once1] { __DEFAULT -> case word16ToWord# ww1_svoD of sat_svoO [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svoO 7# of sat_svoP [Occ=Once1] { __DEFAULT -> case and# sat_svoP 65535## of sat_svoQ [Occ=Once1] { __DEFAULT -> case or# sat_svoQ sat_svoS of sat_svoT [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svoT of sat_svoU [Occ=Once1] { __DEFAULT -> let { sat_svoV [Occ=Once1] :: Word16 [LclId] sat_svoV = W16# sat_svoU } in ((((((cont_svoC sat_svoV) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N :: StateT Int (Decoder RealWorld) Word16 ~R# (Int -> Decoder RealWorld (Word16, Int)))) sat_svoX) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (Version -> Decoder RealWorld (Word16, Int)))) eta1_svoF) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_suIG eta2_svoG } } } } } } } }; 0## -> case +# ww3_svoK 1# of sat_svp6 [Occ=Once1] { __DEFAULT -> let { sat_svp7 [Occ=Once1] :: Int [LclId] sat_svp7 = I# sat_svp6 } in case word8ToWord# ww4_svoL of sat_svp1 [Occ=Once1] { __DEFAULT -> case and# sat_svp1 65535## of sat_svp2 [Occ=Once1] { __DEFAULT -> case word16ToWord# ww1_svoD of sat_svoY [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svoY 7# of sat_svoZ [Occ=Once1] { __DEFAULT -> case and# sat_svoZ 65535## of sat_svp0 [Occ=Once1] { __DEFAULT -> case or# sat_svp0 sat_svp2 of sat_svp3 [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svp3 of sat_svp4 [Occ=Once1] { __DEFAULT -> let { sat_svp5 [Occ=Once1] :: Word16 [LclId] sat_svp5 = W16# sat_svp4 } in let { sat_svp8 [Occ=Once1] :: (Word16, Int) [LclId] sat_svp8 = (sat_svp5, sat_svp7) } in eta2_svoG sat_svp8 } } } } } } } } } } } } in case ># x_svoI lvl57_svne of { __DEFAULT -> $wkarg1_svoJ x_svoI; 1# -> let { sat_svpg [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_suIG) [LclId] sat_svpg = \ (m6_svpa [Occ=Once1!] :: ((), Int)) -> case m6_svpa of { (_ [Occ=Dead], ww4_svpd [Occ=Once1!]) -> case ww4_svpd of { I# ww5_svpf [Occ=Once1] -> $wkarg1_svoJ ww5_svpf } } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name3_ruZC lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) wild1_svoH) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta1_svoF) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_suIG sat_svpg } } } in case case and# 1## wild_svnb of { __DEFAULT -> Mainnet; 0## -> Testnet } of lvl58_svph { __DEFAULT -> let { $s$wlvl_svpj [Occ=OnceL2!] :: Int# -> Credential 'Payment StandardCrypto -> State# RealWorld -> (# State# RealWorld, DecodeAction RealWorld (Addr StandardCrypto) #) [LclId, Arity=3, Str=<L><L><L>, Unf=OtherCon []] $s$wlvl_svpj = \ (sc_svpk :: Int#) (sc1_svpl [Occ=OnceL6] :: Credential 'Payment StandardCrypto) (eta_svpm [Occ=Once9, OS=OneShot] :: State# RealWorld) -> case and# 64## wild_svnb of { __DEFAULT -> case and# 32## wild_svnb of { __DEFAULT -> let { sat_svpq [Occ=Once1, Dmd=1L] :: Int [LclId] sat_svpq = I# sc_svpk } in let { sat_svpp [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svpp = Addr @StandardCrypto lvl58_svph sc1_svpl (StakeRefNull @StandardCrypto) } in $wlvl1_sv48 sat_svpp sat_svpq eta_svpm; 0## -> let { lvl59_svpr [Occ=OnceL1!] :: Word8 [LclId] lvl59_svpr = case $wunsafeShortByteStringIndex ww_sv46 sc_svpk of ww1_svps [Occ=Once1] { __DEFAULT -> W8# ww1_svps } } in let { $wk1_svpt [InlPrag=[2], Dmd=LC(L,C(1,L))] :: Word32 -> Int -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId[StrictWorker([~, !])], Arity=2, Str=<ML><SL>, Unf=OtherCon []] $wk1_svpt = \ (ww1_svpu [Occ=Once1!] :: Word32) (ww3_svpv [OS=OneShot] :: Int) -> let { lvl60_svpw [Occ=OnceL1!] :: Word8 [LclId] lvl60_svpw = case ww3_svpv of { I# ww4_svpy [Occ=Once1] -> case $wunsafeShortByteStringIndex ww_sv46 ww4_svpy of ww5_svpz [Occ=Once1] { __DEFAULT -> W8# ww5_svpz } } } in let { a4_svpA [Occ=OnceL1!] :: Word64 [LclId] a4_svpA = case ww1_svpu of { W32# x#1_svpC [Occ=Once1] -> case word32ToWord# x#1_svpC of sat_svpD [Occ=Once1] { __DEFAULT -> case wordToWord64# sat_svpD of sat_svpE [Occ=Once1] { __DEFAULT -> W64# sat_svpE } } } } in let { sat_svs9 [Occ=Once1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svs9 = \ (x2_svqD [Occ=Once1!] :: (Word16, Int)) -> case x2_svqD of { (a5_svqF [Occ=Once1!], s'3_svqG) -> let { lvl61_svqH [Occ=OnceL1!] :: Word8 [LclId] lvl61_svqH = case s'3_svqG of { I# ww4_svqJ [Occ=Once1] -> case $wunsafeShortByteStringIndex ww_sv46 ww4_svqJ of ww5_svqK [Occ=Once1] { __DEFAULT -> W8# ww5_svqK } } } in let { ds1_svqL [Occ=OnceL1!] :: Word64 [LclId] ds1_svqL = case a5_svqF of { W16# x#1_svqN [Occ=Once1] -> case word16ToWord# x#1_svqN of sat_svqO [Occ=Once1] { __DEFAULT -> case word2Int# sat_svqO of sat_svqP [Occ=Once1] { __DEFAULT -> case intToInt64# sat_svqP of sat_svqQ [Occ=Once1] { __DEFAULT -> case int64ToWord64# sat_svqQ of sat_svqR [Occ=Once1] { __DEFAULT -> W64# sat_svqR } } } } } } in let { sat_svs8 [Occ=Once1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svs8 = (\ (x3_svrQ [Occ=Once1!] :: (Word16, Int)) (eta1_svrR [Occ=Once1, OS=OneShot] :: State# RealWorld) -> case x3_svrQ of { (a6_svrT [Occ=Once1!], s'4_svrU [Occ=Once1]) -> let { sat_svs6 [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svs6 = case a6_svrT of { W16# x#1_svrW [Occ=Once1] -> case a4_svpA of { W64# unbx_svrY [Occ=Once1] -> case ds1_svqL of { W64# unbx1_svs0 [Occ=Once1] -> case word16ToWord# x#1_svrW of sat_svs1 [Occ=Once1] { __DEFAULT -> case word2Int# sat_svs1 of sat_svs2 [Occ=Once1] { __DEFAULT -> case intToInt64# sat_svs2 of sat_svs3 [Occ=Once1] { __DEFAULT -> case int64ToWord64# sat_svs3 of sat_svs4 [Occ=Once1] { __DEFAULT -> let { sat_svs5 [Occ=Once1] :: Ptr [LclId] sat_svs5 = Ptr unbx_svrY unbx1_svs0 sat_svs4 } in StakeRefPtr @StandardCrypto sat_svs5 } } } } } } } } in let { sat_svs7 [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svs7 = Addr @StandardCrypto lvl58_svph sc1_svpl sat_svs6 } in $wlvl1_sv48 sat_svs7 s'4_svrU eta1_svrR }) `cast` (<(Word16, Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: ((Word16, Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) } in let { cont_svqS [Occ=OnceL1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r) [LclId, Arity=4, Str=<1L><1L><L><LC(S,L)>, Unf=OtherCon []] cont_svqS = \ (acc_svqT [Occ=Once1!] :: Word16) (eta1_svqU [Occ=Once1!, OS=OneShot] :: Int) (eta2_svqV [OS=OneShot] :: Version) (@r_X1H) (eta3_svqW [Occ=OnceL2!, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H)) -> case acc_svqT of { W16# ipv_svqY [Occ=OnceL1] -> case eta1_svqU of wild4_svqZ [Occ=Once1] { I# x_svr0 -> let { $weta_svr1 [InlPrag=[2], Dmd=LC(S,L)] :: Word16 -> Int -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] $weta_svr1 = \ (ww4_svr2 [Occ=OnceL2] :: Word16) (ww5_svr3 [Occ=Once2] :: Int) -> case lvl61_svqH of { W8# x#1_svr5 [Occ=Once1] -> case word8ToWord# x#1_svr5 of sat_svr6 [Occ=Once1] { __DEFAULT -> case and# 252## sat_svr6 of { __DEFAULT -> let { sat_svrd [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svrd = \ (m8_svr8 [Occ=Once1!] :: ((), Int)) -> case m8_svr8 of { (_ [Occ=Dead], s'5_svrb [Occ=Once1]) -> let { sat_svrc [Occ=Once1] :: (Word16, Int) [LclId] sat_svrc = (ww4_svr2, s'5_svrb) } in eta3_svqW sat_svrc } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name3_ruZC lvl38_ruZI) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) ww5_svr3) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svqV) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svrd; 128## -> let { sat_svre [Occ=Once1] :: (Word16, Int) [LclId] sat_svre = (ww4_svr2, ww5_svr3) } in eta3_svqW sat_svre } } } } in let { eta5_svrf [InlPrag=[2], Occ=OnceL1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<1!P(L,L)>, Unf=OtherCon []] eta5_svrf = \ (m7_svrg [Occ=Once1!] :: (Word16, Int)) -> case m7_svrg of { (ww4_svri [Occ=Once1], ww5_svrj [Occ=Once1]) -> $weta_svr1 ww4_svri ww5_svrj } } in let { $wkarg1_svrk [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svrk = \ (ww4_svrl :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww4_svrl of ww5_svrm { __DEFAULT -> case word8ToWord# ww5_svrm of sat_svrn [Occ=Once1] { __DEFAULT -> case and# 128## sat_svrn of { __DEFAULT -> case +# ww4_svrl 1# of sat_svrp [Occ=Once1] { __DEFAULT -> let { sat_svrq [Occ=Once1] :: Int [LclId] sat_svrq = I# sat_svrp } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @Word16 $dMonadFail6_ruYJ name3_ruZC lvl36_ruZG) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N :: StateT Int (Decoder RealWorld) Word16 ~R# (Int -> Decoder RealWorld (Word16, Int)))) sat_svrq) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (Version -> Decoder RealWorld (Word16, Int)))) eta2_svqV) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H eta5_svrf }; 0## -> case +# ww4_svrl 1# of sat_svrz [Occ=Once1] { __DEFAULT -> let { sat_svrA [Occ=Once1] :: Int [LclId] sat_svrA = I# sat_svrz } in case word8ToWord# ww5_svrm of sat_svru [Occ=Once1] { __DEFAULT -> case and# sat_svru 65535## of sat_svrv [Occ=Once1] { __DEFAULT -> case word16ToWord# ipv_svqY of sat_svrr [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svrr 7# of sat_svrs [Occ=Once1] { __DEFAULT -> case and# sat_svrs 65535## of sat_svrt [Occ=Once1] { __DEFAULT -> case or# sat_svrt sat_svrv of sat_svrw [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svrw of sat_svrx [Occ=Once1] { __DEFAULT -> let { sat_svry [Occ=Once1] :: Word16 [LclId] sat_svry = W16# sat_svrx } in $weta_svr1 sat_svry sat_svrA } } } } } } } } } } } } in case ># x_svr0 lvl57_svne of { __DEFAULT -> $wkarg1_svrk x_svr0; 1# -> let { sat_svrI [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svrI = \ (m7_svrC [Occ=Once1!] :: ((), Int)) -> case m7_svrC of { (_ [Occ=Dead], ww5_svrF [Occ=Once1!]) -> case ww5_svrF of { I# ww6_svrH [Occ=Once1] -> $wkarg1_svrk ww6_svrH } } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name3_ruZC lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) wild4_svqZ) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svqV) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svrI } } } } in let { sat_svrP [Occ=Once1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> StateT Int (Decoder RealWorld) Word16 [LclId] sat_svrP = (\ (acc_svrJ [Occ=Once1!] :: Word16) (eta1_svrK [Occ=Once1, OS=OneShot] :: Int) (eta2_svrL [Occ=Once1, OS=OneShot] :: Version) (@r_suIG) (eta3_svrM [Occ=Once1, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_suIG)) -> case acc_svrJ of { W16# ww4_svrO [Occ=Once1] -> $wd1_svoB (cont_svqS `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16))) ww4_svrO eta1_svrK eta2_svrL @r_suIG eta3_svrM }) `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16)) } in $wd1_svoB sat_svrP 0#Word16 s'3_svqG ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version)) @(Addr StandardCrypto) sat_svs8 } } in let { cont_svpF [Occ=OnceL1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r) [LclId, Arity=4, Str=<1L><1L><L><LC(S,L)>, Unf=OtherCon []] cont_svpF = \ (acc_svpG [Occ=Once1!] :: Word16) (eta1_svpH [Occ=Once1!, OS=OneShot] :: Int) (eta2_svpI [OS=OneShot] :: Version) (@r_X1H) (eta3_svpJ [Occ=OnceL2!, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H)) -> case acc_svpG of { W16# ipv_svpL [Occ=OnceL1] -> case eta1_svpH of wild4_svpM [Occ=Once1] { I# x_svpN -> let { $weta_svpO [InlPrag=[2], Dmd=LC(S,L)] :: Word16 -> Int -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] $weta_svpO = \ (ww4_svpP [Occ=OnceL2] :: Word16) (ww5_svpQ [Occ=Once2] :: Int) -> case lvl60_svpw of { W8# x#1_svpS [Occ=Once1] -> case word8ToWord# x#1_svpS of sat_svpT [Occ=Once1] { __DEFAULT -> case and# 252## sat_svpT of { __DEFAULT -> let { sat_svq0 [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svq0 = \ (m8_svpV [Occ=Once1!] :: ((), Int)) -> case m8_svpV of { (_ [Occ=Dead], s'4_svpY [Occ=Once1]) -> let { sat_svpZ [Occ=Once1] :: (Word16, Int) [LclId] sat_svpZ = (ww4_svpP, s'4_svpY) } in eta3_svpJ sat_svpZ } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name2_ruZA lvl38_ruZI) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) ww5_svpQ) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svpI) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svq0; 128## -> let { sat_svq1 [Occ=Once1] :: (Word16, Int) [LclId] sat_svq1 = (ww4_svpP, ww5_svpQ) } in eta3_svpJ sat_svq1 } } } } in let { eta5_svq2 [InlPrag=[2], Occ=OnceL1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<1!P(L,L)>, Unf=OtherCon []] eta5_svq2 = \ (m7_svq3 [Occ=Once1!] :: (Word16, Int)) -> case m7_svq3 of { (ww4_svq5 [Occ=Once1], ww5_svq6 [Occ=Once1]) -> $weta_svpO ww4_svq5 ww5_svq6 } } in let { $wkarg1_svq7 [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svq7 = \ (ww4_svq8 :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww4_svq8 of ww5_svq9 { __DEFAULT -> case word8ToWord# ww5_svq9 of sat_svqa [Occ=Once1] { __DEFAULT -> case and# 128## sat_svqa of { __DEFAULT -> case +# ww4_svq8 1# of sat_svqc [Occ=Once1] { __DEFAULT -> let { sat_svqd [Occ=Once1] :: Int [LclId] sat_svqd = I# sat_svqc } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @Word16 $dMonadFail6_ruYJ name2_ruZA lvl36_ruZG) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N :: StateT Int (Decoder RealWorld) Word16 ~R# (Int -> Decoder RealWorld (Word16, Int)))) sat_svqd) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (Version -> Decoder RealWorld (Word16, Int)))) eta2_svpI) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H eta5_svq2 }; 0## -> case +# ww4_svq8 1# of sat_svqm [Occ=Once1] { __DEFAULT -> let { sat_svqn [Occ=Once1] :: Int [LclId] sat_svqn = I# sat_svqm } in case word8ToWord# ww5_svq9 of sat_svqh [Occ=Once1] { __DEFAULT -> case and# sat_svqh 65535## of sat_svqi [Occ=Once1] { __DEFAULT -> case word16ToWord# ipv_svpL of sat_svqe [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svqe 7# of sat_svqf [Occ=Once1] { __DEFAULT -> case and# sat_svqf 65535## of sat_svqg [Occ=Once1] { __DEFAULT -> case or# sat_svqg sat_svqi of sat_svqj [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svqj of sat_svqk [Occ=Once1] { __DEFAULT -> let { sat_svql [Occ=Once1] :: Word16 [LclId] sat_svql = W16# sat_svqk } in $weta_svpO sat_svql sat_svqn } } } } } } } } } } } } in case ># x_svpN lvl57_svne of { __DEFAULT -> $wkarg1_svq7 x_svpN; 1# -> let { sat_svqv [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svqv = \ (m7_svqp [Occ=Once1!] :: ((), Int)) -> case m7_svqp of { (_ [Occ=Dead], ww5_svqs [Occ=Once1!]) -> case ww5_svqs of { I# ww6_svqu [Occ=Once1] -> $wkarg1_svq7 ww6_svqu } } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name2_ruZA lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) wild4_svpM) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svpI) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svqv } } } } in let { sat_svqC [Occ=Once1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> StateT Int (Decoder RealWorld) Word16 [LclId] sat_svqC = (\ (acc_svqw [Occ=Once1!] :: Word16) (eta1_svqx [Occ=Once1, OS=OneShot] :: Int) (eta2_svqy [Occ=Once1, OS=OneShot] :: Version) (@r_suJ3) (eta3_svqz [Occ=Once1, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_suJ3)) -> case acc_svqw of { W16# ww4_svqB [Occ=Once1] -> $wd7_svnV (cont_svpF `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16))) ww4_svqB eta1_svqx eta2_svqy @r_suJ3 eta3_svqz }) `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16)) } in $wd7_svnV sat_svqC 0#Word16 ww3_svpv ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version)) @(Addr StandardCrypto) sat_svs9 } in let { $wk2_svsa [InlPrag=[2], Dmd=LC(S,L)] :: Word32 -> Int -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] $wk2_svsa = \ (ww1_svsb [Occ=OnceL2] :: Word32) (ww3_svsc [Occ=Once2] :: Int) -> case lvl59_svpr of { W8# x#5_svse [Occ=Once1] -> case word8ToWord# x#5_svse of sat_svsf [Occ=Once1] { __DEFAULT -> case and# 240## sat_svsf of { __DEFAULT -> let { sat_svsl [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svsl = \ (m11_svsh [Occ=Once1!] :: ((), Int)) -> case m11_svsh of { (_ [Occ=Dead], s'7_svsk [Occ=Once1]) -> $wk1_svpt ww1_svsb s'7_svsk } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl40_ruZK) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) ww3_svsc) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svsl; 128## -> $wk1_svpt ww1_svsb ww3_svsc } } } } in let { k2_svsm [InlPrag=[2], Occ=OnceL1] :: (Word32, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<1!P(L,L)>, Unf=OtherCon []] k2_svsm = \ (m10_svsn [Occ=Once1!] :: (Word32, Int)) -> case m10_svsn of { (ww1_svsp [Occ=Once1], ww3_svsq [Occ=Once1]) -> $wk2_svsa ww1_svsp ww3_svsq } } in let { $wkarg1_svsr [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svsr = \ (ww1_svss :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww1_svss of ww3_svst { __DEFAULT -> case +# ww1_svss 1# of karg2_svsu { __DEFAULT -> case word8ToWord# ww3_svst of sat_svsv [Occ=Once1] { __DEFAULT -> case and# 128## sat_svsv of { __DEFAULT -> case word8ToWord# ww3_svst of sat_svsy [Occ=Once1] { __DEFAULT -> case and# 127## sat_svsy of sat_svsz [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svsz of ds1_svsx [Occ=OnceL2] { __DEFAULT -> let { $wkarg3_svsA [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg3_svsA = \ (ww4_svsB :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww4_svsB of ww5_svsC { __DEFAULT -> case +# ww4_svsB 1# of karg4_svsD { __DEFAULT -> case word8ToWord# ww5_svsC of sat_svsE [Occ=Once1] { __DEFAULT -> case and# 128## sat_svsE of { __DEFAULT -> case word8ToWord# ww5_svsC of sat_svsK [Occ=Once1] { __DEFAULT -> case and# 127## sat_svsK of sat_svsL [Occ=Once1] { __DEFAULT -> case word32ToWord# ds1_svsx of sat_svsH [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svsH 7# of sat_svsI [Occ=Once1] { __DEFAULT -> case and# sat_svsI 4294967295## of sat_svsJ [Occ=Once1] { __DEFAULT -> case or# sat_svsJ sat_svsL of sat_svsM [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svsM of ipv_svsG [Occ=OnceL2] { __DEFAULT -> let { $wkarg5_svsN [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg5_svsN = \ (ww6_svsO :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww6_svsO of ww7_svsP { __DEFAULT -> case +# ww6_svsO 1# of karg6_svsQ { __DEFAULT -> case word8ToWord# ww7_svsP of sat_svsR [Occ=Once1] { __DEFAULT -> case and# 128## sat_svsR of { __DEFAULT -> case word8ToWord# ww7_svsP of sat_svsX [Occ=Once1] { __DEFAULT -> case and# 127## sat_svsX of sat_svsY [Occ=Once1] { __DEFAULT -> case word32ToWord# ipv_svsG of sat_svsU [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svsU 7# of sat_svsV [Occ=Once1] { __DEFAULT -> case and# sat_svsV 4294967295## of sat_svsW [Occ=Once1] { __DEFAULT -> case or# sat_svsW sat_svsY of sat_svsZ [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svsZ of ipv1_svsT [Occ=OnceL2] { __DEFAULT -> let { $wkarg7_svt0 [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg7_svt0 = \ (ww8_svt1 :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww8_svt1 of ww9_svt2 { __DEFAULT -> case +# ww8_svt1 1# of karg8_svt3 { __DEFAULT -> case word8ToWord# ww9_svt2 of sat_svt4 [Occ=Once1] { __DEFAULT -> case and# 128## sat_svt4 of { __DEFAULT -> case word8ToWord# ww9_svt2 of sat_svta [Occ=Once1] { __DEFAULT -> case and# 127## sat_svta of sat_svtb [Occ=Once1] { __DEFAULT -> case word32ToWord# ipv1_svsT of sat_svt7 [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svt7 7# of sat_svt8 [Occ=Once1] { __DEFAULT -> case and# sat_svt8 4294967295## of sat_svt9 [Occ=Once1] { __DEFAULT -> case or# sat_svt9 sat_svtb of sat_svtc [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svtc of acc_svt6 [Occ=OnceL1] { __DEFAULT -> let { $wkarg9_svtd [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg9_svtd = \ (ww10_svte :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww10_svte of ww11_svtf { __DEFAULT -> case word8ToWord# ww11_svtf of sat_svtg [Occ=Once1] { __DEFAULT -> case and# 128## sat_svtg of { __DEFAULT -> case +# ww10_svte 1# of sat_svti [Occ=Once1] { __DEFAULT -> let { sat_svtj [Occ=Once1] :: Int [LclId] sat_svtj = I# sat_svti } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @Word32 $dMonadFail6_ruYJ name1_ruZy lvl36_ruZG) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word32>_N :: StateT Int (Decoder RealWorld) Word32 ~R# (Int -> Decoder RealWorld (Word32, Int)))) sat_svtj) `cast` (N:Decoder[0] <RealWorld>_N <(Word32, Int)>_R :: Decoder RealWorld (Word32, Int) ~R# (Version -> Decoder RealWorld (Word32, Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <(Word32, Int)>_R :: Decoder RealWorld (Word32, Int) ~R# (forall r. ((Word32, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) k2_svsm }; 0## -> case +# ww10_svte 1# of sat_svts [Occ=Once1] { __DEFAULT -> let { sat_svtt [Occ=Once1] :: Int [LclId] sat_svtt = I# sat_svts } in case word8ToWord# ww11_svtf of sat_svtn [Occ=Once1] { __DEFAULT -> case and# sat_svtn 4294967295## of sat_svto [Occ=Once1] { __DEFAULT -> case word32ToWord# acc_svt6 of sat_svtk [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svtk 7# of sat_svtl [Occ=Once1] { __DEFAULT -> case and# sat_svtl 4294967295## of sat_svtm [Occ=Once1] { __DEFAULT -> case or# sat_svtm sat_svto of sat_svtp [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svtp of sat_svtq [Occ=Once1] { __DEFAULT -> let { sat_svtr [Occ=Once1] :: Word32 [LclId] sat_svtr = W32# sat_svtq } in $wk2_svsa sat_svtr sat_svtt } } } } } } } } } } } } in case ># karg8_svt3 lvl57_svne of { __DEFAULT -> $wkarg9_svtd karg8_svt3; 1# -> let { sat_svtC [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svtC = \ (m10_svtw [Occ=Once1!] :: ((), Int)) -> case m10_svtw of { (_ [Occ=Dead], ww11_svtz [Occ=Once1!]) -> case ww11_svtz of { I# ww12_svtB [Occ=Once1] -> $wkarg9_svtd ww12_svtB } } } in let { sat_svtv [Occ=Once1] :: Int [LclId] sat_svtv = I# karg8_svt3 } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svtv) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svtC } } } } } } } }; 0## -> let { sat_svtL [Occ=Once1, Dmd=SL] :: Int [LclId] sat_svtL = I# karg8_svt3 } in case word8ToWord# ww9_svt2 of sat_svtG [Occ=Once1] { __DEFAULT -> case and# sat_svtG 4294967295## of sat_svtH [Occ=Once1] { __DEFAULT -> case word32ToWord# ipv1_svsT of sat_svtD [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svtD 7# of sat_svtE [Occ=Once1] { __DEFAULT -> case and# sat_svtE 4294967295## of sat_svtF [Occ=Once1] { __DEFAULT -> case or# sat_svtF sat_svtH of sat_svtI [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svtI of sat_svtJ [Occ=Once1] { __DEFAULT -> let { sat_svtK [Occ=Once1, Dmd=ML] :: Word32 [LclId] sat_svtK = W32# sat_svtJ } in $wk1_svpt sat_svtK sat_svtL } } } } } } } } } } } } in case ># karg6_svsQ lvl57_svne of { __DEFAULT -> $wkarg7_svt0 karg6_svsQ; 1# -> let { sat_svtU [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svtU = \ (m9_svtO [Occ=Once1!] :: ((), Int)) -> case m9_svtO of { (_ [Occ=Dead], ww9_svtR [Occ=Once1!]) -> case ww9_svtR of { I# ww10_svtT [Occ=Once1] -> $wkarg7_svt0 ww10_svtT } } } in let { sat_svtN [Occ=Once1] :: Int [LclId] sat_svtN = I# karg6_svsQ } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svtN) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svtU } } } } } } } }; 0## -> let { sat_svu3 [Occ=Once1, Dmd=SL] :: Int [LclId] sat_svu3 = I# karg6_svsQ } in case word8ToWord# ww7_svsP of sat_svtY [Occ=Once1] { __DEFAULT -> case and# sat_svtY 4294967295## of sat_svtZ [Occ=Once1] { __DEFAULT -> case word32ToWord# ipv_svsG of sat_svtV [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svtV 7# of sat_svtW [Occ=Once1] { __DEFAULT -> case and# sat_svtW 4294967295## of sat_svtX [Occ=Once1] { __DEFAULT -> case or# sat_svtX sat_svtZ of sat_svu0 [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svu0 of sat_svu1 [Occ=Once1] { __DEFAULT -> let { sat_svu2 [Occ=Once1, Dmd=ML] :: Word32 [LclId] sat_svu2 = W32# sat_svu1 } in $wk1_svpt sat_svu2 sat_svu3 } } } } } } } } } } } } in case ># karg4_svsD lvl57_svne of { __DEFAULT -> $wkarg5_svsN karg4_svsD; 1# -> let { sat_svuc [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svuc = \ (m8_svu6 [Occ=Once1!] :: ((), Int)) -> case m8_svu6 of { (_ [Occ=Dead], ww7_svu9 [Occ=Once1!]) -> case ww7_svu9 of { I# ww8_svub [Occ=Once1] -> $wkarg5_svsN ww8_svub } } } in let { sat_svu5 [Occ=Once1] :: Int [LclId] sat_svu5 = I# karg4_svsD } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svu5) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svuc } } } } } } } }; 0## -> let { sat_svul [Occ=Once1, Dmd=SL] :: Int [LclId] sat_svul = I# karg4_svsD } in case word8ToWord# ww5_svsC of sat_svug [Occ=Once1] { __DEFAULT -> case and# sat_svug 4294967295## of sat_svuh [Occ=Once1] { __DEFAULT -> case word32ToWord# ds1_svsx of sat_svud [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svud 7# of sat_svue [Occ=Once1] { __DEFAULT -> case and# sat_svue 4294967295## of sat_svuf [Occ=Once1] { __DEFAULT -> case or# sat_svuf sat_svuh of sat_svui [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svui of sat_svuj [Occ=Once1] { __DEFAULT -> let { sat_svuk [Occ=Once1, Dmd=ML] :: Word32 [LclId] sat_svuk = W32# sat_svuj } in $wk1_svpt sat_svuk sat_svul } } } } } } } } } } } } in case ># karg2_svsu lvl57_svne of { __DEFAULT -> $wkarg3_svsA karg2_svsu; 1# -> let { sat_svuu [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svuu = \ (m7_svuo [Occ=Once1!] :: ((), Int)) -> case m7_svuo of { (_ [Occ=Dead], ww5_svur [Occ=Once1!]) -> case ww5_svur of { I# ww6_svut [Occ=Once1] -> $wkarg3_svsA ww6_svut } } } in let { sat_svun [Occ=Once1] :: Int [LclId] sat_svun = I# karg2_svsu } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svun) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svuu } } } }; 0## -> let { sat_svuy [Occ=Once1, Dmd=SL] :: Int [LclId] sat_svuy = I# karg2_svsu } in case word8ToWord# ww3_svst of sat_svuv [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svuv of sat_svuw [Occ=Once1] { __DEFAULT -> let { sat_svux [Occ=Once1, Dmd=ML] :: Word32 [LclId] sat_svux = W32# sat_svuw } in $wk1_svpt sat_svux sat_svuy } } } } } } } in case ># sc_svpk lvl57_svne of { __DEFAULT -> (($wkarg1_svsr sc_svpk) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svpm; 1# -> let { sat_svuH [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svuH = \ (m6_svuB [Occ=Once1!] :: ((), Int)) -> case m6_svuB of { (_ [Occ=Dead], ww3_svuE [Occ=Once1!]) -> case ww3_svuE of { I# ww4_svuG [Occ=Once1] -> $wkarg1_svsr ww4_svuG } } } in let { sat_svuA [Occ=Once1] :: Int [LclId] sat_svuA = I# sc_svpk } in ((((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svuA) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svuH) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svpm } }; 0## -> case and# 32## wild_svnb of { __DEFAULT -> case $wpackBytesMaybe @(SizeHash (ADDRHASH StandardCrypto)) ($fHashAlgorithmBlake2b_5 `cast` (Sym (N:SNat[0] <28>_N) ; Sym (N:KnownNat[0] ((SizeHash (D:R:ADDRHASHStandardCrypto[0]))_N ; D:R:SizeHashBlake2b_224[0])) :: Natural ~R# KnownNat (SizeHash (ADDRHASH StandardCrypto)))) (m1_svnf `cast` (Sym (N:ShortByteString[0]) :: ByteArray ~R# ShortByteString)) sc_svpk of { Nothing -> case >=# sc_svpk 0# of { __DEFAULT -> (# eta_svpm, lvl27_ruZr @(Addr StandardCrypto) #); 1# -> let { sat_svuZ [Occ=Once1] :: (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svuZ = (\ (x1_svuQ [Occ=Once1!] :: (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)) (eta1_svuR [Occ=Once1, OS=OneShot] :: State# RealWorld) -> case x1_svuQ of { (a3_svuT [Occ=Once1], s'2_svuU [Occ=Once1]) -> let { sat_svuX [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svuX = case a3_svuT `cast` (N:Hash[0] <ADDRHASH StandardCrypto>_N <EraIndependentScript>_P :: Hash (ADDRHASH StandardCrypto) EraIndependentScript ~R# PackedBytes (SizeHash (ADDRHASH StandardCrypto))) of nt_svuV [Occ=Once1] { __DEFAULT -> let { sat_svuW [Occ=Once1] :: Credential 'Staking StandardCrypto [LclId] sat_svuW = ScriptHashObj @'Staking @StandardCrypto (nt_svuV `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <EraIndependentScript>_P) ; Sym (N:ScriptHash[0] <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# ScriptHash StandardCrypto)) } in StakeRefBase @StandardCrypto sat_svuW } } in let { sat_svuY [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svuY = Addr @StandardCrypto lvl58_svph sc1_svpl sat_svuX } in $wlvl1_sv48 sat_svuY s'2_svuU eta1_svuR }) `cast` (<(Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: ((Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# ((Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) } in let { sat_svuP [Occ=Once1] :: Int [LclId] sat_svuP = I# sc_svpk } in let { sat_svuO [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svuO = let { sat_svuN [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svuN = case -# len_sv47 sc_svpk of sat_svuL [Occ=Once1] { __DEFAULT -> case itos sat_svuL ([] @Char) of sat_svuM [Occ=Once1, Dmd=1L] { __DEFAULT -> ++ @Char sat_svuM lvl32_ruZw } } } in unpackAppendCString# lvl48_ruZT sat_svuN } in ((((((((failDecoding @(StateT Int (Decoder RealWorld)) @(Hash (ADDRHASH StandardCrypto) EraIndependentScript) $dMonadFail6_ruYJ lvl29_ruZt sat_svuO) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Hash (ADDRHASH StandardCrypto) EraIndependentScript>_N :: StateT Int (Decoder RealWorld) (Hash (ADDRHASH StandardCrypto) EraIndependentScript) ~R# (Int -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)))) sat_svuP) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) ~R# (Version -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) ~R# (forall r. ((Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svuZ) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svpm }; Just a3_svv0 [Occ=Once1] -> case +# sc_svpk 28# of sat_svv5 [Occ=Once1] { __DEFAULT -> let { sat_svv6 [Occ=Once1, Dmd=1L] :: Int [LclId] sat_svv6 = I# sat_svv5 } in let { sat_svv3 [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svv3 = case a3_svv0 of nt_svv1 [Occ=Once1] { __DEFAULT -> let { sat_svv2 [Occ=Once1] :: Credential 'Staking StandardCrypto [LclId] sat_svv2 = ScriptHashObj @'Staking @StandardCrypto (nt_svv1 `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <EraIndependentScript>_P) ; Sym (N:ScriptHash[0] <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# ScriptHash StandardCrypto)) } in StakeRefBase @StandardCrypto sat_svv2 } } in let { sat_svv4 [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svv4 = Addr @StandardCrypto lvl58_svph sc1_svpl sat_svv3 } in $wlvl1_sv48 sat_svv4 sat_svv6 eta_svpm } }; 0## -> case $wpackBytesMaybe @(SizeHash (ADDRHASH StandardCrypto)) ($fHashAlgorithmBlake2b_5 `cast` (Sym (N:SNat[0] <28>_N) ; Sym (N:KnownNat[0] ((SizeHash (D:R:ADDRHASHStandardCrypto[0]))_N ; D:R:SizeHashBlake2b_224[0])) :: Natural ~R# KnownNat (SizeHash (ADDRHASH StandardCrypto)))) (m1_svnf `cast` (Sym (N:ShortByteString[0]) :: ByteArray ~R# ShortByteString)) sc_svpk of { Nothing -> case >=# sc_svpk 0# of { __DEFAULT -> (# eta_svpm, lvl27_ruZr @(Addr StandardCrypto) #); 1# -> let { sat_svvn [Occ=Once1] :: (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svvn = (\ (x1_svve [Occ=Once1!] :: (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)) (eta1_svvf [Occ=Once1, OS=OneShot] :: State# RealWorld) -> case x1_svve of { (a3_svvh [Occ=Once1], s'2_svvi [Occ=Once1]) -> let { sat_svvl [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svvl = case a3_svvh `cast` (N:Hash[0] <ADDRHASH StandardCrypto>_N <VerKeyDSIGN (DSIGN StandardCrypto)>_P :: Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)) ~R# PackedBytes (SizeHash (ADDRHASH StandardCrypto))) of nt_svvj [Occ=Once1] { __DEFAULT -> let { sat_svvk [Occ=Once1] :: Credential 'Staking StandardCrypto [LclId] sat_svvk = KeyHashObj @'Staking @StandardCrypto (nt_svvj `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <VerKeyDSIGN (DSIGN StandardCrypto)>_P) ; Sym (N:KeyHash[0] <'Staking>_P <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# KeyHash 'Staking StandardCrypto)) } in StakeRefBase @StandardCrypto sat_svvk } } in let { sat_svvm [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svvm = Addr @StandardCrypto lvl58_svph sc1_svpl sat_svvl } in $wlvl1_sv48 sat_svvm s'2_svvi eta1_svvf }) `cast` (<(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: ((Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# ((Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) } in let { sat_svvd [Occ=Once1] :: Int [LclId] sat_svvd = I# sc_svpk } in let { sat_svvc [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svvc = let { sat_svvb [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svvb = case -# len_sv47 sc_svpk of sat_svv9 [Occ=Once1] { __DEFAULT -> case itos sat_svv9 ([] @Char) of sat_svva [Occ=Once1, Dmd=1L] { __DEFAULT -> ++ @Char sat_svva lvl32_ruZw } } } in unpackAppendCString# lvl48_ruZT sat_svvb } in ((((((((failDecoding @(StateT Int (Decoder RealWorld)) @(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))) $dMonadFail6_ruYJ lvl29_ruZt sat_svvc) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))>_N :: StateT Int (Decoder RealWorld) (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))) ~R# (Int -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)))) sat_svvd) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) ~R# (Version -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) ~R# (forall r. ((Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svvn) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svpm }; Just a3_svvo [Occ=Once1] -> case +# sc_svpk 28# of sat_svvt [Occ=Once1] { __DEFAULT -> let { sat_svvu [Occ=Once1, Dmd=1L] :: Int [LclId] sat_svvu = I# sat_svvt } in let { sat_svvr [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svvr = case a3_svvo of nt_svvp [Occ=Once1] { __DEFAULT -> let { sat_svvq [Occ=Once1] :: Credential 'Staking StandardCrypto [LclId] sat_svvq = KeyHashObj @'Staking @StandardCrypto (nt_svvp `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <VerKeyDSIGN (DSIGN StandardCrypto)>_P) ; Sym (N:KeyHash[0] <'Staking>_P <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# KeyHash 'Staking StandardCrypto)) } in StakeRefBase @StandardCrypto sat_svvq } } in let { sat_svvs [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svvs = Addr @StandardCrypto lvl58_svph sc1_svpl sat_svvr } in $wlvl1_sv48 sat_svvs sat_svvu eta_svpm } } } } } in let { $wlvl2_svvv [InlPrag=[2], Dmd=LC(S,C(1,C(1,!P(L,L))))] :: PaymentCredential StandardCrypto -> Int -> State# RealWorld -> (# State# RealWorld, DecodeAction RealWorld (Addr StandardCrypto) #) [LclId[StrictWorker([~, !])], Arity=3, Str=<L><1L><L>, Unf=OtherCon []] $wlvl2_svvv = \ (ww1_svvw :: PaymentCredential StandardCrypto) (ww3_svvx [Occ=Once4!, OS=OneShot] :: Int) (eta_svvy [Occ=Once9, OS=OneShot] :: State# RealWorld) -> case and# 64## wild_svnb of { __DEFAULT -> case and# 32## wild_svnb of { __DEFAULT -> let { sat_svvB [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svvB = Addr @StandardCrypto lvl58_svph ww1_svvw (StakeRefNull @StandardCrypto) } in $wlvl1_sv48 sat_svvB ww3_svvx eta_svvy; 0## -> case ww3_svvx of wild4_svvC [Occ=Once1] { I# x_svvD -> let { lvl59_svvE [Occ=OnceL1!] :: Word8 [LclId] lvl59_svvE = case $wunsafeShortByteStringIndex ww_sv46 x_svvD of ww4_svvF [Occ=Once1] { __DEFAULT -> W8# ww4_svvF } } in let { $s$wk1_svvG [Occ=OnceL4!] :: Int# -> Word32# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] $s$wk1_svvG = \ (sc_svvH :: Int#) (sc1_svvI [Occ=Once1] :: Word32#) -> let { lvl60_svvJ [Occ=OnceL1!] :: Word8 [LclId] lvl60_svvJ = case $wunsafeShortByteStringIndex ww_sv46 sc_svvH of ww4_svvK [Occ=Once1] { __DEFAULT -> W8# ww4_svvK } } in case word32ToWord# sc1_svvI of sat_svvM [Occ=Once1] { __DEFAULT -> case wordToWord64# sat_svvM of a4_svvL [Occ=OnceL1] { __DEFAULT -> let { sat_svyf [Occ=Once1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svyf = \ (x2_svwL [Occ=Once1!] :: (Word16, Int)) -> case x2_svwL of { (a5_svwN [Occ=Once1!], s'3_svwO) -> let { lvl61_svwP [Occ=OnceL1!] :: Word8 [LclId] lvl61_svwP = case s'3_svwO of { I# ww4_svwR [Occ=Once1] -> case $wunsafeShortByteStringIndex ww_sv46 ww4_svwR of ww5_svwS [Occ=Once1] { __DEFAULT -> W8# ww5_svwS } } } in let { ds1_svwT [Occ=OnceL1!] :: Word64 [LclId] ds1_svwT = case a5_svwN of { W16# x#1_svwV [Occ=Once1] -> case word16ToWord# x#1_svwV of sat_svwW [Occ=Once1] { __DEFAULT -> case word2Int# sat_svwW of sat_svwX [Occ=Once1] { __DEFAULT -> case intToInt64# sat_svwX of sat_svwY [Occ=Once1] { __DEFAULT -> case int64ToWord64# sat_svwY of sat_svwZ [Occ=Once1] { __DEFAULT -> W64# sat_svwZ } } } } } } in let { sat_svye [Occ=Once1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svye = (\ (x3_svxY [Occ=Once1!] :: (Word16, Int)) (eta1_svxZ [Occ=Once1, OS=OneShot] :: State# RealWorld) -> case x3_svxY of { (a6_svy1 [Occ=Once1!], s'4_svy2 [Occ=Once1]) -> let { sat_svyc [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svyc = case a6_svy1 of { W16# x#1_svy4 [Occ=Once1] -> case ds1_svwT of { W64# unbx_svy6 [Occ=Once1] -> case word16ToWord# x#1_svy4 of sat_svy7 [Occ=Once1] { __DEFAULT -> case word2Int# sat_svy7 of sat_svy8 [Occ=Once1] { __DEFAULT -> case intToInt64# sat_svy8 of sat_svy9 [Occ=Once1] { __DEFAULT -> case int64ToWord64# sat_svy9 of sat_svya [Occ=Once1] { __DEFAULT -> let { sat_svyb [Occ=Once1] :: Ptr [LclId] sat_svyb = Ptr a4_svvL unbx_svy6 sat_svya } in StakeRefPtr @StandardCrypto sat_svyb } } } } } } } in let { sat_svyd [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svyd = Addr @StandardCrypto lvl58_svph ww1_svvw sat_svyc } in $wlvl1_sv48 sat_svyd s'4_svy2 eta1_svxZ }) `cast` (<(Word16, Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: ((Word16, Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) } in let { cont_svx0 [Occ=OnceL1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r) [LclId, Arity=4, Str=<1L><1L><L><LC(S,L)>, Unf=OtherCon []] cont_svx0 = \ (acc_svx1 [Occ=Once1!] :: Word16) (eta1_svx2 [Occ=Once1!, OS=OneShot] :: Int) (eta2_svx3 [OS=OneShot] :: Version) (@r_X1H) (eta3_svx4 [Occ=OnceL2!, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H)) -> case acc_svx1 of { W16# ipv_svx6 [Occ=OnceL1] -> case eta1_svx2 of wild5_svx7 [Occ=Once1] { I# x1_svx8 -> let { $weta_svx9 [InlPrag=[2], Dmd=LC(S,L)] :: Word16 -> Int -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] $weta_svx9 = \ (ww4_svxa [Occ=OnceL2] :: Word16) (ww5_svxb [Occ=Once2] :: Int) -> case lvl61_svwP of { W8# x#1_svxd [Occ=Once1] -> case word8ToWord# x#1_svxd of sat_svxe [Occ=Once1] { __DEFAULT -> case and# 252## sat_svxe of { __DEFAULT -> let { sat_svxl [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svxl = \ (m8_svxg [Occ=Once1!] :: ((), Int)) -> case m8_svxg of { (_ [Occ=Dead], s'5_svxj [Occ=Once1]) -> let { sat_svxk [Occ=Once1] :: (Word16, Int) [LclId] sat_svxk = (ww4_svxa, s'5_svxj) } in eta3_svx4 sat_svxk } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name3_ruZC lvl38_ruZI) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) ww5_svxb) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svx3) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svxl; 128## -> let { sat_svxm [Occ=Once1] :: (Word16, Int) [LclId] sat_svxm = (ww4_svxa, ww5_svxb) } in eta3_svx4 sat_svxm } } } } in let { eta5_svxn [InlPrag=[2], Occ=OnceL1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<1!P(L,L)>, Unf=OtherCon []] eta5_svxn = \ (m7_svxo [Occ=Once1!] :: (Word16, Int)) -> case m7_svxo of { (ww4_svxq [Occ=Once1], ww5_svxr [Occ=Once1]) -> $weta_svx9 ww4_svxq ww5_svxr } } in let { $wkarg1_svxs [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svxs = \ (ww4_svxt :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww4_svxt of ww5_svxu { __DEFAULT -> case word8ToWord# ww5_svxu of sat_svxv [Occ=Once1] { __DEFAULT -> case and# 128## sat_svxv of { __DEFAULT -> case +# ww4_svxt 1# of sat_svxx [Occ=Once1] { __DEFAULT -> let { sat_svxy [Occ=Once1] :: Int [LclId] sat_svxy = I# sat_svxx } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @Word16 $dMonadFail6_ruYJ name3_ruZC lvl36_ruZG) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N :: StateT Int (Decoder RealWorld) Word16 ~R# (Int -> Decoder RealWorld (Word16, Int)))) sat_svxy) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (Version -> Decoder RealWorld (Word16, Int)))) eta2_svx3) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H eta5_svxn }; 0## -> case +# ww4_svxt 1# of sat_svxH [Occ=Once1] { __DEFAULT -> let { sat_svxI [Occ=Once1] :: Int [LclId] sat_svxI = I# sat_svxH } in case word8ToWord# ww5_svxu of sat_svxC [Occ=Once1] { __DEFAULT -> case and# sat_svxC 65535## of sat_svxD [Occ=Once1] { __DEFAULT -> case word16ToWord# ipv_svx6 of sat_svxz [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svxz 7# of sat_svxA [Occ=Once1] { __DEFAULT -> case and# sat_svxA 65535## of sat_svxB [Occ=Once1] { __DEFAULT -> case or# sat_svxB sat_svxD of sat_svxE [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svxE of sat_svxF [Occ=Once1] { __DEFAULT -> let { sat_svxG [Occ=Once1] :: Word16 [LclId] sat_svxG = W16# sat_svxF } in $weta_svx9 sat_svxG sat_svxI } } } } } } } } } } } } in case ># x1_svx8 lvl57_svne of { __DEFAULT -> $wkarg1_svxs x1_svx8; 1# -> let { sat_svxQ [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svxQ = \ (m7_svxK [Occ=Once1!] :: ((), Int)) -> case m7_svxK of { (_ [Occ=Dead], ww5_svxN [Occ=Once1!]) -> case ww5_svxN of { I# ww6_svxP [Occ=Once1] -> $wkarg1_svxs ww6_svxP } } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name3_ruZC lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) wild5_svx7) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svx3) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svxQ } } } } in let { sat_svxX [Occ=Once1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> StateT Int (Decoder RealWorld) Word16 [LclId] sat_svxX = (\ (acc_svxR [Occ=Once1!] :: Word16) (eta1_svxS [Occ=Once1, OS=OneShot] :: Int) (eta2_svxT [Occ=Once1, OS=OneShot] :: Version) (@r_suIG) (eta3_svxU [Occ=Once1, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_suIG)) -> case acc_svxR of { W16# ww4_svxW [Occ=Once1] -> $wd1_svoB (cont_svx0 `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16))) ww4_svxW eta1_svxS eta2_svxT @r_suIG eta3_svxU }) `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16)) } in $wd1_svoB sat_svxX 0#Word16 s'3_svwO ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version)) @(Addr StandardCrypto) sat_svye } } in let { cont_svvN [Occ=OnceL1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r) [LclId, Arity=4, Str=<1L><1L><L><LC(S,L)>, Unf=OtherCon []] cont_svvN = \ (acc_svvO [Occ=Once1!] :: Word16) (eta1_svvP [Occ=Once1!, OS=OneShot] :: Int) (eta2_svvQ [OS=OneShot] :: Version) (@r_X1H) (eta3_svvR [Occ=OnceL2!, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H)) -> case acc_svvO of { W16# ipv_svvT [Occ=OnceL1] -> case eta1_svvP of wild5_svvU [Occ=Once1] { I# x1_svvV -> let { $weta_svvW [InlPrag=[2], Dmd=LC(S,L)] :: Word16 -> Int -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] $weta_svvW = \ (ww4_svvX [Occ=OnceL2] :: Word16) (ww5_svvY [Occ=Once2] :: Int) -> case lvl60_svvJ of { W8# x#1_svw0 [Occ=Once1] -> case word8ToWord# x#1_svw0 of sat_svw1 [Occ=Once1] { __DEFAULT -> case and# 252## sat_svw1 of { __DEFAULT -> let { sat_svw8 [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svw8 = \ (m8_svw3 [Occ=Once1!] :: ((), Int)) -> case m8_svw3 of { (_ [Occ=Dead], s'4_svw6 [Occ=Once1]) -> let { sat_svw7 [Occ=Once1] :: (Word16, Int) [LclId] sat_svw7 = (ww4_svvX, s'4_svw6) } in eta3_svvR sat_svw7 } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name2_ruZA lvl38_ruZI) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) ww5_svvY) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svvQ) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svw8; 128## -> let { sat_svw9 [Occ=Once1] :: (Word16, Int) [LclId] sat_svw9 = (ww4_svvX, ww5_svvY) } in eta3_svvR sat_svw9 } } } } in let { eta5_svwa [InlPrag=[2], Occ=OnceL1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<1!P(L,L)>, Unf=OtherCon []] eta5_svwa = \ (m7_svwb [Occ=Once1!] :: (Word16, Int)) -> case m7_svwb of { (ww4_svwd [Occ=Once1], ww5_svwe [Occ=Once1]) -> $weta_svvW ww4_svwd ww5_svwe } } in let { $wkarg1_svwf [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svwf = \ (ww4_svwg :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww4_svwg of ww5_svwh { __DEFAULT -> case word8ToWord# ww5_svwh of sat_svwi [Occ=Once1] { __DEFAULT -> case and# 128## sat_svwi of { __DEFAULT -> case +# ww4_svwg 1# of sat_svwk [Occ=Once1] { __DEFAULT -> let { sat_svwl [Occ=Once1] :: Int [LclId] sat_svwl = I# sat_svwk } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @Word16 $dMonadFail6_ruYJ name2_ruZA lvl36_ruZG) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N :: StateT Int (Decoder RealWorld) Word16 ~R# (Int -> Decoder RealWorld (Word16, Int)))) sat_svwl) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (Version -> Decoder RealWorld (Word16, Int)))) eta2_svvQ) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H eta5_svwa }; 0## -> case +# ww4_svwg 1# of sat_svwu [Occ=Once1] { __DEFAULT -> let { sat_svwv [Occ=Once1] :: Int [LclId] sat_svwv = I# sat_svwu } in case word8ToWord# ww5_svwh of sat_svwp [Occ=Once1] { __DEFAULT -> case and# sat_svwp 65535## of sat_svwq [Occ=Once1] { __DEFAULT -> case word16ToWord# ipv_svvT of sat_svwm [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svwm 7# of sat_svwn [Occ=Once1] { __DEFAULT -> case and# sat_svwn 65535## of sat_svwo [Occ=Once1] { __DEFAULT -> case or# sat_svwo sat_svwq of sat_svwr [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svwr of sat_svws [Occ=Once1] { __DEFAULT -> let { sat_svwt [Occ=Once1] :: Word16 [LclId] sat_svwt = W16# sat_svws } in $weta_svvW sat_svwt sat_svwv } } } } } } } } } } } } in case ># x1_svvV lvl57_svne of { __DEFAULT -> $wkarg1_svwf x1_svvV; 1# -> let { sat_svwD [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svwD = \ (m7_svwx [Occ=Once1!] :: ((), Int)) -> case m7_svwx of { (_ [Occ=Dead], ww5_svwA [Occ=Once1!]) -> case ww5_svwA of { I# ww6_svwC [Occ=Once1] -> $wkarg1_svwf ww6_svwC } } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name2_ruZA lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) wild5_svvU) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svvQ) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svwD } } } } in let { sat_svwK [Occ=Once1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> StateT Int (Decoder RealWorld) Word16 [LclId] sat_svwK = (\ (acc_svwE [Occ=Once1!] :: Word16) (eta1_svwF [Occ=Once1, OS=OneShot] :: Int) (eta2_svwG [Occ=Once1, OS=OneShot] :: Version) (@r_suJ3) (eta3_svwH [Occ=Once1, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_suJ3)) -> case acc_svwE of { W16# ww4_svwJ [Occ=Once1] -> $wd7_svnV (cont_svvN `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16))) ww4_svwJ eta1_svwF eta2_svwG @r_suJ3 eta3_svwH }) `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16)) } in $s$wd7_svng sc_svvH 0#Word16 sat_svwK ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version)) @(Addr StandardCrypto) sat_svyf } } } in let { $wk1_svyg [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,C(1,L))] :: Word32 -> Int -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId[StrictWorker([~, !])], Arity=2, Str=<ML><SL>, Unf=OtherCon []] $wk1_svyg = \ (ww4_svyh [Occ=Once1!] :: Word32) (ww5_svyi [OS=OneShot] :: Int) -> let { lvl60_svyj [Occ=OnceL1!] :: Word8 [LclId] lvl60_svyj = case ww5_svyi of { I# ww6_svyl [Occ=Once1] -> case $wunsafeShortByteStringIndex ww_sv46 ww6_svyl of ww7_svym [Occ=Once1] { __DEFAULT -> W8# ww7_svym } } } in let { a4_svyn [Occ=OnceL1!] :: Word64 [LclId] a4_svyn = case ww4_svyh of { W32# x#1_svyp [Occ=Once1] -> case word32ToWord# x#1_svyp of sat_svyq [Occ=Once1] { __DEFAULT -> case wordToWord64# sat_svyq of sat_svyr [Occ=Once1] { __DEFAULT -> W64# sat_svyr } } } } in let { sat_svAW [Occ=Once1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svAW = \ (x2_svzq [Occ=Once1!] :: (Word16, Int)) -> case x2_svzq of { (a5_svzs [Occ=Once1!], s'3_svzt) -> let { lvl61_svzu [Occ=OnceL1!] :: Word8 [LclId] lvl61_svzu = case s'3_svzt of { I# ww6_svzw [Occ=Once1] -> case $wunsafeShortByteStringIndex ww_sv46 ww6_svzw of ww7_svzx [Occ=Once1] { __DEFAULT -> W8# ww7_svzx } } } in let { ds1_svzy [Occ=OnceL1!] :: Word64 [LclId] ds1_svzy = case a5_svzs of { W16# x#1_svzA [Occ=Once1] -> case word16ToWord# x#1_svzA of sat_svzB [Occ=Once1] { __DEFAULT -> case word2Int# sat_svzB of sat_svzC [Occ=Once1] { __DEFAULT -> case intToInt64# sat_svzC of sat_svzD [Occ=Once1] { __DEFAULT -> case int64ToWord64# sat_svzD of sat_svzE [Occ=Once1] { __DEFAULT -> W64# sat_svzE } } } } } } in let { sat_svAV [Occ=Once1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svAV = (\ (x3_svAD [Occ=Once1!] :: (Word16, Int)) (eta1_svAE [Occ=Once1, OS=OneShot] :: State# RealWorld) -> case x3_svAD of { (a6_svAG [Occ=Once1!], s'4_svAH [Occ=Once1]) -> let { sat_svAT [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svAT = case a6_svAG of { W16# x#1_svAJ [Occ=Once1] -> case a4_svyn of { W64# unbx_svAL [Occ=Once1] -> case ds1_svzy of { W64# unbx1_svAN [Occ=Once1] -> case word16ToWord# x#1_svAJ of sat_svAO [Occ=Once1] { __DEFAULT -> case word2Int# sat_svAO of sat_svAP [Occ=Once1] { __DEFAULT -> case intToInt64# sat_svAP of sat_svAQ [Occ=Once1] { __DEFAULT -> case int64ToWord64# sat_svAQ of sat_svAR [Occ=Once1] { __DEFAULT -> let { sat_svAS [Occ=Once1] :: Ptr [LclId] sat_svAS = Ptr unbx_svAL unbx1_svAN sat_svAR } in StakeRefPtr @StandardCrypto sat_svAS } } } } } } } } in let { sat_svAU [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svAU = Addr @StandardCrypto lvl58_svph ww1_svvw sat_svAT } in $wlvl1_sv48 sat_svAU s'4_svAH eta1_svAE }) `cast` (<(Word16, Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: ((Word16, Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) } in let { cont_svzF [Occ=OnceL1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r) [LclId, Arity=4, Str=<1L><1L><L><LC(S,L)>, Unf=OtherCon []] cont_svzF = \ (acc_svzG [Occ=Once1!] :: Word16) (eta1_svzH [Occ=Once1!, OS=OneShot] :: Int) (eta2_svzI [OS=OneShot] :: Version) (@r_X1H) (eta3_svzJ [Occ=OnceL2!, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H)) -> case acc_svzG of { W16# ipv_svzL [Occ=OnceL1] -> case eta1_svzH of wild5_svzM [Occ=Once1] { I# x1_svzN -> let { $weta_svzO [InlPrag=[2], Dmd=LC(S,L)] :: Word16 -> Int -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] $weta_svzO = \ (ww6_svzP [Occ=OnceL2] :: Word16) (ww7_svzQ [Occ=Once2] :: Int) -> case lvl61_svzu of { W8# x#1_svzS [Occ=Once1] -> case word8ToWord# x#1_svzS of sat_svzT [Occ=Once1] { __DEFAULT -> case and# 252## sat_svzT of { __DEFAULT -> let { sat_svA0 [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svA0 = \ (m8_svzV [Occ=Once1!] :: ((), Int)) -> case m8_svzV of { (_ [Occ=Dead], s'5_svzY [Occ=Once1]) -> let { sat_svzZ [Occ=Once1] :: (Word16, Int) [LclId] sat_svzZ = (ww6_svzP, s'5_svzY) } in eta3_svzJ sat_svzZ } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name3_ruZC lvl38_ruZI) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) ww7_svzQ) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svzI) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svA0; 128## -> let { sat_svA1 [Occ=Once1] :: (Word16, Int) [LclId] sat_svA1 = (ww6_svzP, ww7_svzQ) } in eta3_svzJ sat_svA1 } } } } in let { eta5_svA2 [InlPrag=[2], Occ=OnceL1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<1!P(L,L)>, Unf=OtherCon []] eta5_svA2 = \ (m7_svA3 [Occ=Once1!] :: (Word16, Int)) -> case m7_svA3 of { (ww6_svA5 [Occ=Once1], ww7_svA6 [Occ=Once1]) -> $weta_svzO ww6_svA5 ww7_svA6 } } in let { $wkarg1_svA7 [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svA7 = \ (ww6_svA8 :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww6_svA8 of ww7_svA9 { __DEFAULT -> case word8ToWord# ww7_svA9 of sat_svAa [Occ=Once1] { __DEFAULT -> case and# 128## sat_svAa of { __DEFAULT -> case +# ww6_svA8 1# of sat_svAc [Occ=Once1] { __DEFAULT -> let { sat_svAd [Occ=Once1] :: Int [LclId] sat_svAd = I# sat_svAc } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @Word16 $dMonadFail6_ruYJ name3_ruZC lvl36_ruZG) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N :: StateT Int (Decoder RealWorld) Word16 ~R# (Int -> Decoder RealWorld (Word16, Int)))) sat_svAd) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (Version -> Decoder RealWorld (Word16, Int)))) eta2_svzI) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H eta5_svA2 }; 0## -> case +# ww6_svA8 1# of sat_svAm [Occ=Once1] { __DEFAULT -> let { sat_svAn [Occ=Once1] :: Int [LclId] sat_svAn = I# sat_svAm } in case word8ToWord# ww7_svA9 of sat_svAh [Occ=Once1] { __DEFAULT -> case and# sat_svAh 65535## of sat_svAi [Occ=Once1] { __DEFAULT -> case word16ToWord# ipv_svzL of sat_svAe [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svAe 7# of sat_svAf [Occ=Once1] { __DEFAULT -> case and# sat_svAf 65535## of sat_svAg [Occ=Once1] { __DEFAULT -> case or# sat_svAg sat_svAi of sat_svAj [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svAj of sat_svAk [Occ=Once1] { __DEFAULT -> let { sat_svAl [Occ=Once1] :: Word16 [LclId] sat_svAl = W16# sat_svAk } in $weta_svzO sat_svAl sat_svAn } } } } } } } } } } } } in case ># x1_svzN lvl57_svne of { __DEFAULT -> $wkarg1_svA7 x1_svzN; 1# -> let { sat_svAv [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svAv = \ (m7_svAp [Occ=Once1!] :: ((), Int)) -> case m7_svAp of { (_ [Occ=Dead], ww7_svAs [Occ=Once1!]) -> case ww7_svAs of { I# ww8_svAu [Occ=Once1] -> $wkarg1_svA7 ww8_svAu } } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name3_ruZC lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) wild5_svzM) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svzI) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svAv } } } } in let { sat_svAC [Occ=Once1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> StateT Int (Decoder RealWorld) Word16 [LclId] sat_svAC = (\ (acc_svAw [Occ=Once1!] :: Word16) (eta1_svAx [Occ=Once1, OS=OneShot] :: Int) (eta2_svAy [Occ=Once1, OS=OneShot] :: Version) (@r_suIG) (eta3_svAz [Occ=Once1, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_suIG)) -> case acc_svAw of { W16# ww6_svAB [Occ=Once1] -> $wd1_svoB (cont_svzF `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16))) ww6_svAB eta1_svAx eta2_svAy @r_suIG eta3_svAz }) `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16)) } in $wd1_svoB sat_svAC 0#Word16 s'3_svzt ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version)) @(Addr StandardCrypto) sat_svAV } } in let { cont_svys [Occ=OnceL1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r) [LclId, Arity=4, Str=<1L><1L><L><LC(S,L)>, Unf=OtherCon []] cont_svys = \ (acc_svyt [Occ=Once1!] :: Word16) (eta1_svyu [Occ=Once1!, OS=OneShot] :: Int) (eta2_svyv [OS=OneShot] :: Version) (@r_X1H) (eta3_svyw [Occ=OnceL2!, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H)) -> case acc_svyt of { W16# ipv_svyy [Occ=OnceL1] -> case eta1_svyu of wild5_svyz [Occ=Once1] { I# x1_svyA -> let { $weta_svyB [InlPrag=[2], Dmd=LC(S,L)] :: Word16 -> Int -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] $weta_svyB = \ (ww6_svyC [Occ=OnceL2] :: Word16) (ww7_svyD [Occ=Once2] :: Int) -> case lvl60_svyj of { W8# x#1_svyF [Occ=Once1] -> case word8ToWord# x#1_svyF of sat_svyG [Occ=Once1] { __DEFAULT -> case and# 252## sat_svyG of { __DEFAULT -> let { sat_svyN [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svyN = \ (m8_svyI [Occ=Once1!] :: ((), Int)) -> case m8_svyI of { (_ [Occ=Dead], s'4_svyL [Occ=Once1]) -> let { sat_svyM [Occ=Once1] :: (Word16, Int) [LclId] sat_svyM = (ww6_svyC, s'4_svyL) } in eta3_svyw sat_svyM } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name2_ruZA lvl38_ruZI) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) ww7_svyD) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svyv) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svyN; 128## -> let { sat_svyO [Occ=Once1] :: (Word16, Int) [LclId] sat_svyO = (ww6_svyC, ww7_svyD) } in eta3_svyw sat_svyO } } } } in let { eta5_svyP [InlPrag=[2], Occ=OnceL1] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<1!P(L,L)>, Unf=OtherCon []] eta5_svyP = \ (m7_svyQ [Occ=Once1!] :: (Word16, Int)) -> case m7_svyQ of { (ww6_svyS [Occ=Once1], ww7_svyT [Occ=Once1]) -> $weta_svyB ww6_svyS ww7_svyT } } in let { $wkarg1_svyU [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svyU = \ (ww6_svyV :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww6_svyV of ww7_svyW { __DEFAULT -> case word8ToWord# ww7_svyW of sat_svyX [Occ=Once1] { __DEFAULT -> case and# 128## sat_svyX of { __DEFAULT -> case +# ww6_svyV 1# of sat_svyZ [Occ=Once1] { __DEFAULT -> let { sat_svz0 [Occ=Once1] :: Int [LclId] sat_svz0 = I# sat_svyZ } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @Word16 $dMonadFail6_ruYJ name2_ruZA lvl36_ruZG) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N :: StateT Int (Decoder RealWorld) Word16 ~R# (Int -> Decoder RealWorld (Word16, Int)))) sat_svz0) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (Version -> Decoder RealWorld (Word16, Int)))) eta2_svyv) `cast` (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R :: Decoder RealWorld (Word16, Int) ~R# (forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H eta5_svyP }; 0## -> case +# ww6_svyV 1# of sat_svz9 [Occ=Once1] { __DEFAULT -> let { sat_svza [Occ=Once1] :: Int [LclId] sat_svza = I# sat_svz9 } in case word8ToWord# ww7_svyW of sat_svz4 [Occ=Once1] { __DEFAULT -> case and# sat_svz4 65535## of sat_svz5 [Occ=Once1] { __DEFAULT -> case word16ToWord# ipv_svyy of sat_svz1 [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svz1 7# of sat_svz2 [Occ=Once1] { __DEFAULT -> case and# sat_svz2 65535## of sat_svz3 [Occ=Once1] { __DEFAULT -> case or# sat_svz3 sat_svz5 of sat_svz6 [Occ=Once1] { __DEFAULT -> case wordToWord16# sat_svz6 of sat_svz7 [Occ=Once1] { __DEFAULT -> let { sat_svz8 [Occ=Once1] :: Word16 [LclId] sat_svz8 = W16# sat_svz7 } in $weta_svyB sat_svz8 sat_svza } } } } } } } } } } } } in case ># x1_svyA lvl57_svne of { __DEFAULT -> $wkarg1_svyU x1_svyA; 1# -> let { sat_svzi [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld r_X1H) [LclId] sat_svzi = \ (m7_svzc [Occ=Once1!] :: ((), Int)) -> case m7_svzc of { (_ [Occ=Dead], ww7_svzf [Occ=Once1!]) -> case ww7_svzf of { I# ww8_svzh [Occ=Once1] -> $wkarg1_svyU ww8_svzh } } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name2_ruZA lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) wild5_svyz) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) eta2_svyv) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @r_X1H sat_svzi } } } } in let { sat_svzp [Occ=Once1, Dmd=LC(S,C(1,C(1,C(1,L))))] :: Word16 -> StateT Int (Decoder RealWorld) Word16 [LclId] sat_svzp = (\ (acc_svzj [Occ=Once1!] :: Word16) (eta1_svzk [Occ=Once1, OS=OneShot] :: Int) (eta2_svzl [Occ=Once1, OS=OneShot] :: Version) (@r_suJ3) (eta3_svzm [Occ=Once1, OS=OneShot] :: (Word16, Int) -> ST RealWorld (DecodeAction RealWorld r_suJ3)) -> case acc_svzj of { W16# ww6_svzo [Occ=Once1] -> $wd7_svnV (cont_svys `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16))) ww6_svzo eta1_svzk eta2_svzl @r_suJ3 eta3_svzm }) `cast` (<Word16>_R %<'Many>_N ->_R <Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <(Word16, Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word16>_N) :: (Word16 -> Int -> Version -> forall r. ((Word16, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# (Word16 -> StateT Int (Decoder RealWorld) Word16)) } in $wd7_svnV sat_svzp 0#Word16 ww5_svyi ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version)) @(Addr StandardCrypto) sat_svAW } in let { $wk2_svAX [InlPrag=[2], Dmd=LC(S,L)] :: Word32 -> Int -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] $wk2_svAX = \ (ww4_svAY [Occ=OnceL2] :: Word32) (ww5_svAZ [Occ=Once2] :: Int) -> case lvl59_svvE of { W8# x#5_svB1 [Occ=Once1] -> case word8ToWord# x#5_svB1 of sat_svB2 [Occ=Once1] { __DEFAULT -> case and# 240## sat_svB2 of { __DEFAULT -> let { sat_svB8 [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svB8 = \ (m11_svB4 [Occ=Once1!] :: ((), Int)) -> case m11_svB4 of { (_ [Occ=Dead], s'7_svB7 [Occ=Once1]) -> $wk1_svyg ww4_svAY s'7_svB7 } } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl40_ruZK) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) ww5_svAZ) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svB8; 128## -> $wk1_svyg ww4_svAY ww5_svAZ } } } } in let { k2_svB9 [InlPrag=[2], Occ=OnceL1] :: (Word32, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<1!P(L,L)>, Unf=OtherCon []] k2_svB9 = \ (m10_svBa [Occ=Once1!] :: (Word32, Int)) -> case m10_svBa of { (ww4_svBc [Occ=Once1], ww5_svBd [Occ=Once1]) -> $wk2_svAX ww4_svBc ww5_svBd } } in let { $wkarg1_svBe [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg1_svBe = \ (ww4_svBf :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww4_svBf of ww5_svBg { __DEFAULT -> case +# ww4_svBf 1# of karg2_svBh { __DEFAULT -> case word8ToWord# ww5_svBg of sat_svBi [Occ=Once1] { __DEFAULT -> case and# 128## sat_svBi of { __DEFAULT -> case word8ToWord# ww5_svBg of sat_svBl [Occ=Once1] { __DEFAULT -> case and# 127## sat_svBl of sat_svBm [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svBm of ds1_svBk [Occ=OnceL2] { __DEFAULT -> let { $wkarg3_svBn [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg3_svBn = \ (ww6_svBo :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww6_svBo of ww7_svBp { __DEFAULT -> case +# ww6_svBo 1# of karg4_svBq { __DEFAULT -> case word8ToWord# ww7_svBp of sat_svBr [Occ=Once1] { __DEFAULT -> case and# 128## sat_svBr of { __DEFAULT -> case word8ToWord# ww7_svBp of sat_svBx [Occ=Once1] { __DEFAULT -> case and# 127## sat_svBx of sat_svBy [Occ=Once1] { __DEFAULT -> case word32ToWord# ds1_svBk of sat_svBu [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svBu 7# of sat_svBv [Occ=Once1] { __DEFAULT -> case and# sat_svBv 4294967295## of sat_svBw [Occ=Once1] { __DEFAULT -> case or# sat_svBw sat_svBy of sat_svBz [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svBz of ipv_svBt [Occ=OnceL2] { __DEFAULT -> let { $wkarg5_svBA [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg5_svBA = \ (ww8_svBB :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww8_svBB of ww9_svBC { __DEFAULT -> case +# ww8_svBB 1# of karg6_svBD { __DEFAULT -> case word8ToWord# ww9_svBC of sat_svBE [Occ=Once1] { __DEFAULT -> case and# 128## sat_svBE of { __DEFAULT -> case word8ToWord# ww9_svBC of sat_svBK [Occ=Once1] { __DEFAULT -> case and# 127## sat_svBK of sat_svBL [Occ=Once1] { __DEFAULT -> case word32ToWord# ipv_svBt of sat_svBH [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svBH 7# of sat_svBI [Occ=Once1] { __DEFAULT -> case and# sat_svBI 4294967295## of sat_svBJ [Occ=Once1] { __DEFAULT -> case or# sat_svBJ sat_svBL of sat_svBM [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svBM of ipv1_svBG [Occ=OnceL2] { __DEFAULT -> let { $wkarg7_svBN [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg7_svBN = \ (ww10_svBO :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww10_svBO of ww11_svBP { __DEFAULT -> case +# ww10_svBO 1# of karg8_svBQ { __DEFAULT -> case word8ToWord# ww11_svBP of sat_svBR [Occ=Once1] { __DEFAULT -> case and# 128## sat_svBR of { __DEFAULT -> case word8ToWord# ww11_svBP of sat_svBX [Occ=Once1] { __DEFAULT -> case and# 127## sat_svBX of sat_svBY [Occ=Once1] { __DEFAULT -> case word32ToWord# ipv1_svBG of sat_svBU [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svBU 7# of sat_svBV [Occ=Once1] { __DEFAULT -> case and# sat_svBV 4294967295## of sat_svBW [Occ=Once1] { __DEFAULT -> case or# sat_svBW sat_svBY of sat_svBZ [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svBZ of acc_svBT [Occ=OnceL1] { __DEFAULT -> let { $wkarg9_svC0 [InlPrag=[2], Occ=OnceL2!, Dmd=LC(S,L)] :: Int# -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId, Arity=1, Str=<L>, Unf=OtherCon []] $wkarg9_svC0 = \ (ww12_svC1 :: Int#) -> case $wunsafeShortByteStringIndex ww_sv46 ww12_svC1 of ww13_svC2 { __DEFAULT -> case word8ToWord# ww13_svC2 of sat_svC3 [Occ=Once1] { __DEFAULT -> case and# 128## sat_svC3 of { __DEFAULT -> case +# ww12_svC1 1# of sat_svC5 [Occ=Once1] { __DEFAULT -> let { sat_svC6 [Occ=Once1] :: Int [LclId] sat_svC6 = I# sat_svC5 } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @Word32 $dMonadFail6_ruYJ name1_ruZy lvl36_ruZG) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Word32>_N :: StateT Int (Decoder RealWorld) Word32 ~R# (Int -> Decoder RealWorld (Word32, Int)))) sat_svC6) `cast` (N:Decoder[0] <RealWorld>_N <(Word32, Int)>_R :: Decoder RealWorld (Word32, Int) ~R# (Version -> Decoder RealWorld (Word32, Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <(Word32, Int)>_R :: Decoder RealWorld (Word32, Int) ~R# (forall r. ((Word32, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) k2_svB9 }; 0## -> case +# ww12_svC1 1# of sat_svCf [Occ=Once1] { __DEFAULT -> let { sat_svCg [Occ=Once1] :: Int [LclId] sat_svCg = I# sat_svCf } in case word8ToWord# ww13_svC2 of sat_svCa [Occ=Once1] { __DEFAULT -> case and# sat_svCa 4294967295## of sat_svCb [Occ=Once1] { __DEFAULT -> case word32ToWord# acc_svBT of sat_svC7 [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svC7 7# of sat_svC8 [Occ=Once1] { __DEFAULT -> case and# sat_svC8 4294967295## of sat_svC9 [Occ=Once1] { __DEFAULT -> case or# sat_svC9 sat_svCb of sat_svCc [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svCc of sat_svCd [Occ=Once1] { __DEFAULT -> let { sat_svCe [Occ=Once1] :: Word32 [LclId] sat_svCe = W32# sat_svCd } in $wk2_svAX sat_svCe sat_svCg } } } } } } } } } } } } in case ># karg8_svBQ lvl57_svne of { __DEFAULT -> $wkarg9_svC0 karg8_svBQ; 1# -> let { sat_svCp [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svCp = \ (m10_svCj [Occ=Once1!] :: ((), Int)) -> case m10_svCj of { (_ [Occ=Dead], ww13_svCm [Occ=Once1!]) -> case ww13_svCm of { I# ww14_svCo [Occ=Once1] -> $wkarg9_svC0 ww14_svCo } } } in let { sat_svCi [Occ=Once1] :: Int [LclId] sat_svCi = I# karg8_svBQ } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svCi) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svCp } } } } } } } }; 0## -> case word8ToWord# ww11_svBP of sat_svCt [Occ=Once1] { __DEFAULT -> case and# sat_svCt 4294967295## of sat_svCu [Occ=Once1] { __DEFAULT -> case word32ToWord# ipv1_svBG of sat_svCq [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svCq 7# of sat_svCr [Occ=Once1] { __DEFAULT -> case and# sat_svCr 4294967295## of sat_svCs [Occ=Once1] { __DEFAULT -> case or# sat_svCs sat_svCu of sat_svCv [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svCv of sat_svCw [Occ=Once1] { __DEFAULT -> $s$wk1_svvG karg8_svBQ sat_svCw } } } } } } } } } } } } in case ># karg6_svBD lvl57_svne of { __DEFAULT -> $wkarg7_svBN karg6_svBD; 1# -> let { sat_svCF [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svCF = \ (m9_svCz [Occ=Once1!] :: ((), Int)) -> case m9_svCz of { (_ [Occ=Dead], ww11_svCC [Occ=Once1!]) -> case ww11_svCC of { I# ww12_svCE [Occ=Once1] -> $wkarg7_svBN ww12_svCE } } } in let { sat_svCy [Occ=Once1] :: Int [LclId] sat_svCy = I# karg6_svBD } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svCy) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svCF } } } } } } } }; 0## -> case word8ToWord# ww9_svBC of sat_svCJ [Occ=Once1] { __DEFAULT -> case and# sat_svCJ 4294967295## of sat_svCK [Occ=Once1] { __DEFAULT -> case word32ToWord# ipv_svBt of sat_svCG [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svCG 7# of sat_svCH [Occ=Once1] { __DEFAULT -> case and# sat_svCH 4294967295## of sat_svCI [Occ=Once1] { __DEFAULT -> case or# sat_svCI sat_svCK of sat_svCL [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svCL of sat_svCM [Occ=Once1] { __DEFAULT -> $s$wk1_svvG karg6_svBD sat_svCM } } } } } } } } } } } } in case ># karg4_svBq lvl57_svne of { __DEFAULT -> $wkarg5_svBA karg4_svBq; 1# -> let { sat_svCV [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svCV = \ (m8_svCP [Occ=Once1!] :: ((), Int)) -> case m8_svCP of { (_ [Occ=Dead], ww9_svCS [Occ=Once1!]) -> case ww9_svCS of { I# ww10_svCU [Occ=Once1] -> $wkarg5_svBA ww10_svCU } } } in let { sat_svCO [Occ=Once1] :: Int [LclId] sat_svCO = I# karg4_svBq } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svCO) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svCV } } } } } } } }; 0## -> case word8ToWord# ww7_svBp of sat_svCZ [Occ=Once1] { __DEFAULT -> case and# sat_svCZ 4294967295## of sat_svD0 [Occ=Once1] { __DEFAULT -> case word32ToWord# ds1_svBk of sat_svCW [Occ=Once1] { __DEFAULT -> case uncheckedShiftL# sat_svCW 7# of sat_svCX [Occ=Once1] { __DEFAULT -> case and# sat_svCX 4294967295## of sat_svCY [Occ=Once1] { __DEFAULT -> case or# sat_svCY sat_svD0 of sat_svD1 [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svD1 of sat_svD2 [Occ=Once1] { __DEFAULT -> $s$wk1_svvG karg4_svBq sat_svD2 } } } } } } } } } } } } in case ># karg2_svBh lvl57_svne of { __DEFAULT -> $wkarg3_svBn karg2_svBh; 1# -> let { sat_svDb [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svDb = \ (m7_svD5 [Occ=Once1!] :: ((), Int)) -> case m7_svD5 of { (_ [Occ=Dead], ww7_svD8 [Occ=Once1!]) -> case ww7_svD8 of { I# ww8_svDa [Occ=Once1] -> $wkarg3_svBn ww8_svDa } } } in let { sat_svD4 [Occ=Once1] :: Int [LclId] sat_svD4 = I# karg2_svBh } in ((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) sat_svD4) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svDb } } } }; 0## -> case word8ToWord# ww5_svBg of sat_svDc [Occ=Once1] { __DEFAULT -> case wordToWord32# sat_svDc of sat_svDd [Occ=Once1] { __DEFAULT -> $s$wk1_svvG karg2_svBh sat_svDd } } } } } } } in case ># x_svvD lvl57_svne of { __DEFAULT -> (($wkarg1_svBe x_svvD) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svvy; 1# -> let { sat_svDl [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svDl = \ (m6_svDf [Occ=Once1!] :: ((), Int)) -> case m6_svDf of { (_ [Occ=Dead], ww5_svDi [Occ=Once1!]) -> case ww5_svDi of { I# ww6_svDk [Occ=Once1] -> $wkarg1_svBe ww6_svDk } } } in ((((((((failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ name1_ruZy lvl34_ruZE) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) wild4_svvC) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svDl) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svvy } } }; 0## -> case and# 32## wild_svnb of { __DEFAULT -> case ww3_svvx of wild9_svDn [Occ=Once1] { I# ww4_svDo -> case $wpackBytesMaybe @(SizeHash (ADDRHASH StandardCrypto)) ($fHashAlgorithmBlake2b_5 `cast` (Sym (N:SNat[0] <28>_N) ; Sym (N:KnownNat[0] ((SizeHash (D:R:ADDRHASHStandardCrypto[0]))_N ; D:R:SizeHashBlake2b_224[0])) :: Natural ~R# KnownNat (SizeHash (ADDRHASH StandardCrypto)))) (m1_svnf `cast` (Sym (N:ShortByteString[0]) :: ByteArray ~R# ShortByteString)) ww4_svDo of { Nothing -> case >=# ww4_svDo 0# of { __DEFAULT -> (# eta_svvy, lvl27_ruZr @(Addr StandardCrypto) #); 1# -> let { sat_svDE [Occ=Once1] :: (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svDE = (\ (x1_svDv [Occ=Once1!] :: (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)) (eta1_svDw [Occ=Once1, OS=OneShot] :: State# RealWorld) -> case x1_svDv of { (a3_svDy [Occ=Once1], s'2_svDz [Occ=Once1]) -> let { sat_svDC [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svDC = case a3_svDy `cast` (N:Hash[0] <ADDRHASH StandardCrypto>_N <EraIndependentScript>_P :: Hash (ADDRHASH StandardCrypto) EraIndependentScript ~R# PackedBytes (SizeHash (ADDRHASH StandardCrypto))) of nt_svDA [Occ=Once1] { __DEFAULT -> let { sat_svDB [Occ=Once1] :: Credential 'Staking StandardCrypto [LclId] sat_svDB = ScriptHashObj @'Staking @StandardCrypto (nt_svDA `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <EraIndependentScript>_P) ; Sym (N:ScriptHash[0] <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# ScriptHash StandardCrypto)) } in StakeRefBase @StandardCrypto sat_svDB } } in let { sat_svDD [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svDD = Addr @StandardCrypto lvl58_svph ww1_svvw sat_svDC } in $wlvl1_sv48 sat_svDD s'2_svDz eta1_svDw }) `cast` (<(Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: ((Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# ((Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) } in let { sat_svDu [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svDu = let { sat_svDt [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svDt = case -# len_sv47 ww4_svDo of sat_svDr [Occ=Once1] { __DEFAULT -> case itos sat_svDr ([] @Char) of sat_svDs [Occ=Once1, Dmd=1L] { __DEFAULT -> ++ @Char sat_svDs lvl32_ruZw } } } in unpackAppendCString# lvl48_ruZT sat_svDt } in ((((((((failDecoding @(StateT Int (Decoder RealWorld)) @(Hash (ADDRHASH StandardCrypto) EraIndependentScript) $dMonadFail6_ruYJ lvl29_ruZt sat_svDu) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Hash (ADDRHASH StandardCrypto) EraIndependentScript>_N :: StateT Int (Decoder RealWorld) (Hash (ADDRHASH StandardCrypto) EraIndependentScript) ~R# (Int -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)))) wild9_svDn) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) ~R# (Version -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) ~R# (forall r. ((Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svDE) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svvy }; Just a3_svDF [Occ=Once1] -> case +# ww4_svDo 28# of sat_svDK [Occ=Once1] { __DEFAULT -> let { sat_svDL [Occ=Once1, Dmd=1L] :: Int [LclId] sat_svDL = I# sat_svDK } in let { sat_svDI [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svDI = case a3_svDF of nt_svDG [Occ=Once1] { __DEFAULT -> let { sat_svDH [Occ=Once1] :: Credential 'Staking StandardCrypto [LclId] sat_svDH = ScriptHashObj @'Staking @StandardCrypto (nt_svDG `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <EraIndependentScript>_P) ; Sym (N:ScriptHash[0] <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# ScriptHash StandardCrypto)) } in StakeRefBase @StandardCrypto sat_svDH } } in let { sat_svDJ [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svDJ = Addr @StandardCrypto lvl58_svph ww1_svvw sat_svDI } in $wlvl1_sv48 sat_svDJ sat_svDL eta_svvy } } }; 0## -> case ww3_svvx of wild9_svDM [Occ=Once1] { I# ww4_svDN -> case $wpackBytesMaybe @(SizeHash (ADDRHASH StandardCrypto)) ($fHashAlgorithmBlake2b_5 `cast` (Sym (N:SNat[0] <28>_N) ; Sym (N:KnownNat[0] ((SizeHash (D:R:ADDRHASHStandardCrypto[0]))_N ; D:R:SizeHashBlake2b_224[0])) :: Natural ~R# KnownNat (SizeHash (ADDRHASH StandardCrypto)))) (m1_svnf `cast` (Sym (N:ShortByteString[0]) :: ByteArray ~R# ShortByteString)) ww4_svDN of { Nothing -> case >=# ww4_svDN 0# of { __DEFAULT -> (# eta_svvy, lvl27_ruZr @(Addr StandardCrypto) #); 1# -> let { sat_svE3 [Occ=Once1] :: (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svE3 = (\ (x1_svDU [Occ=Once1!] :: (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)) (eta1_svDV [Occ=Once1, OS=OneShot] :: State# RealWorld) -> case x1_svDU of { (a3_svDX [Occ=Once1], s'2_svDY [Occ=Once1]) -> let { sat_svE1 [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svE1 = case a3_svDX `cast` (N:Hash[0] <ADDRHASH StandardCrypto>_N <VerKeyDSIGN (DSIGN StandardCrypto)>_P :: Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)) ~R# PackedBytes (SizeHash (ADDRHASH StandardCrypto))) of nt_svDZ [Occ=Once1] { __DEFAULT -> let { sat_svE0 [Occ=Once1] :: Credential 'Staking StandardCrypto [LclId] sat_svE0 = KeyHashObj @'Staking @StandardCrypto (nt_svDZ `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <VerKeyDSIGN (DSIGN StandardCrypto)>_P) ; Sym (N:KeyHash[0] <'Staking>_P <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# KeyHash 'Staking StandardCrypto)) } in StakeRefBase @StandardCrypto sat_svE0 } } in let { sat_svE2 [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svE2 = Addr @StandardCrypto lvl58_svph ww1_svvw sat_svE1 } in $wlvl1_sv48 sat_svE2 s'2_svDY eta1_svDV }) `cast` (<(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: ((Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# ((Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) } in let { sat_svDT [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svDT = let { sat_svDS [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svDS = case -# len_sv47 ww4_svDN of sat_svDQ [Occ=Once1] { __DEFAULT -> case itos sat_svDQ ([] @Char) of sat_svDR [Occ=Once1, Dmd=1L] { __DEFAULT -> ++ @Char sat_svDR lvl32_ruZw } } } in unpackAppendCString# lvl48_ruZT sat_svDS } in ((((((((failDecoding @(StateT Int (Decoder RealWorld)) @(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))) $dMonadFail6_ruYJ lvl29_ruZt sat_svDT) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))>_N :: StateT Int (Decoder RealWorld) (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))) ~R# (Int -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)))) wild9_svDM) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) ~R# (Version -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) ~R# (forall r. ((Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svE3) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svvy }; Just a3_svE4 [Occ=Once1] -> case +# ww4_svDN 28# of sat_svE9 [Occ=Once1] { __DEFAULT -> let { sat_svEa [Occ=Once1, Dmd=1L] :: Int [LclId] sat_svEa = I# sat_svE9 } in let { sat_svE7 [Occ=Once1] :: StakeReference StandardCrypto [LclId] sat_svE7 = case a3_svE4 of nt_svE5 [Occ=Once1] { __DEFAULT -> let { sat_svE6 [Occ=Once1] :: Credential 'Staking StandardCrypto [LclId] sat_svE6 = KeyHashObj @'Staking @StandardCrypto (nt_svE5 `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <VerKeyDSIGN (DSIGN StandardCrypto)>_P) ; Sym (N:KeyHash[0] <'Staking>_P <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# KeyHash 'Staking StandardCrypto)) } in StakeRefBase @StandardCrypto sat_svE6 } } in let { sat_svE8 [Occ=Once1] :: Addr StandardCrypto [LclId] sat_svE8 = Addr @StandardCrypto lvl58_svph ww1_svvw sat_svE7 } in $wlvl1_sv48 sat_svE8 sat_svEa eta_svvy } } } } } } in let { lvl59_svEb [Occ=OnceL1] :: (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> State# RealWorld -> (# State# RealWorld, DecodeAction RealWorld (Addr StandardCrypto) #) [LclId, Arity=2, Str=<1P(ML,1L)><L>, Unf=OtherCon []] lvl59_svEb = \ (x_svEc [Occ=Once1!] :: (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)) (eta_svEd [Occ=Once1, OS=OneShot] :: State# RealWorld) -> case x_svEc of { (a2_svEf [Occ=Once1], s'1_svEg [Occ=Once1]) -> let { sat_svEi [Occ=Once1] :: PaymentCredential StandardCrypto [LclId] sat_svEi = case a2_svEf `cast` (N:Hash[0] <ADDRHASH StandardCrypto>_N <VerKeyDSIGN (DSIGN StandardCrypto)>_P :: Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)) ~R# PackedBytes (SizeHash (ADDRHASH StandardCrypto))) of nt_svEh [Occ=Once1] { __DEFAULT -> KeyHashObj @'Payment @StandardCrypto (nt_svEh `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <VerKeyDSIGN (DSIGN StandardCrypto)>_P) ; Sym (N:KeyHash[0] <'Payment>_P <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# KeyHash 'Payment StandardCrypto)) } } in $wlvl2_svvv sat_svEi s'1_svEg eta_svEd } } in let { lvl60_svEj [Occ=OnceL1] :: (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> State# RealWorld -> (# State# RealWorld, DecodeAction RealWorld (Addr StandardCrypto) #) [LclId, Arity=2, Str=<1P(ML,1L)><L>, Unf=OtherCon []] lvl60_svEj = \ (x_svEk [Occ=Once1!] :: (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)) (eta_svEl [Occ=Once1, OS=OneShot] :: State# RealWorld) -> case x_svEk of { (a2_svEn [Occ=Once1], s'1_svEo [Occ=Once1]) -> let { sat_svEq [Occ=Once1] :: PaymentCredential StandardCrypto [LclId] sat_svEq = case a2_svEn `cast` (N:Hash[0] <ADDRHASH StandardCrypto>_N <EraIndependentScript>_P :: Hash (ADDRHASH StandardCrypto) EraIndependentScript ~R# PackedBytes (SizeHash (ADDRHASH StandardCrypto))) of nt_svEp [Occ=Once1] { __DEFAULT -> ScriptHashObj @'Payment @StandardCrypto (nt_svEp `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <EraIndependentScript>_P) ; Sym (N:ScriptHash[0] <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# ScriptHash StandardCrypto)) } } in $wlvl2_svvv sat_svEq s'1_svEo eta_svEl } } in let { sat_svEW [Occ=Once1] :: ((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) [LclId] sat_svEW = (\ (m4_svEr [Occ=Once1!] :: ((), Int)) (eta_svEs [Occ=Once6, OS=OneShot] :: State# RealWorld) -> case m4_svEr of { (_ [Occ=Dead], s'1_svEv [Occ=Once1!]) -> case s'1_svEv of { I# x_svEx [Occ=Once1] -> case +# x_svEx 1# of karg_svEy { __DEFAULT -> case and# 16## wild_svnb of { __DEFAULT -> case $wpackBytesMaybe @(SizeHash (ADDRHASH StandardCrypto)) ($fHashAlgorithmBlake2b_5 `cast` (Sym (N:SNat[0] <28>_N) ; Sym (N:KnownNat[0] ((SizeHash (D:R:ADDRHASHStandardCrypto[0]))_N ; D:R:SizeHashBlake2b_224[0])) :: Natural ~R# KnownNat (SizeHash (ADDRHASH StandardCrypto)))) (m1_svnf `cast` (Sym (N:ShortByteString[0]) :: ByteArray ~R# ShortByteString)) karg_svEy of { Nothing -> case >=# karg_svEy 0# of { __DEFAULT -> (# eta_svEs, lvl27_ruZr @(Addr StandardCrypto) #); 1# -> let { sat_svEG [Occ=Once1] :: Int [LclId] sat_svEG = I# karg_svEy } in let { sat_svEF [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svEF = let { sat_svEE [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svEE = case -# len_sv47 karg_svEy of sat_svEC [Occ=Once1] { __DEFAULT -> case itos sat_svEC ([] @Char) of sat_svED [Occ=Once1, Dmd=1L] { __DEFAULT -> ++ @Char sat_svED lvl32_ruZw } } } in unpackAppendCString# lvl48_ruZT sat_svEE } in ((((((((failDecoding @(StateT Int (Decoder RealWorld)) @(Hash (ADDRHASH StandardCrypto) EraIndependentScript) $dMonadFail6_ruYJ lvl29_ruZt sat_svEF) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Hash (ADDRHASH StandardCrypto) EraIndependentScript>_N :: StateT Int (Decoder RealWorld) (Hash (ADDRHASH StandardCrypto) EraIndependentScript) ~R# (Int -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)))) sat_svEG) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) ~R# (Version -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) ~R# (forall r. ((Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) (lvl60_svEj `cast` (<(Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: ((Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# ((Hash (ADDRHASH StandardCrypto) EraIndependentScript, Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))))) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svEs }; Just a3_svEH [Occ=Once1] -> let { sat_svEK [Occ=Once1] :: Credential 'Payment StandardCrypto [LclId] sat_svEK = case a3_svEH of nt_svEJ [Occ=Once1] { __DEFAULT -> ScriptHashObj @'Payment @StandardCrypto (nt_svEJ `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <EraIndependentScript>_P) ; Sym (N:ScriptHash[0] <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# ScriptHash StandardCrypto)) } } in case +# karg_svEy 28# of sat_svEI [Occ=Once1] { __DEFAULT -> $s$wlvl_svpj sat_svEI sat_svEK eta_svEs } }; 0## -> case $wpackBytesMaybe @(SizeHash (ADDRHASH StandardCrypto)) ($fHashAlgorithmBlake2b_5 `cast` (Sym (N:SNat[0] <28>_N) ; Sym (N:KnownNat[0] ((SizeHash (D:R:ADDRHASHStandardCrypto[0]))_N ; D:R:SizeHashBlake2b_224[0])) :: Natural ~R# KnownNat (SizeHash (ADDRHASH StandardCrypto)))) (m1_svnf `cast` (Sym (N:ShortByteString[0]) :: ByteArray ~R# ShortByteString)) karg_svEy of { Nothing -> case >=# karg_svEy 0# of { __DEFAULT -> (# eta_svEs, lvl27_ruZr @(Addr StandardCrypto) #); 1# -> let { sat_svER [Occ=Once1] :: Int [LclId] sat_svER = I# karg_svEy } in let { sat_svEQ [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svEQ = let { sat_svEP [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svEP = case -# len_sv47 karg_svEy of sat_svEN [Occ=Once1] { __DEFAULT -> case itos sat_svEN ([] @Char) of sat_svEO [Occ=Once1, Dmd=1L] { __DEFAULT -> ++ @Char sat_svEO lvl32_ruZw } } } in unpackAppendCString# lvl48_ruZT sat_svEP } in ((((((((failDecoding @(StateT Int (Decoder RealWorld)) @(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))) $dMonadFail6_ruYJ lvl29_ruZt sat_svEQ) `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))>_N :: StateT Int (Decoder RealWorld) (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto))) ~R# (Int -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)))) sat_svER) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) ~R# (Version -> Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)>_R :: Decoder RealWorld (Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) ~R# (forall r. ((Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) (lvl59_svEb `cast` (<(Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: ((Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# ((Hash (ADDRHASH StandardCrypto) (VerKeyDSIGN (DSIGN StandardCrypto)), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))))) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_svEs }; Just a3_svES [Occ=Once1] -> let { sat_svEV [Occ=Once1] :: Credential 'Payment StandardCrypto [LclId] sat_svEV = case a3_svES of nt_svEU [Occ=Once1] { __DEFAULT -> KeyHashObj @'Payment @StandardCrypto (nt_svEU `cast` (Sym (N:Hash[0] <ADDRHASH StandardCrypto>_N <VerKeyDSIGN (DSIGN StandardCrypto)>_P) ; Sym (N:KeyHash[0] <'Payment>_P <StandardCrypto>_N) :: PackedBytes (SizeHash (ADDRHASH StandardCrypto)) ~R# KeyHash 'Payment StandardCrypto)) } } in case +# karg_svEy 28# of sat_svET [Occ=Once1] { __DEFAULT -> $s$wlvl_svpj sat_svET sat_svEV eta_svEs } } } } } }) `cast` (<((), Int)>_R %<'Many>_N ->_R Sym (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R) :: (((), Int) -> STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto))) ~R# (((), Int) -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) } in (((((eta4_svnd `cast` (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N :: StateT Int (Decoder RealWorld) () ~R# (Int -> Decoder RealWorld ((), Int)))) s'_svn7) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (Version -> Decoder RealWorld ((), Int)))) ($fBoundedVersion1 `cast` (Sym (N:Version[0]) :: Word64 ~R# Version))) `cast` (N:Decoder[0] <RealWorld>_N <((), Int)>_R :: Decoder RealWorld ((), Int) ~R# (forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)))) @(Addr StandardCrypto) sat_svEW } } } in case and# 142## wild_svnb of { __DEFAULT -> let { sat_svF0 [Occ=Once1, Dmd=ML] :: [Char] [LclId] sat_svF0 = let { sat_svEZ [Occ=Once1, Dmd=ML] :: String [LclId] sat_svEZ = let { sat_svEY [Occ=Once1] :: Word8 [LclId] sat_svEY = W8# ww2_svna } in showIntAtBase @Word8 $fIntegralWord8 lvl23_ruZn intToDigit sat_svEY ([] @Char) } in unpackAppendCString# lvl49_ruZU sat_svEZ } in case failDecoding @(StateT Int (Decoder RealWorld)) @() $dMonadFail6_ruYJ lvl22_ruZm sat_svF0 of sat_svF1 [Occ=Once1, Dmd=1C(1,C(1,C(1,L)))] { __DEFAULT -> jump $j2_svnc sat_svF1 }; 0## -> jump $j2_svnc (lvl24_ruZo `cast` (<Int>_R %<'Many>_N ->_R <Version>_R %<'Many>_N ->_R Sym (N:Decoder[0] <RealWorld>_N <((), Int)>_R) ; Sym (N:Decoder[0] <RealWorld>_N <((), Int)>_R) ; Sym (N:StateT[0] <Int>_N <Decoder RealWorld>_R <()>_N) :: (Int -> Version -> forall r. (((), Int) -> ST RealWorld (DecodeAction RealWorld r)) -> ST RealWorld (DecodeAction RealWorld r)) ~R# StateT Int (Decoder RealWorld) ())) }) `cast` (N:ST[0] <RealWorld>_N <DecodeAction RealWorld (Addr StandardCrypto)>_R :: ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ~R# STRep RealWorld (DecodeAction RealWorld (Addr StandardCrypto)))) eta_B0 Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/GHC/Utils/Panic.hs:190:37 in ghc-9.10.1-inplace:GHC.Utils.Panic pprPanic, called at compiler/GHC/CoreToStg.hs:406:16 in ghc-9.10.1-inplace:GHC.CoreToStg CallStack (from HasCallStack): panic, called at compiler/GHC/Utils/Error.hs:507:29 in ghc-9.10.1-inplace:GHC.Utils.Error Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug Error: cabal: Failed to build bench:address from ledger-state-9.9.9.9.
- Developer
@erikd Posting a big reproducer is fine, otherwise seems very hard to make progress.
Collapse replies - Author Developer
I would have thought that since the "coreToStgExpr - Invalid app head" identifies exactly where the abort happens, I would not have thought the reproducer was actually that interesting.
The tar bzip file is 18 Meg and this bug tracker will not allow me to submit anything bigger than 10Meg.
Edited by Erik de Castro Lopo
- Developer
I would have thought that since the "coreToStgExpr - Invalid app head" identifies exactly where the abort happens, I would not have thought the reproducer was actually that interesting.
It does say where it come from -- but it can be super hard to guess how that crash arose. A reproducer is really helpful, even if it is big.
The tar bzip file is 18 Meg and this bug tracker will not allow me to submit anything bigger than 10Meg.
Can you put it somewhere else, and share a link to it? Or say how to git-clone a repo?
- Author Developer
Ok, reproducer is at http://www.mega-nerd.com/erikd/cardano-ledger-min-reproducer.tbz
Collapse replies - Developer
Thanks, I am trying.
1 - Developer
How do I provision the
blst
library? (and other system dependencies). I tried using the version ofblst
package on nixpkgs but that doesn't get picked up by pkg-config. - Author Developer
Sorry, I had forgotten about that dependency.
I have
libblst
installed at~/Local/lib/libblst.a
and the following pkgc-nfig file at~/Local/lib/pkgconfig/libblst.pc
prefix=/home/erikd/Local exec_prefix=${prefix} libdir=${prefix}/lib includedir=${prefix}/include/blst Name: libblst Version: 0.3.10 Description: Multilingual BLS12-381 signature library Cflags: -I${includedir} Libs: -L${libdir} -lblst
And the following env var set:
PKG_CONFIG_PATH=/home/erikd/Local/lib/pkgconfig
Does that help?
Edited by Erik de Castro Lopo - Developer
I entered the nix shell provided by https://github.com/IntersectMBO/cardano-ledger (using
nix develop
) and then can reproduce the issue. 2 - Developer
@erikd If you want a workaround, compiler the module with
-fno-spec-constr
. - Author Developer
Thanks, if I need it I will try that. Otherwise, happy to wait for a fix.
- Developer
Perhaps related to 66dc09b1
I am building a 9.10 compiler to be able to debug further.
- Developer
@sgraf812 @simonpj The issue is due to
Note [Eta expansion of argument in CorePrep] Wrinkle (EA1)
Workaround: Run with
-fno-do-clever-arg-eta-expansion
.cpeEtaExpandArg
sees something like..\ (m3_svnH :: ((), Int)) -> case m3_svnH of { (a1_svnJ, s'_svnK) -> case <# 0# len_sv4K of { __DEFAULT -> case lvl47_rv0t ww_sv4J of {}; 1# -> case indexWord8Array# ww_sv4J 0# of ww2_svnN { __DEFAULT -> case word8ToWord# ww2_svnN of wild_svnO { __DEFAULT -> join { $j2_svnP [Dmd=1C(1,L)] :: StateT Int (Decoder RealWorld) () -> ST RealWorld (DecodeAction RealWorld (Addr StandardCrypto)) ... 6000 more lines
has_join_in_tail_context
returnsFalse
because the expression starts with a value lambda. It then eta expands the argument which leads to this panic in CoreToStg (nearly precisely described already in the Note). - Developer
Thank you for debugging. My guess is that we should just delete the
isTyVar b
guard. That is the principled solution because if we cannot eta-expande ==> \y. e y
because it has a join in tail context, then we shouldn't eta-expand\x. e ==> \x y. e y
either. Maybe rename the function towould_eta_expand_join
.The new definition:
has_join_in_tail_context (Let bs e) = isJoinBind bs || has_join_in_tail_context e has_join_in_tail_context (Lam b e) = has_join_in_tail_context e has_join_in_tail_context (Cast e _) = has_join_in_tail_context e has_join_in_tail_context (Tick _ e) = has_join_in_tail_context e has_join_in_tail_context (Case _ _ _ alts) = any has_join_in_tail_context (rhssOfAlts alts) has_join_in_tail_context _ = False
@simonpj could you verify that this would be all the cases to consider? I think so:
-
App
:e a
cannot possibly contain a join in tail position because we would have simplified -
Type
/Coercion
/Lit
: Not a function type -
Var
: Would not eta over a join point
(would be nice to use Or patterns here :))
-
- Developer
In the meantime, can you perhaps produce a smaller reproducer by decreasing the unfolding threshold?
Collapse replies - Developer
I don't intend to spend any more time minimising this issue, it is a very large project.
- Developer
We tried deleting the guard and it does fix the issue. However I'm not able to judge whether this is a "proper fix" or just some workaround.
- sheaf added Phigh Tbug compiler crash core prep and lowering labels
added Phigh Tbug compiler crash core prep and lowering labels
- sheaf added Arity and eta conversion label and removed needs triage label
added Arity and eta conversion label and removed needs triage label
- Matthew Pickering changed milestone to %9.10.2
changed milestone to %9.10.2
- Matthew Pickering assigned to @AndreasK
assigned to @AndreasK
- Maintainer
I will put up a patch removing the guard for now.
- Author Developer
Would love to be pointed to that patch so I can patch my
ghc-9.10
to test it out on our code base. Collapse replies - Developer
Try !12983 (closed), Erik.
- Simon Peyton Jones mentioned in merge request !12983 (closed)
mentioned in merge request !12983 (closed)
- Simon Peyton Jones mentioned in commit 010445e1
mentioned in commit 010445e1
- Author Developer
After appling the suggested patch, I was able to remove the
{-# OPTIONS_GHC -fno-do-clever-arg-eta-expansion #-}
I had added as a workaround. Everything I had compiled with the olderghc-9.10.1
compiled without issue with the patched version.Edited by Erik de Castro Lopo - Simon Peyton Jones mentioned in commit cd8509f5
mentioned in commit cd8509f5
- Simon Peyton Jones mentioned in commit 5cc08d8d
mentioned in commit 5cc08d8d