diff --git a/ghc/compiler/Jmakefile b/ghc/compiler/Jmakefile index 20af031635666093ed320bec56d72b2102f253ea..d2346c51e784396a69ebafac692def0fcd1a7c4a 100644 --- a/ghc/compiler/Jmakefile +++ b/ghc/compiler/Jmakefile @@ -840,7 +840,7 @@ compile(envs/TCE,lhs,) compile(envs/TVE,lhs,) compile_rec(envs/TyVarEnv,lhs,) -compile(main/CmdLineOpts,lhs,-K2m) +compile(main/CmdLineOpts,lhs,-K2m if_ghc(-fvia-C)) compile_rec(main/Errors,lhs,) compile_rec(main/ErrsTc,lhs,-H20m if_ghc26(-monly-4-regs)) compile_rec(main/ErrsRn,lhs,) diff --git a/ghc/compiler/basicTypes/Unique.hi b/ghc/compiler/basicTypes/Unique.hi index 480725d2e80e851f5e3723620ff8685d20d6a394..06c2e096f59a3035cbb6a90216567438d92765bf 100644 --- a/ghc/compiler/basicTypes/Unique.hi +++ b/ghc/compiler/basicTypes/Unique.hi @@ -18,7 +18,9 @@ absentErrorIdKey :: Unique addrDataConKey :: Unique addrPrimTyConKey :: Unique addrTyConKey :: Unique +appendIdKey :: Unique arrayPrimTyConKey :: Unique +augmentIdKey :: Unique binaryClassKey :: Unique boolTyConKey :: Unique buildDataConKey :: Unique @@ -159,6 +161,7 @@ u2i :: Unique -> Int# uniqSupply_u :: UniqueSupply unpackCString2IdKey :: Unique unpackCStringAppendIdKey :: Unique +unpackCStringFoldrIdKey :: Unique unpackCStringIdKey :: Unique unpkUnifiableTyVarUnique :: Unique -> Int voidPrimIdKey :: Unique diff --git a/ghc/compiler/basicTypes/Unique.lhs b/ghc/compiler/basicTypes/Unique.lhs index d92bab0084777c38be00b8c473811e1e755ed9e2..ac9d7fb891db94c209310bf855a784bd4e2837e5 100644 --- a/ghc/compiler/basicTypes/Unique.lhs +++ b/ghc/compiler/basicTypes/Unique.lhs @@ -1,5 +1,5 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1995 +% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996 % \section[Unique]{The @Unique@ data type and a (monadic) supply thereof} @@ -150,7 +150,13 @@ module Unique ( textClassKey, traceIdKey, trueDataConKey, - unpackCStringIdKey, unpackCString2IdKey, unpackCStringAppendIdKey, + unpackCString2IdKey, + unpackCStringAppendIdKey, + unpackCStringFoldrIdKey, + unpackCStringIdKey, + augmentIdKey, + appendIdKey, +--NO: rangeComplaintIdKey, packCStringIdKey, integerZeroIdKey, integerPlusOneIdKey, integerPlusTwoIdKey, integerMinusOneIdKey, @@ -611,41 +617,42 @@ mkPrimOpIdUnique op = mkUnique '5' IBOX((tagOf_PrimOp op)) Now for other non-@DataCon@ @Ids@: \begin{code} absentErrorIdKey = mkPreludeMiscIdUnique 1 -buildIdKey = mkPreludeMiscIdUnique 2 -errorIdKey = mkPreludeMiscIdUnique 3 -foldlIdKey = mkPreludeMiscIdUnique 4 -foldrIdKey = mkPreludeMiscIdUnique 5 -forkIdKey = mkPreludeMiscIdUnique 6 -int2IntegerIdKey = mkPreludeMiscIdUnique 7 -integerMinusOneIdKey = mkPreludeMiscIdUnique 8 -integerPlusOneIdKey = mkPreludeMiscIdUnique 9 -integerZeroIdKey = mkPreludeMiscIdUnique 10 -integerPlusTwoIdKey = mkPreludeMiscIdUnique 11 -packCStringIdKey = mkPreludeMiscIdUnique 12 -parIdKey = mkPreludeMiscIdUnique 13 -parErrorIdKey = mkPreludeMiscIdUnique 14 -patErrorIdKey = mkPreludeMiscIdUnique 15 ---UNUSED:readParenIdKey = mkPreludeMiscIdUnique 16 -realWorldPrimIdKey = mkPreludeMiscIdUnique 17 -runSTIdKey = mkPreludeMiscIdUnique 18 -seqIdKey = mkPreludeMiscIdUnique 19 ---UNUSED:showParenIdKey = mkPreludeMiscIdUnique 20 ---UNUSED:showSpaceIdKey = mkPreludeMiscIdUnique 21 -traceIdKey = mkPreludeMiscIdUnique 22 -unpackCStringIdKey = mkPreludeMiscIdUnique 23 -unpackCString2IdKey = mkPreludeMiscIdUnique 20 -- NB: NB: NB -unpackCStringAppendIdKey= mkPreludeMiscIdUnique 21 -- NB: NB: NB -voidPrimIdKey = mkPreludeMiscIdUnique 24 +appendIdKey = mkPreludeMiscIdUnique 2 +augmentIdKey = mkPreludeMiscIdUnique 3 +buildIdKey = mkPreludeMiscIdUnique 4 +errorIdKey = mkPreludeMiscIdUnique 5 +foldlIdKey = mkPreludeMiscIdUnique 6 +foldrIdKey = mkPreludeMiscIdUnique 7 +forkIdKey = mkPreludeMiscIdUnique 8 +int2IntegerIdKey = mkPreludeMiscIdUnique 9 +integerMinusOneIdKey = mkPreludeMiscIdUnique 10 +integerPlusOneIdKey = mkPreludeMiscIdUnique 11 +integerPlusTwoIdKey = mkPreludeMiscIdUnique 12 +integerZeroIdKey = mkPreludeMiscIdUnique 13 +packCStringIdKey = mkPreludeMiscIdUnique 14 +parErrorIdKey = mkPreludeMiscIdUnique 15 +parIdKey = mkPreludeMiscIdUnique 16 +patErrorIdKey = mkPreludeMiscIdUnique 25 +--NO:rangeComplaintIdKey = mkPreludeMiscIdUnique 17 +realWorldPrimIdKey = mkPreludeMiscIdUnique 18 +runSTIdKey = mkPreludeMiscIdUnique 19 +seqIdKey = mkPreludeMiscIdUnique 20 +traceIdKey = mkPreludeMiscIdUnique 21 +unpackCString2IdKey = mkPreludeMiscIdUnique 22 +unpackCStringAppendIdKey= mkPreludeMiscIdUnique 23 +unpackCStringFoldrIdKey = mkPreludeMiscIdUnique 24 +unpackCStringIdKey = mkPreludeMiscIdUnique 25 +voidPrimIdKey = mkPreludeMiscIdUnique 26 #ifdef GRAN -parLocalIdKey = mkPreludeMiscIdUnique 25 -parGlobalIdKey = mkPreludeMiscIdUnique 26 -noFollowIdKey = mkPreludeMiscIdUnique 27 -copyableIdKey = mkPreludeMiscIdUnique 28 +parLocalIdKey = mkPreludeMiscIdUnique 27 +parGlobalIdKey = mkPreludeMiscIdUnique 28 +noFollowIdKey = mkPreludeMiscIdUnique 29 +copyableIdKey = mkPreludeMiscIdUnique 30 #endif #ifdef DPH -podSelectorIdKey = mkPreludeMiscIdUnique 29 +podSelectorIdKey = mkPreludeMiscIdUnique 31 #endif {- Data Parallel Haskell -} \end{code} diff --git a/ghc/compiler/coreSyn/CoreFuns.lhs b/ghc/compiler/coreSyn/CoreFuns.lhs index 2f11ea3db04544e055e0a350180966ed0d24f172..9fcd186758e249b2818f673c3e1c7cd3901b14a3 100644 --- a/ghc/compiler/coreSyn/CoreFuns.lhs +++ b/ghc/compiler/coreSyn/CoreFuns.lhs @@ -1,5 +1,5 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1995 +% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996 % \section[CoreUtils]{Utility functions} @@ -56,7 +56,7 @@ import Pretty import AbsPrel ( mkFunTy, trueDataCon, falseDataCon, eRROR_ID, pAT_ERROR_ID, aBSENT_ERROR_ID, - buildId, + buildId, augmentId, boolTyCon, fragilePrimOp, PrimOp(..), typeOfPrimOp, PrimKind @@ -862,7 +862,9 @@ exprSmallEnoughToDup (CoLit lit) = not (isNoRepLit lit) exprSmallEnoughToDup expr -- for now, just: <var> applied to <args> = case (collectArgs expr) of { (fun, args) -> case fun of - CoVar v -> v /= buildId && length args <= 6 -- or 10 or 1 or 4 or anything smallish. + CoVar v -> v /= buildId + && v /= augmentId + && length args <= 6 -- or 10 or 1 or 4 or anything smallish. _ -> False } \end{code} diff --git a/ghc/compiler/main/CmdLineOpts.hi b/ghc/compiler/main/CmdLineOpts.hi index e88aa45c4ae8f43902b9f1658059a51fe92cb613..91c9490256c519918e1b9bd6c57af4222f39940e 100644 --- a/ghc/compiler/main/CmdLineOpts.hi +++ b/ghc/compiler/main/CmdLineOpts.hi @@ -8,7 +8,7 @@ data GlobalSwitch = ProduceC [Char] | ProduceS [Char] | ProduceHi [Char] | AsmTarget [Char] | ForConcurrent | Haskell_1_3 | GlasgowExts | CompilingPrelude | HideBuiltinNames | HideMostBuiltinNames | EnsureSplittableC [Char] | Verbose | PprStyle_User | PprStyle_Debug | PprStyle_All | DoCoreLinting | EmitArityChecks | OmitInterfacePragmas | OmitDerivedRead | OmitReexportedInstances | UnfoldingUseThreshold Int | UnfoldingCreationThreshold Int | UnfoldingOverrideThreshold Int | ReportWhyUnfoldingsDisallowed | UseGetMentionedVars | ShowPragmaNameErrs | NameShadowingNotOK | SigsRequired | SccProfilingOn | AutoSccsOnExportedToplevs | AutoSccsOnAllToplevs | AutoSccsOnIndividualCafs | SccGroup [Char] | DoTickyProfiling | DoSemiTagging | FoldrBuildOn | FoldrBuildTrace | SpecialiseImports | ShowImportSpecs | OmitDefaultInstanceMethods | SpecialiseOverloaded | SpecialiseUnboxed | SpecialiseAll | SpecialiseTrace | OmitBlackHoling | StgDoLetNoEscapes | IgnoreStrictnessPragmas | IrrefutableTuples | IrrefutableEverything | AllStrict | NumbersStrict | AllDemanded | ReturnInRegsThreshold Int | VectoredReturnThreshold Int | D_dump_rif2hs | D_dump_rn4 | D_dump_tc | D_dump_deriv | D_dump_ds | D_dump_occur_anal | D_dump_simpl | D_dump_spec | D_dump_stranal | D_dump_deforest | D_dump_stg | D_dump_absC | D_dump_flatC | D_dump_realC | D_dump_asm | D_show_passes | D_verbose_core2core | D_verbose_stg2stg | D_simplifier_stats | D_source_stats type MainIO a = _State _RealWorld -> (a, _State _RealWorld) data Labda a -data SimplifierSwitch = SimplOkToDupCode | SimplFloatLetsExposingWHNF | SimplOkToFloatPrimOps | SimplAlwaysFloatLetsFromLets | SimplDoCaseElim | SimplReuseCon | SimplCaseOfCase | SimplLetToCase | SimplMayDeleteConjurableIds | SimplPedanticBottoms | SimplDoArityExpand | SimplDoFoldrBuild | SimplDoNewOccurAnal | SimplDoInlineFoldrBuild | IgnoreINLINEPragma | SimplDoLambdaEtaExpansion | SimplDoEtaReduction | EssentialUnfoldingsOnly | ShowSimplifierProgress | MaxSimplifierIterations Int | SimplUnfoldingUseThreshold Int | SimplUnfoldingCreationThreshold Int | KeepSpecPragmaIds | KeepUnusedBindings | SimplNoLetFromCase | SimplNoLetFromApp | SimplNoLetFromStrictLet +data SimplifierSwitch = SimplOkToDupCode | SimplFloatLetsExposingWHNF | SimplOkToFloatPrimOps | SimplAlwaysFloatLetsFromLets | SimplDoCaseElim | SimplReuseCon | SimplCaseOfCase | SimplLetToCase | SimplMayDeleteConjurableIds | SimplPedanticBottoms | SimplDoArityExpand | SimplDoFoldrBuild | SimplDoNewOccurAnal | SimplDoInlineFoldrBuild | IgnoreINLINEPragma | SimplDoLambdaEtaExpansion | SimplDoEtaReduction | EssentialUnfoldingsOnly | ShowSimplifierProgress | MaxSimplifierIterations Int | SimplUnfoldingUseThreshold Int | SimplUnfoldingCreationThreshold Int | KeepSpecPragmaIds | KeepUnusedBindings | SimplNoLetFromCase | SimplNoLetFromApp | SimplNoLetFromStrictLet | SimplDontFoldBackAppend data StgToDo = StgDoStaticArgs | StgDoUpdateAnalysis | StgDoLambdaLift | StgDoMassageForProfiling | D_stg_stats data SwitchResult = SwBool Bool | SwString [Char] | SwInt Int classifyOpts :: [[Char]] -> _State _RealWorld -> ((GlobalSwitch -> SwitchResult, [CoreToDo], [StgToDo]), _State _RealWorld) diff --git a/ghc/compiler/main/CmdLineOpts.lhs b/ghc/compiler/main/CmdLineOpts.lhs index 210251ca7fbd9ea1b248326029a24b1ff0cea58e..4588a889f277c0e6f8e106e68ea4142869e52326 100644 --- a/ghc/compiler/main/CmdLineOpts.lhs +++ b/ghc/compiler/main/CmdLineOpts.lhs @@ -276,6 +276,17 @@ data SimplifierSwitch | SimplNoLetFromCase -- used when turning off floating entirely | SimplNoLetFromApp -- (for experimentation only) WDP 95/10 | SimplNoLetFromStrictLet + + | SimplDontFoldBackAppend + -- we fold `foldr (:)' back into flip (++), + -- but we *don't* want to do it when compiling + -- List.hs, otherwise + -- xs ++ ys = foldr (:) ys xs + -- {- via our loopback -} + -- xs ++ ys = xs ++ ys + -- Oops! + -- So only use this flag inside List.hs + -- (Sigh, what a HACK, Andy. WDP 96/01) {- | Extra__SimplFlag1 | Extra__SimplFlag2 @@ -609,6 +620,7 @@ classifyOpts opts "-fdo-eta-reduction" -> GLOBAL_SIMPL_SW(SimplDoEtaReduction) "-fdo-lambda-eta-expansion" -> GLOBAL_SIMPL_SW(SimplDoLambdaEtaExpansion) "-fdo-foldr-build" -> GLOBAL_SIMPL_SW(SimplDoFoldrBuild) + "-fdo-not-fold-back-append" -> GLOBAL_SIMPL_SW(SimplDontFoldBackAppend) "-fdo-new-occur-anal" -> GLOBAL_SIMPL_SW(SimplDoNewOccurAnal) "-fdo-arity-expand" -> GLOBAL_SIMPL_SW(SimplDoArityExpand) "-fdo-inline-foldr-build" -> GLOBAL_SIMPL_SW(SimplDoInlineFoldrBuild) @@ -790,6 +802,7 @@ tagOf_SimplSwitch KeepUnusedBindings = ILIT(25) tagOf_SimplSwitch SimplNoLetFromCase = ILIT(26) tagOf_SimplSwitch SimplNoLetFromApp = ILIT(27) tagOf_SimplSwitch SimplNoLetFromStrictLet = ILIT(28) +tagOf_SimplSwitch SimplDontFoldBackAppend = ILIT(29) -- If you add anything here, be sure to change lAST_SIMPL_SWITCH_TAG, too! {- @@ -805,7 +818,7 @@ tagOf_SimplSwitch Extra__SimplFlag8 = ILIT(32) tagOf_SimplSwitch _ = case (panic "tagOf_SimplSwitch") of -- BUG avoidance s -> tagOf_SimplSwitch s -lAST_SIMPL_SWITCH_TAG = IBOX(tagOf_SimplSwitch SimplNoLetFromStrictLet) +lAST_SIMPL_SWITCH_TAG = IBOX(tagOf_SimplSwitch SimplDontFoldBackAppend) \end{code} %************************************************************************ diff --git a/ghc/compiler/prelude/AbsPrel.hi b/ghc/compiler/prelude/AbsPrel.hi index c9165ea4f5c1de292ff082ba05b9c0bb0a974434..0eba17f161c86d1b887fcd0acbb20b7239e72d65 100644 --- a/ghc/compiler/prelude/AbsPrel.hi +++ b/ghc/compiler/prelude/AbsPrel.hi @@ -11,7 +11,7 @@ import NameTypes(FullName, ShortName) import Outputable(NamedThing, Outputable) import PlainCore(PlainCoreExpr(..)) import PrelFuns(gLASGOW_MISC, gLASGOW_ST, pRELUDE, pRELUDE_BUILTIN, pRELUDE_CORE, pRELUDE_IO, pRELUDE_LIST, pRELUDE_PRIMIO, pRELUDE_PS, pRELUDE_RATIO, pRELUDE_TEXT) -import PrelVals(aBSENT_ERROR_ID, buildId, eRROR_ID, foldlId, foldrId, integerMinusOneId, integerPlusOneId, integerPlusTwoId, integerZeroId, mkBuild, mkFoldl, mkFoldr, pAT_ERROR_ID, packStringForCId, realWorldPrimId, unpackCString2Id, unpackCStringAppendId, unpackCStringId, voidPrimId) +import PrelVals(aBSENT_ERROR_ID, appendId, augmentId, buildId, eRROR_ID, foldlId, foldrId, integerMinusOneId, integerPlusOneId, integerPlusTwoId, integerZeroId, mkBuild, mkFoldl, mkFoldr, pAT_ERROR_ID, packStringForCId, realWorldPrimId, unpackCString2Id, unpackCStringAppendId, unpackCStringFoldrId, unpackCStringId, voidPrimId) import PreludePS(_PackedString) import Pretty(PprStyle, PrettyRep) import PrimKind(PrimKind) @@ -51,6 +51,8 @@ pRELUDE_PS :: _PackedString pRELUDE_RATIO :: _PackedString pRELUDE_TEXT :: _PackedString aBSENT_ERROR_ID :: Id +appendId :: Id +augmentId :: Id buildId :: Id eRROR_ID :: Id foldlId :: Id @@ -112,6 +114,7 @@ packStringForCId :: Id realWorldPrimId :: Id unpackCString2Id :: Id unpackCStringAppendId :: Id +unpackCStringFoldrId :: Id unpackCStringId :: Id voidPrimId :: Id pprPrimOp :: PprStyle -> PrimOp -> Int -> Bool -> PrettyRep diff --git a/ghc/compiler/prelude/AbsPrel.lhs b/ghc/compiler/prelude/AbsPrel.lhs index 22cc946c719ad507f1f1bc2bfe7fd5173487d743..3f581960950b62699616b1389aed858b105f9a1a 100644 --- a/ghc/compiler/prelude/AbsPrel.lhs +++ b/ghc/compiler/prelude/AbsPrel.lhs @@ -29,7 +29,9 @@ module AbsPrel ( -- *odd* values that need to be reached out and grabbed: eRROR_ID, pAT_ERROR_ID, aBSENT_ERROR_ID, - unpackCStringId, unpackCString2Id, packStringForCId, unpackCStringAppendId, + packStringForCId, + unpackCStringId, unpackCString2Id, + unpackCStringAppendId, unpackCStringFoldrId, integerZeroId, integerPlusOneId, integerPlusTwoId, integerMinusOneId, @@ -99,7 +101,8 @@ module AbsPrel ( -- packedStringTyCon, packedStringTy, psDataCon, cpsDataCon, -- for compilation of List Comprehensions and foldr - foldlId, foldrId, mkFoldl, mkFoldr, mkBuild, buildId, + foldlId, foldrId, mkFoldl, mkFoldr, + mkBuild, buildId, augmentId, appendId, #ifdef DPH mkProcessorTy, @@ -257,10 +260,15 @@ totally_wired_in_Ids (SLIT("parError#"), WiredInVal pAR_ERROR_ID), -- ditto (SLIT("_trace"), WiredInVal tRACE_ID), - -- now the build / foldr Id, which needs to be built in + -- now the foldr/build Ids, which need to be built in + -- because they have magic unfoldings (SLIT("_build"), WiredInVal buildId), + (SLIT("_augment"), WiredInVal augmentId), (SLIT("foldl"), WiredInVal foldlId), (SLIT("foldr"), WiredInVal foldrId), + (SLIT("unpackAppendPS#"), WiredInVal unpackCStringAppendId), + (SLIT("unpackFoldrPS#"), WiredInVal unpackCStringFoldrId), + (SLIT("_runST"), WiredInVal runSTId), (SLIT("_seq_"), WiredInVal seqId), -- yes, used in sequential-land, too -- WDP 95/11 diff --git a/ghc/compiler/prelude/PrelVals.hi b/ghc/compiler/prelude/PrelVals.hi index 660d781ebe7c35a8784c02fae1bc03de82fafff4..d5981a4c10dab445a9ed9be1bdec4142cd6615f6 100644 --- a/ghc/compiler/prelude/PrelVals.hi +++ b/ghc/compiler/prelude/PrelVals.hi @@ -7,6 +7,8 @@ import TyVar(TyVar) import UniType(UniType) import Unique(Unique) aBSENT_ERROR_ID :: Id +appendId :: Id +augmentId :: Id buildId :: Id eRROR_ID :: Id errorTy :: UniType @@ -32,6 +34,7 @@ seqId :: Id tRACE_ID :: Id unpackCString2Id :: Id unpackCStringAppendId :: Id +unpackCStringFoldrId :: Id unpackCStringId :: Id voidPrimId :: Id diff --git a/ghc/compiler/prelude/PrelVals.lhs b/ghc/compiler/prelude/PrelVals.lhs index ba6118b213fbcfff9d88b00d78def6d41637a637..e8c7ce41b12d578f43b6c68484d7d4713decc13c 100644 --- a/ghc/compiler/prelude/PrelVals.lhs +++ b/ghc/compiler/prelude/PrelVals.lhs @@ -1,5 +1,5 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1995 +% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996 % \section[PrelVals]{Prelude values the compiler ``knows about''} @@ -114,28 +114,44 @@ int2IntegerId -------------------------------------------------------------------- +packStringForCId + = pcMiscPrelId packCStringIdKey{-ToDo:rename-} pRELUDE_PS SLIT("_packStringForC") + (UniFun stringTy byteArrayPrimTy) noIdInfo + +-------------------------------------------------------------------- + unpackCStringId - = pcMiscPrelId unpackCStringIdKey pRELUDE_PS SLIT("unpackPS#") + = pcMiscPrelId unpackCStringIdKey pRELUDE_BUILTIN SLIT("unpackPS#") (addrPrimTy{-a char *-} `UniFun` stringTy) noIdInfo +-- Andy says: +-- (UniFun addrPrimTy{-a char *-} stringTy) (noIdInfo `addInfo` mkArityInfo 1) +-- but I don't like wired-in IdInfos (WDP) unpackCString2Id -- for cases when a string has a NUL in it - = pcMiscPrelId unpackCString2IdKey pRELUDE_PS SLIT("unpackPS2#") + = pcMiscPrelId unpackCString2IdKey pRELUDE_BUILTIN SLIT("unpackPS2#") (addrPrimTy{-a char *-} `UniFun` (intPrimTy -- length `UniFun` stringTy)) noIdInfo + -------------------------------------------------------------------- unpackCStringAppendId - = pcMiscPrelId unpackCStringAppendIdKey pRELUDE_BUILTIN SLIT("unpackCStringAppend#") + = pcMiscPrelId unpackCStringAppendIdKey pRELUDE_BUILTIN SLIT("unpackAppendPS#") (addrPrimTy{-a "char *" pointer-} `UniFun` (stringTy - `UniFun` stringTy)) noIdInfo + `UniFun` stringTy)) ((noIdInfo + `addInfo_UF` mkMagicUnfolding SLIT("unpackAppendPS#")) + `addInfo` mkArityInfo 2) --------------------------------------------------------------------- - -packStringForCId - = pcMiscPrelId packCStringIdKey{-ToDo:rename-} pRELUDE_PS SLIT("_packStringForC") - (UniFun stringTy byteArrayPrimTy) noIdInfo +unpackCStringFoldrId + = pcMiscPrelId unpackCStringFoldrIdKey pRELUDE_BUILTIN SLIT("unpackFoldrPS#") + (mkSigmaTy [alpha_tv] [] + (addrPrimTy{-a "char *" pointer-} + `UniFun` ((charTy `UniFun` (alpha `UniFun` alpha)) + `UniFun` (alpha + `UniFun` alpha)))) ((noIdInfo + `addInfo_UF` mkMagicUnfolding SLIT("unpackFoldrPS#")) + `addInfo` mkArityInfo 3) \end{code} OK, this is Will's idea: we should have magic values for Integers 0, @@ -502,6 +518,7 @@ runSTId = noIdInfo `addInfo` mkArityInfo 1 `addInfo` mkStrictnessInfo [WwStrict] Nothing + `addInfo` mkArgUsageInfo [ArgUsage 1] -- ABSOLUTELY NO UNFOLDING, e.g.: (mkUnfolding EssentialUnfolding run_ST_template) -- see example below {- OUT: @@ -568,6 +585,23 @@ realWorldPrimId %* * %************************************************************************ +\begin{code} +{- NO: +rangeComplaint_Ix_IntId + = pcMiscPrelId rangeComplaintIdKey pRELUDE_BUILTIN SLIT("_rangeComplaint_Ix_Int") my_ty id_info + where + my_ty + = mkSigmaTy [alpha_tv] [] ( + intPrimTy `UniFun` ( + intPrimTy `UniFun` ( + intPrimTy `UniFun` alpha))) + id_info + = noIdInfo + `addInfo` mkArityInfo 3 + `addInfo` mkBottomStrictnessInfo +-} +\end{code} + \begin{code} buildId = pcMiscPrelId buildIdKey pRELUDE_CORE SLIT("_build") buildTy @@ -614,6 +648,26 @@ mkBuild ty tv c n g expr (CoApp (mkCoTyApp (CoVar buildId) ty) (CoVarAtom g)) \end{code} +\begin{code} +augmentId + = pcMiscPrelId buildIdKey pRELUDE_CORE SLIT("_augment") augmentTy + (((noIdInfo + `addInfo_UF` mkMagicUnfolding SLIT("augment")) + `addInfo` mkStrictnessInfo [WwStrict,WwLazy False] Nothing) + `addInfo` mkArgUsageInfo [ArgUsage 2,UnknownArgUsage]) + -- cheating, but since _build never actually exists ... + where + -- The type of this strange object is: + -- \/ a . (\/ b . (a -> b -> b) -> b -> b) -> [a] -> [a] + + augmentTy = mkSigmaTy [alpha_tv] [] (buildUniTy `UniFun` + (mkListTy alpha `UniFun` mkListTy alpha)) + where + buildUniTy = mkSigmaTy [beta_tv] [] + ((alpha `UniFun` (beta `UniFun` beta)) + `UniFun` (beta `UniFun` beta)) +\end{code} + mkFoldr ty_a ty_b [x,y...] => foldr ty_a ty_b x y .. \begin{code} @@ -659,5 +713,30 @@ mkFoldl a b f z xs = foldl CoApp (mkCoTyApps (CoVar foldlId) [a, b]) [CoVarAtom f,CoVarAtom z,CoVarAtom xs] +-- A bit of magic goes no here. We translate appendId into ++, +-- you have to be carefull when you actually compile append: +-- xs ++ ys = augment (\ c n -> foldr c n xs) ys +-- {- unfold augment -} +-- = foldr (:) ys xs +-- {- fold foldr to append -} +-- = ys `appendId` xs +-- = ys ++ xs -- ugg! +-- *BUT* you want (++) and not _append in your interfaces. +-- +-- So you have to turn *off* unfolding of foldr inside FoldrBuild.hs inside +-- the prelude. +-- + +appendId + = pcMiscPrelId appendIdKey pRELUDE_LIST SLIT("++") appendTy idInfo + where + appendTy = + (mkSigmaTy [alpha_tv] [] + ((mkListTy alpha) `UniFun` ((mkListTy alpha) `UniFun` (mkListTy alpha)))) + idInfo = (((noIdInfo + `addInfo` mkStrictnessInfo [WwStrict,WwLazy False] Nothing) + `addInfo` mkArityInfo 2) + `addInfo` mkUpdateInfo [1,2]) + pRELUDE_FB = SLIT("PreludeFoldrBuild") \end{code} diff --git a/ghc/compiler/simplCore/MagicUFs.lhs b/ghc/compiler/simplCore/MagicUFs.lhs index e1e75d0a7616218b5401ecec29876f5d5a676468..0f29a90a0fa32bf85a0a9b3cd246080ee09f72ec 100644 --- a/ghc/compiler/simplCore/MagicUFs.lhs +++ b/ghc/compiler/simplCore/MagicUFs.lhs @@ -20,9 +20,10 @@ module MagicUFs ( IMPORT_Trace -- ToDo: not sure why this is being used -import AbsPrel ( foldlId, foldrId, buildId, +import AbsPrel ( foldlId, foldrId, buildId, augmentId, nilDataCon, consDataCon, mkListTy, mkFunTy, - unpackCStringAppendId + unpackCStringAppendId, unpackCStringFoldrId, + appendId ) import AbsUniType ( splitTypeWithDictsAsArgs, TyVarTemplate ) import BasicLit ( BasicLit(..) ) @@ -85,9 +86,12 @@ applyMagicUnfoldingFun (MUF fun) env args = fun env args magic_UFs_table :: [(FAST_STRING, MagicUnfoldingFun)] magic_UFs_table - = [(SLIT("build"), MUF build_fun), - (SLIT("foldl"), MUF foldl_fun), - (SLIT("foldr"), MUF foldr_fun) ] + = [(SLIT("augment"), MUF augment_fun), + (SLIT("build"), MUF build_fun), + (SLIT("foldl"), MUF foldl_fun), + (SLIT("foldr"), MUF foldr_fun), + (SLIT("unpackFoldrPS#"), MUF unpack_foldr_fun), + (SLIT("unpackAppendPS#"), MUF unpack_append_fun)] \end{code} %************************************************************************ @@ -119,26 +123,48 @@ build_fun env [TypeArg ty,ValArg (CoVarAtom e)] build_fun env _ = ASSERT (not (switchIsSet env SimplDoInlineFoldrBuild)) returnSmpl Nothing +\end{code} --- Now foldr, the way we consume lists. +\begin{code} +augment_fun :: SimplEnv + -> [PlainCoreArg] + -> SmplM (Maybe PlainCoreExpr) +augment_fun env [TypeArg ty,ValArg (CoVarAtom e),ValArg nil] + | switchIsSet env SimplDoInlineFoldrBuild = + let + tyL = mkListTy ty + ourCons = mkCoTyApp (CoVar consDataCon) ty + in + newId (ty `mkFunTy` (tyL `mkFunTy` tyL)) `thenSmpl` \ c -> + returnSmpl (Just (CoLet (CoNonRec c ourCons) + (CoApp (CoApp (mkCoTyApp (CoVar e) tyL) (CoVarAtom c)) nil))) +-- ToDo: add `build' without an argument instance. +-- This is strange, because of g's type. +augment_fun env _ = + ASSERT (not (switchIsSet env SimplDoInlineFoldrBuild)) + returnSmpl Nothing +\end{code} + +Now foldr, the way we consume lists. + +\begin{code} foldr_fun :: SimplEnv -> [PlainCoreArg] -> SmplM (Maybe PlainCoreExpr) -{- -foldr_fun env _ - | trace "HEHJDHF!" False = error "NEVER" --} + foldr_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:rest_args) - | isConsFun env arg_k && isNilForm env arg_z + | do_fb_red && isConsFun env arg_k && isNilForm env arg_z = -- foldr (:) [] ==> id -- this transformation is *always* benificial -- cf. foldr (:) [] (build g) == g (:) [] -- with foldr (:) [] (build g) == build g -- after unfolding build, they are the same thing. - tick FoldrConsNil `thenSmpl_` + tick Foldr_Cons_Nil `thenSmpl_` newId (mkListTy ty1) `thenSmpl` \ x -> returnSmpl({-trace "foldr (:) []"-} (Just (applyToArgs (CoLam [x] (CoVar x)) rest_args))) + where + do_fb_red = switchIsSet env SimplDoFoldrBuild foldr_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:ValArg arg_list:rest_args) | do_fb_red && isNilForm env arg_list @@ -153,20 +179,18 @@ foldr_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:ValArg arg_list tick FoldrBuild `thenSmpl_` returnSmpl (Just (applyToArgs (CoVar g) (TypeArg ty2:ValArg arg_k:ValArg arg_z:rest_args))) - | do_fb_red && arg_list_isAppendForm - = -- foldr k z (foldr (:) ys xs) <args> ==> foldr k (foldr k z ys) xs <args> - -- this unfolds foldr one into foldr - tick FoldrFoldr `thenSmpl_` - newId ty2 `thenSmpl` \ other_foldr -> - let - inner_foldr = applyToArgs (CoVar foldrId) - [TypeArg ty1,TypeArg ty2, - ValArg arg_k,ValArg arg_z,ValArg ys] - outer_foldr = applyToArgs (CoVar foldrId) - ([TypeArg ty1,TypeArg ty2, - ValArg arg_k,ValArg (CoVarAtom other_foldr),ValArg xs] - ++ rest_args) - in returnSmpl (Just (CoLet (CoNonRec other_foldr inner_foldr) outer_foldr)) + | do_fb_red && arg_list_isAugmentForm + = -- foldr k z (augment g h) ==> let v = foldr k z h in g k v + -- this next line *is* the foldr/augment rule proper. + tick FoldrAugment `thenSmpl_` + newId ty2 `thenSmpl` \ v -> + returnSmpl (Just + (CoLet (CoNonRec v (applyToArgs (CoVar foldrId) + [TypeArg ty1,TypeArg ty2, + ValArg arg_k, + ValArg arg_z, + ValArg h])) + (applyToArgs (CoVar g') (TypeArg ty2:ValArg arg_k:ValArg (CoVarAtom v):rest_args)))) | do_fb_red && arg_list_isListForm = -- foldr k z (a:b:c:rest) = @@ -212,26 +236,46 @@ foldr_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:ValArg arg_list returnSmpl (Just (applyToArgs (CoLam [f_id] core_list) (ValArg arg_k:rest_args))) + + -- + + | do_fb_red && arg_list_isStringForm -- ok, its a string! + -- foldr f z "foo" => unpackFoldrPS# f z "foo"# + = tick Str_FoldrStr `thenSmpl_` + returnSmpl (Just (applyToArgs (CoVar unpackCStringFoldrId) + (TypeArg ty2: + ValArg (CoLitAtom (MachStr str_val)): + ValArg arg_k: + ValArg arg_z: + rest_args))) where do_fb_red = switchIsSet env SimplDoFoldrBuild + arg_list_isStringForm = maybeToBool stringForm + stringForm = getStringForm env arg_list + (Just str_val) = stringForm + arg_list_isBuildForm = maybeToBool buildForm buildForm = getBuildForm env arg_list (Just g) = buildForm + arg_list_isAugmentForm = maybeToBool augmentForm + augmentForm = getAugmentForm env arg_list + (Just (g',h)) = augmentForm + arg_list_isListForm = maybeToBool listForm listForm = getListForm env arg_list (Just (the_list,the_tl)) = listForm - +{- arg_list_isAppendForm = maybeToBool appendForm appendForm = getAppendForm env arg_list (Just (xs,ys)) = appendForm +-} foldr_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:rest_args) -{- OLD: - | doing_inlining && isConsFun env arg_k + | doing_inlining && isConsFun env arg_k && not dont_fold_back_append = -- foldr (:) z xs = xs ++ z - tick FoldrCons `thenSmpl_` + tick Foldr_Cons `thenSmpl_` newIds [ty2,mkListTy ty1] `thenSmpl` \ [z,x] -> returnSmpl (Just (applyToArgs (CoLam [z,x] (applyToArgs @@ -240,7 +284,6 @@ foldr_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:rest_args) ValArg (CoVarAtom x), ValArg (CoVarAtom z)])) rest_args)) --} | doing_inlining && (isInterestingArg env arg_k || isConsFun env arg_k) = -- foldr k args = @@ -252,7 +295,7 @@ foldr_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:rest_args) -- in -- h xs) k args -- - tick FoldrInline `thenSmpl_` +-- tick FoldrInline `thenSmpl_` newIds [ ty1, -- a :: t1 mkListTy ty1, -- b :: [t1] @@ -284,6 +327,7 @@ foldr_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:rest_args) (ValArg arg_k:rest_args))) where doing_inlining = switchIsSet env SimplDoInlineFoldrBuild + dont_fold_back_append = switchIsSet env SimplDontFoldBackAppend foldr_fun _ _ = returnSmpl Nothing isConsFun :: SimplEnv -> PlainCoreAtom -> Bool @@ -310,12 +354,34 @@ isNilForm env _ = False getBuildForm :: SimplEnv -> PlainCoreAtom -> Maybe Id getBuildForm env (CoVarAtom v) = case lookupUnfolding env v of - GeneralForm False _ _ _ -> Nothing -- not allowed to inline :-( + GeneralForm False _ _ _ -> Nothing + -- not allowed to inline :-( GeneralForm _ _ (CoApp (CoTyApp (CoVar bld) _) (CoVarAtom g)) _ | bld == buildId -> Just g + GeneralForm _ _ (CoApp (CoApp (CoTyApp (CoVar bld) _) + (CoVarAtom g)) h) _ + | bld == augmentId && isNilForm env h -> Just g _ -> Nothing getBuildForm env _ = Nothing + + +getAugmentForm :: SimplEnv -> PlainCoreAtom -> Maybe (Id,PlainCoreAtom) +getAugmentForm env (CoVarAtom v) = + case lookupUnfolding env v of + GeneralForm False _ _ _ -> Nothing + -- not allowed to inline :-( + GeneralForm _ _ (CoApp (CoApp (CoTyApp (CoVar bld) _) + (CoVarAtom g)) h) _ + | bld == augmentId -> Just (g,h) + _ -> Nothing +getAugmentForm env _ = Nothing + +getStringForm :: SimplEnv -> PlainCoreAtom -> Maybe FAST_STRING +getStringForm env (CoLitAtom (NoRepStr str)) = Just str +getStringForm env _ = Nothing + +{- getAppendForm :: SimplEnv -> PlainCoreAtom -> Maybe (CoreAtom Id,CoreAtom Id) getAppendForm env (CoVarAtom v) = case lookupUnfolding env v of @@ -324,6 +390,7 @@ getAppendForm env (CoVarAtom v) = | fld == foldrId && isConsFun env con -> Just (xs,ys) _ -> Nothing getAppendForm env _ = Nothing +-} -- -- this gets a list of the form a : b : c : d and returns ([a,b,c],d) @@ -353,10 +420,10 @@ isInterestingArg env (CoVarAtom v) = isInterestingArg env _ = False foldl_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:ValArg arg_list:rest_args) - | do_fb_red && isNilForm env arg_list + | do_fb_red && isNilForm env arg_list = -- foldl f z [] = z -- again another short cut, helps with unroling of constant lists - tick Foldr_Nil `thenSmpl_` + tick Foldl_Nil `thenSmpl_` returnSmpl (Just (atomToExpr arg_z)) | do_fb_red && arg_list_isBuildForm @@ -365,7 +432,7 @@ foldl_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:ValArg arg_list -- n {- INLINE -} = \ a -> a -- in g t1 c n z -- this next line *is* the foldr/build rule proper. - tick FoldrBuild `thenSmpl_` + tick FoldlBuild `thenSmpl_` -- c :: t2 -> (t1 -> t1) -> t1 -> t1 -- n :: t1 -> t1 newIds [ @@ -397,21 +464,54 @@ foldl_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:ValArg arg_list (TypeArg (ty1 `mkFunTy` ty1):ValArg (CoVarAtom c):ValArg (CoVarAtom n) :ValArg arg_z:rest_args))))) + | do_fb_red && arg_list_isAugmentForm + = -- foldl t1 t2 k z (augment t3 g h) ==> + -- let c {- INLINE -} = \ b g' a -> g' (f a b) + -- n {- INLINE -} = \ a -> a + -- r {- INLINE -} = foldr t2 (t1 -> t1) c n h + -- in g t1 c r z + -- this next line *is* the foldr/build rule proper. + tick FoldlAugment `thenSmpl_` + -- c :: t2 -> (t1 -> t1) -> t1 -> t1 + -- n :: t1 -> t1 + newIds [ + {- pre_c -} ty2 `mkFunTy` ((ty1 `mkFunTy` ty1) `mkFunTy` (ty1 `mkFunTy` ty1)), + {- pre_n -} ty1 `mkFunTy` ty1, + {- pre_r -} ty1 `mkFunTy` ty1, + {- b -} ty2, + {- g_ -} ty1 `mkFunTy` ty1, + {- a -} ty1, + {- a' -} ty1, + {- t -} ty1 + ] `thenSmpl` \ [pre_c, + pre_n, + pre_r, + b, + g_, + a, + a', + t] -> - | do_fb_red && arg_list_isAppendForm - = -- foldl k z (foldr (:) ys xs) <args> ==> foldl k (foldl k z xs) ys <args> - -- be caseful with for order of xs / ys - tick FoldrFoldr `thenSmpl_` - newId ty1 `thenSmpl` \ other_foldl -> - let - inner_foldl = applyToArgs (CoVar foldlId) - [TypeArg ty1,TypeArg ty2, - ValArg arg_k,ValArg arg_z,ValArg xs] - outer_foldl = applyToArgs (CoVar foldlId) - ([TypeArg ty1,TypeArg ty2, - ValArg arg_k,ValArg (CoVarAtom other_foldl),ValArg ys] - ++ rest_args) - in returnSmpl (Just (CoLet (CoNonRec other_foldl inner_foldl) outer_foldl)) + let + c = addIdUnfolding pre_c (iWantToBeINLINEd UnfoldAlways) + c_rhs = CoLam [b,g_,a] + (CoLet (CoNonRec t (CoApp (CoApp (atomToExpr arg_k) (CoVarAtom a)) (CoVarAtom b))) + (CoApp (CoVar g_) (CoVarAtom t))) + n = addIdUnfolding pre_n (iWantToBeINLINEd UnfoldAlways) + n_rhs = CoLam [a'] (CoVar a') + r = addIdUnfolding pre_r (iWantToBeINLINEd UnfoldAlways) + r_rhs = applyToArgs (CoVar foldrId) + [TypeArg ty2,TypeArg (ty1 `mkFunTy` ty1), + ValArg (CoVarAtom c), + ValArg (CoVarAtom n), + ValArg h] + in + returnSmpl (Just (CoLet (CoNonRec c c_rhs) + (CoLet (CoNonRec n n_rhs) + (CoLet (CoNonRec r r_rhs) + (applyToArgs (CoVar g') + (TypeArg (ty1 `mkFunTy` ty1):ValArg (CoVarAtom c):ValArg (CoVarAtom r) + :ValArg arg_z:rest_args)))))) | do_fb_red && arg_list_isListForm = -- foldl k z (a:b:c:rest) = @@ -430,7 +530,7 @@ foldl_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:ValArg arg_list -- ele_3 = f ele_2 c -- in foldl f ele_3 rest -- - tick Foldr_List `thenSmpl_` + tick Foldl_List `thenSmpl_` newIds ( ty1 `mkFunTy` (ty2 `mkFunTy` ty1) : take (length the_list) (repeat ty1) @@ -460,6 +560,10 @@ foldl_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:ValArg arg_list where do_fb_red = switchIsSet env SimplDoFoldrBuild + arg_list_isAugmentForm = maybeToBool augmentForm + augmentForm = getAugmentForm env arg_list + (Just (g',h)) = augmentForm + arg_list_isBuildForm = maybeToBool buildForm buildForm = getBuildForm env arg_list (Just g) = buildForm @@ -468,9 +572,11 @@ foldl_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:ValArg arg_z:ValArg arg_list listForm = getListForm env arg_list (Just (the_list,the_tl)) = listForm +{- arg_list_isAppendForm = maybeToBool appendForm appendForm = getAppendForm env arg_list (Just (xs,ys)) = appendForm +-} foldl_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:rest_args) | doing_inlining && (isInterestingArg env arg_k @@ -484,7 +590,7 @@ foldl_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:rest_args) -- in -- h xs z) k args -- - tick FoldrInline `thenSmpl_` +-- tick FoldrInline `thenSmpl_` newIds [ ty2, -- a :: t1 mkListTy ty2, -- b :: [t1] @@ -523,3 +629,23 @@ foldl_fun env (TypeArg ty1:TypeArg ty2:ValArg arg_k:rest_args) foldl_fun env _ = returnSmpl Nothing \end{code} + +\begin{code} +-- +-- Foldr unpackFoldr "str"# (:) stuff ==> unpackAppend "str"# +-- +unpack_foldr_fun env [TypeArg ty,ValArg str,ValArg arg_k,ValArg arg_z] + | switchIsSet env SimplDoFoldrBuild && isConsFun env arg_k + = tick Str_UnpackCons `thenSmpl_` + returnSmpl (Just (applyToArgs (CoVar unpackCStringAppendId) + [ValArg str, + ValArg arg_z])) +unpack_foldr_fun env _ = returnSmpl Nothing + +unpack_append_fun env + [ValArg (CoLitAtom (MachStr str_val)),ValArg arg_z] + | switchIsSet env SimplDoFoldrBuild && isNilForm env arg_z + = tick Str_UnpackNil `thenSmpl_` + returnSmpl (Just (CoLit (NoRepStr str_val))) +unpack_append_fun env _ = returnSmpl Nothing +\end{code} diff --git a/ghc/compiler/simplCore/NewOccurAnal.lhs b/ghc/compiler/simplCore/NewOccurAnal.lhs index a696a5b463866c9f83e41b1a06523123667ec69f..443b739749a2dd20a0ebb5ca151f57e761d072da 100644 --- a/ghc/compiler/simplCore/NewOccurAnal.lhs +++ b/ghc/compiler/simplCore/NewOccurAnal.lhs @@ -684,10 +684,11 @@ occAnalApp env stk args fun %* * %************************************************************************ - Abstract, but simple rep. for stacks. \begin{code} -data Context = Context Int Bool -- if b then n > 0 +data Context = Context Int Bool + -- if b then n > 0 + -- ie. you *can't* have a linear content with *no* arguments. lamOnContext :: Context -> Int -> Context lamOnContext (Context n b) i = mkContext (max 0 (n - i)) b diff --git a/ghc/compiler/simplCore/SimplEnv.lhs b/ghc/compiler/simplCore/SimplEnv.lhs index a433475cc91d2ae24569eff0e013d174d4e077b9..e55b6ea5a402de13763ef83b2de78ad16ab6376b 100644 --- a/ghc/compiler/simplCore/SimplEnv.lhs +++ b/ghc/compiler/simplCore/SimplEnv.lhs @@ -65,7 +65,6 @@ module SimplEnv ( IMPORT_Trace -import AbsPrel ( buildId ) import AbsUniType ( applyTypeEnvToTy, getUniDataTyCon, cmpUniType ) import Bag ( emptyBag, Bag ) import BasicLit ( isNoRepLit, BasicLit(..), PrimKind ) -- .. for pragmas only diff --git a/ghc/compiler/simplCore/SimplMonad.hi b/ghc/compiler/simplCore/SimplMonad.hi index 015d2f8a1aa4689e00c99ee82294d83637d44172..611eead67d11d219fff686a07b9c70dd11760a05 100644 --- a/ghc/compiler/simplCore/SimplMonad.hi +++ b/ghc/compiler/simplCore/SimplMonad.hi @@ -19,7 +19,7 @@ data PrimOp data SimplCount type SmplM a = SplitUniqSupply -> SimplCount -> (a, SimplCount) data SplitUniqSupply -data TickType = UnfoldingDone | FoldrBuild | MagicUnfold | ConReused | CaseFloatFromLet | CaseOfCase | LetFloatFromLet | LetFloatFromCase | KnownBranch | Let2Case | CaseMerge | CaseElim | CaseIdentity | AtomicRhs | EtaExpansion | CaseOfError | FoldrConsNil | Foldr_Nil | FoldrFoldr | Foldr_List | FoldrCons | FoldrInline | TyBetaReduction | BetaReduction +data TickType = UnfoldingDone | MagicUnfold | ConReused | CaseFloatFromLet | CaseOfCase | LetFloatFromLet | LetFloatFromCase | KnownBranch | Let2Case | CaseMerge | CaseElim | CaseIdentity | AtomicRhs | EtaExpansion | CaseOfError | TyBetaReduction | BetaReduction | FoldrBuild | FoldrAugment | Foldr_Nil | Foldr_List | FoldlBuild | FoldlAugment | Foldl_Nil | Foldl_List | Foldr_Cons_Nil | Foldr_Cons | Str_FoldrStr | Str_UnpackCons | Str_UnpackNil data TyVar data UniType cloneId :: SimplEnv -> (Id, BinderInfo) -> SplitUniqSupply -> SimplCount -> (Id, SimplCount) diff --git a/ghc/compiler/simplCore/SimplMonad.lhs b/ghc/compiler/simplCore/SimplMonad.lhs index e4b312fbb7570812a0b53258dc03aa1abc41fdd9..de3bc24869788c1dd774e06e68912df7fb6a0e30 100644 --- a/ghc/compiler/simplCore/SimplMonad.lhs +++ b/ghc/compiler/simplCore/SimplMonad.lhs @@ -124,59 +124,73 @@ data SimplCount [(TickType, Int)] -- assoc list of all diff kinds of ticks data TickType - = UnfoldingDone {-UNUSED: | Unused -} - | FoldrBuild | MagicUnfold | ConReused - | CaseFloatFromLet | CaseOfCase {-UNUSED: | CaseFloatFromApp -} - | LetFloatFromLet | LetFloatFromCase {-UNUSED: | LetFloatFromApp -} - | KnownBranch | Let2Case {-UNUSED: | UnboxingLet2Case -} - | CaseMerge {-UNUSED: | CaseToLet-} | CaseElim + = UnfoldingDone | MagicUnfold | ConReused + | CaseFloatFromLet | CaseOfCase + | LetFloatFromLet | LetFloatFromCase + | KnownBranch | Let2Case + | CaseMerge | CaseElim | CaseIdentity | AtomicRhs -- Rhs of a let-expression was an atom - | EtaExpansion {-UNUSED: | ArityExpand-} - {-UNUSED: | ConstantFolding-} | CaseOfError {-UNUSED: | InlineRemoved -} - | FoldrConsNil - | Foldr_Nil - | FoldrFoldr - | Foldr_List - | FoldrCons - | FoldrInline + | EtaExpansion + | CaseOfError | TyBetaReduction | BetaReduction + {- BEGIN F/B ENTRIES -} + -- the 8 rules + | FoldrBuild -- foldr f z (build g) ==> + | FoldrAugment -- foldr f z (augment g z) ==> + | Foldr_Nil -- foldr f z [] ==> + | Foldr_List -- foldr f z (x:...) ==> + + | FoldlBuild -- foldl f z (build g) ==> + | FoldlAugment -- foldl f z (augment g z) ==> + | Foldl_Nil -- foldl f z [] ==> + | Foldl_List -- foldl f z (x:...) ==> + + | Foldr_Cons_Nil -- foldr (:) [] => id + | Foldr_Cons -- foldr (:) => flip (++) + + | Str_FoldrStr -- foldr f z "hello" => unpackFoldrPS# f z "hello" + | Str_UnpackCons -- unpackFoldrPS# (:) z "hello" => unpackAppendPS# z "hello" + | Str_UnpackNil -- unpackAppendPS# [] "hello" => "hello" + {- END F/B ENTRIES -} deriving (Eq, Ord, Ix) instance Text TickType where showsPrec p UnfoldingDone = showString "UnfoldingDone " ---UNUSED: showsPrec p Unused = showString "Unused " - showsPrec p FoldrBuild = showString "FoldrBuild " showsPrec p MagicUnfold = showString "MagicUnfold " showsPrec p ConReused = showString "ConReused " showsPrec p CaseFloatFromLet= showString "CaseFloatFromLet " showsPrec p CaseOfCase = showString "CaseOfCase " ---UNUSED: showsPrec p CaseFloatFromApp= showString "CaseFloatFromApp " showsPrec p LetFloatFromLet = showString "LetFloatFromLet " showsPrec p LetFloatFromCase= showString "LetFloatFromCase " ---UNUSED: showsPrec p LetFloatFromApp = showString "LetFloatFromApp " showsPrec p KnownBranch = showString "KnownBranch " showsPrec p Let2Case = showString "Let2Case " ---UNUSED: showsPrec p UnboxingLet2Case= showString "UnboxingLet2Case " showsPrec p CaseMerge = showString "CaseMerge " ---UNUSED: showsPrec p CaseToLet = showString "CaseToLet " showsPrec p CaseElim = showString "CaseElim " showsPrec p CaseIdentity = showString "CaseIdentity " showsPrec p AtomicRhs = showString "AtomicRhs " showsPrec p EtaExpansion = showString "EtaExpansion " ---UNUSED: showsPrec p ArityExpand = showString "ArityExpand " ---UNUSED: showsPrec p ConstantFolding = showString "ConstantFolding " showsPrec p CaseOfError = showString "CaseOfError " ---UNUSED: showsPrec p InlineRemoved = showString "InlineRemoved " - showsPrec p FoldrConsNil = showString "FoldrConsNil " - showsPrec p Foldr_Nil = showString "Foldr_Nil " - showsPrec p FoldrFoldr = showString "FoldrFoldr " - showsPrec p Foldr_List = showString "Foldr_List " - showsPrec p FoldrCons = showString "FoldrCons " - showsPrec p FoldrInline = showString "FoldrInline " showsPrec p TyBetaReduction = showString "TyBetaReduction " showsPrec p BetaReduction = showString "BetaReduction " + -- Foldr/Build Stuff: + showsPrec p FoldrBuild = showString "FoldrBuild " + showsPrec p FoldrAugment = showString "FoldrAugment " + showsPrec p Foldr_Nil = showString "Foldr_Nil " + showsPrec p Foldr_List = showString "Foldr_List " + + showsPrec p FoldlBuild = showString "FoldlBuild " + showsPrec p FoldlAugment = showString "FoldlAugment " + showsPrec p Foldl_Nil = showString "Foldl_Nil " + showsPrec p Foldl_List = showString "Foldl_List " + + showsPrec p Foldr_Cons_Nil = showString "Foldr_Cons_Nil " + showsPrec p Foldr_Cons = showString "Foldr_Cons " + + showsPrec p Str_FoldrStr = showString "Str_FoldrStr " + showsPrec p Str_UnpackCons = showString "Str_UnpackCons " + showsPrec p Str_UnpackNil = showString "Str_UnpackNil " showSimplCount :: SimplCount -> String @@ -190,38 +204,38 @@ showSimplCount (SimplCount _ stuff) zeroSimplCount :: SimplCount zeroSimplCount = SimplCount ILIT(0) - [(UnfoldingDone, 0), ---UNUSED: (Unused, 0), - (FoldrBuild, 0), - (MagicUnfold, 0), - (ConReused, 0), - (CaseFloatFromLet, 0), - (CaseOfCase, 0), ---UNUSED: (CaseFloatFromApp, 0), - (LetFloatFromLet, 0), - (LetFloatFromCase, 0), ---UNUSED: (LetFloatFromApp, 0), - (KnownBranch, 0), - (Let2Case, 0), ---UNUSED: (UnboxingLet2Case, 0), - (CaseMerge, 0), ---UNUSED: (CaseToLet, 0), - (CaseElim, 0), - (CaseIdentity, 0), - (AtomicRhs, 0), - (EtaExpansion, 0), ---UNUSED: (ArityExpand,0), ---UNUSED: (ConstantFolding, 0), - (CaseOfError, 0), ---UNUSED: (InlineRemoved,0), - (FoldrConsNil,0), - (Foldr_Nil,0), - (FoldrFoldr,0), - (Foldr_List,0), - (FoldrCons,0), - (FoldrInline,0), - (TyBetaReduction,0), - (BetaReduction,0) ] + [ (UnfoldingDone, 0), + (MagicUnfold, 0), + (ConReused, 0), + (CaseFloatFromLet, 0), + (CaseOfCase, 0), + (LetFloatFromLet, 0), + (LetFloatFromCase, 0), + (KnownBranch, 0), + (Let2Case, 0), + (CaseMerge, 0), + (CaseElim, 0), + (CaseIdentity, 0), + (AtomicRhs, 0), + (EtaExpansion, 0), + (CaseOfError, 0), + (TyBetaReduction,0), + (BetaReduction,0), + -- Foldr/Build Stuff: + (FoldrBuild, 0), + (FoldrAugment, 0), + (Foldr_Nil, 0), + (Foldr_List, 0), + (FoldlBuild, 0), + (FoldlAugment, 0), + (Foldl_Nil, 0), + (Foldl_List, 0), + (Foldr_Cons_Nil, 0), + (Foldr_Cons, 0), + + (Str_FoldrStr, 0), + (Str_UnpackCons, 0), + (Str_UnpackNil, 0) ] -- --= array (con2tag_TickType UnfoldingDone, con2tag_TickType FoldrInline) -- [ i := 0 | i <- indices zeroSimplCount ] diff --git a/ghc/compiler/simplCore/SimplUtils.lhs b/ghc/compiler/simplCore/SimplUtils.lhs index e0ac4aac258b4f69c8c93a3cc36e29e35485ca42..3d4961f1614b7712ba30d07583f388e257123191 100644 --- a/ghc/compiler/simplCore/SimplUtils.lhs +++ b/ghc/compiler/simplCore/SimplUtils.lhs @@ -31,7 +31,8 @@ import SimplMonad import BinderInfo -import AbsPrel ( primOpIsCheap, realWorldStateTy, buildId +import AbsPrel ( primOpIsCheap, realWorldStateTy, + buildId, augmentId IF_ATTACK_PRAGMAS(COMMA realWorldTy) IF_ATTACK_PRAGMAS(COMMA tagOf_PrimOp) IF_ATTACK_PRAGMAS(COMMA pprPrimOp) @@ -79,7 +80,10 @@ floatExposesHNF float_lets float_primops ok_to_dup rhs -- `build g' -- is like a HNF, -- because it *will* become one. + -- likewise for `augment g h' + -- try (CoApp (CoTyApp (CoVar bld) _) _) | bld == buildId = True + try (CoApp (CoApp (CoTyApp (CoVar bld) _) _) _) | bld == augmentId = True try other = manifestlyWHNF other {- but *not* necessarily "manifestlyBottom other"... diff --git a/ghc/compiler/simplStg/LambdaLift.lhs b/ghc/compiler/simplStg/LambdaLift.lhs index 158ce90bce5f59a375cc9bb9bbdee9d3c1001e03..5e406d175f1b5edc5da77bff913d0374aa6edf2c 100644 --- a/ghc/compiler/simplStg/LambdaLift.lhs +++ b/ghc/compiler/simplStg/LambdaLift.lhs @@ -286,7 +286,10 @@ occurs in an argument position. isLiftable :: PlainStgRhs -> Bool isLiftable (StgRhsClosure _ (StgBinderInfo arg_occ _ _ _ unapplied_occ) fvs _ args _) - -- experimental evidence suggests we should lift only if we will be abstracting up to 4 fvs. + + -- Experimental evidence suggests we should lift only if we will be + -- abstracting up to 4 fvs. + = if not (null args || -- Not a function unapplied_occ || -- Has an occ with no args at all arg_occ || -- Occurs in arg position @@ -297,13 +300,36 @@ isLiftable (StgRhsClosure _ (StgBinderInfo arg_occ _ _ _ unapplied_occ) fvs _ ar isLiftable other_rhs = False isLiftableRec :: PlainStgRhs -> Bool --- this is just the same as for non-rec, except we only lift to abstract up to 1 argument --- this avoids undoing Static Argument Transformation work + +-- this is just the same as for non-rec, except we only lift to +-- abstract up to 1 argument this avoids undoing Static Argument +-- Transformation work + +{- Andre's longer comment about isLiftableRec: 1996/01: + +A rec binding is "liftable" (according to our heuristics) if: +* It is a function, +* all occurrences have arguments, +* does not occur in an argument position and +* has up to *2* free variables (including the rec binding variable + itself!) + +The point is: my experiments show that SAT is more important than LL. +Therefore if we still want to do LL, for *recursive* functions, we do +not want LL to undo what SAT did. We do this by avoiding LL recursive +functions that have more than 2 fvs, since if this recursive function +was created by SAT (we don't know!), it would have at least 3 fvs: one +for the rec binding itself and 2 more for the static arguments (note: +this matches with the choice of performing SAT to have at least 2 +static arguments, if we change things there we should change things +here). +-} + isLiftableRec (StgRhsClosure _ (StgBinderInfo arg_occ _ _ _ unapplied_occ) fvs _ args _) = if not (null args || -- Not a function unapplied_occ || -- Has an occ with no args at all arg_occ || -- Occurs in arg position - length fvs > 1 -- Too many free variables + length fvs > 2 -- Too many free variables ) then {-trace ("LLRec: " ++ show (length fvs))-} True else False @@ -314,10 +340,10 @@ rhsFreeVars (StgRhsClosure _ _ fvs _ _ _) = mkUniqSet fvs rhsFreeVars other = panic "rhsFreeVars" \end{code} -dontLiftRhs is like liftExpr, except that it does not lift a top-level lambda -abstraction. It is used for the right-hand sides of definitions where -we've decided *not* to lift: for example, top-level ones or mutually-recursive -ones where not all are lambdas. +dontLiftRhs is like liftExpr, except that it does not lift a top-level +lambda abstraction. It is used for the right-hand sides of +definitions where we've decided *not* to lift: for example, top-level +ones or mutually-recursive ones where not all are lambdas. \begin{code} dontLiftRhs :: PlainStgRhs -> LiftM (PlainStgRhs, LiftInfo) @@ -329,7 +355,6 @@ dontLiftRhs (StgRhsClosure cc bi fvs upd args body) returnLM (StgRhsClosure cc bi fvs upd args body', body_info) \end{code} - \begin{code} mkScPieces :: IdSet -- Extra args for the supercombinator -> (Id, PlainStgRhs) -- The processed RHS and original Id diff --git a/ghc/compiler/utils/Util.lhs b/ghc/compiler/utils/Util.lhs index 816cb2491903133b51754698dc0a06ab839a7505..4b00e9219c908865aaf63d11a5ce45475406ce6b 100644 --- a/ghc/compiler/utils/Util.lhs +++ b/ghc/compiler/utils/Util.lhs @@ -803,7 +803,7 @@ quite useful by itself I think it was John's idea originally though I believe the lazy version is due to me [surprisingly complicated]. gamma [used to be called] is called gamma because I got inspired by the Gamma calculus. It is not very close to the calculus but does -behave less sequential that both foldr and foldl. One could imagine a +behave less sequentially than both foldr and foldl. One could imagine a version of gamma that took a unit element as well thereby avoiding the problem with empty lists. @@ -812,12 +812,12 @@ I've tried this code against 1) insertion sort - as provided by haskell 2) the normal implementation of quick sort 3) a deforested version of quick sort due to Jan Sparud - 4) a super-optimized-quick-sort of Lennarts + 4) a super-optimized-quick-sort of Lennart's If the list is partially sorted both merge sort and in particular natural merge sort wins. If the list is random [ average length of rising subsequences = approx 2 ] mergesort still wins and natural -merge sort is marginally beeten by lennart's soqs. The space +merge sort is marginally beaten by Lennart's soqs. The space consumption of merge sort is a bit worse than Lennart's quick sort approx a factor of 2. And a lot worse if Sparud's bug-fix [see his fpca article ] isn't used because of group. diff --git a/ghc/driver/ghc-asm.lprl b/ghc/driver/ghc-asm.lprl index 2643ded5b8d9e5a7f82ef4d301d5c193a9098273..4a4834cea4949ad41beac830c1e1ed80dd5b2f37 100644 --- a/ghc/driver/ghc-asm.lprl +++ b/ghc/driver/ghc-asm.lprl @@ -1,6 +1,6 @@ %************************************************************************ %* * -\section[Driver-asm-fiddling]{Fiddling with assembler files (iX86)} +\section[Driver-asm-fiddling]{Fiddling with assembler files} %* * %************************************************************************ @@ -13,6 +13,12 @@ stuff to do with the C stack. Any other required tidying up. \end{itemize} +%************************************************************************ +%* * +\subsection{Constants for various architectures} +%* * +%************************************************************************ + \begin{code} sub init_TARGET_STUFF { @@ -58,6 +64,34 @@ sub init_TARGET_STUFF { $T_MOVE_DIRVS = '^\s*(\.align\s+\d+(,0x90)?\n|\.globl\s+\S+\n|\.text\n|\.data\n|\.section\s+.*\n|\.type\s+.*\n|\.Lfe.*\n\t\.size\s+.*\n|\.size\s+.*\n|\.ident.*\n)'; $T_COPY_DIRVS = '\.(globl)'; + $T_hsc_cc_PAT = '\.string.*\)(hsc|cc) (.*)\\\\t(.*)"'; + $T_DOT_WORD = '\.long'; + $T_HDR_string = "\.section\t\.rodata\n"; # or just use .text??? (WDP 95/11) + $T_HDR_misc = "\.text\n\t\.align 16\n"; + $T_HDR_data = "\.data\n\t\.align 4\n"; # ToDo: change align?? + $T_HDR_consist = "\.text\n"; + $T_HDR_closure = "\.data\n\t\.align 4\n"; # ToDo: change align? + $T_HDR_info = "\.text\n\t\.align 16\n"; # NB: requires padding + $T_HDR_entry = "\.text\n"; # no .align so we're right next to _info (arguably wrong...?) + $T_HDR_fast = "\.text\n\t\.align 16\n"; + $T_HDR_vector = "\.text\n\t\.align 16\n"; # NB: requires padding + $T_HDR_direct = "\.text\n\t\.align 16\n"; + + } elsif ( $TargetPlatform =~ /^powerpc-.*/ ) { + + $T_STABBY = 0; # 1 iff .stab things (usually if a.out format) + $T_US = '\.'; # _ if symbols have an underscore on the front + $T_DO_GC = 'PerformGC_wrapper'; + $T_PRE_APP = 'NOT APPLICABLE'; # regexp that says what comes before APP/NO_APP + $T_CONST_LBL = '^LC\.\.(\d+):$'; # regexp for what such a lbl looks like + $T_POST_LBL = ':'; + $T_PRE_LLBL_PAT = '\.L'; + $T_PRE_LLBL = '.L'; + $T_X86_BADJMP = 'NOT APPLICABLE'; + + $T_MOVE_DIRVS = '^\s*(\.align\s+\d+(,0x90)?\n|\.globl\s+\S+\n|\.text\n|\.data\n|\.section\s+.*\n|\.type\s+.*\n|\.Lfe.*\n\t\.size\s+.*\n|\.size\s+.*\n|\.ident.*\n)'; + $T_COPY_DIRVS = '\.(globl)'; + $T_hsc_cc_PAT = '\.string.*\)(hsc|cc) (.*)\\\\t(.*)"'; $T_DOT_WORD = '\.long'; $T_HDR_string = "\.section\t\.rodata\n"; # or just use .text??? (WDP 95/11) @@ -102,6 +136,12 @@ print STDERR "T_HDR_direct: $T_HDR_direct\n"; } \end{code} +%************************************************************************ +%* * +\subsection{Mangle away} +%* * +%************************************************************************ + \begin{code} sub mangle_asm { local($in_asmf, $out_asmf) = @_; diff --git a/ghc/driver/ghc.lprl b/ghc/driver/ghc.lprl index 90100944f40098059875683f74eb14b6514edb0c..7f00cd2f8f7dd21d593b3e10c476c0a89dce3e3f 100644 --- a/ghc/driver/ghc.lprl +++ b/ghc/driver/ghc.lprl @@ -211,6 +211,7 @@ $Oopt_DoSpecialise = '-fspecialise'; $Oopt_FoldrBuild = 1; # On by default! $Oopt_FB_Support = '-fdo-new-occur-anal -fdo-arity-expand'; #$Oopt_FoldrBuildWW = 0; # Off by default +$Oopt_FoldrBuildInline = '-fdo-inline-foldr-build'; \end{code} Things to do with C compilers/etc: @@ -282,7 +283,7 @@ $BuildTag = ''; # default is sequential build w/ Appel-style GC %BuildDescr = ('', 'normal sequential', '_p', 'profiling', '_t', 'ticky-ticky profiling', - '_t', 'unregisterized (using portable C only)', + '_u', 'unregisterized (using portable C only)', '_mc', 'concurrent', '_mr', 'profiled concurrent', '_mt', 'ticky concurrent', @@ -961,6 +962,12 @@ arg: while($_ = $ARGV[0]) { # Now the foldr/build options, which are *on* by default (for -O). + /^-ffoldr-build$/ + && do { $Oopt_FoldrBuild = 1; + $Oopt_FB_Support = '-fdo-new-occur-anal -fdo-arity-expand'; + #print "Yes F/B\n"; + next arg; }; + /^-fno-foldr-build$/ && do { $Oopt_FoldrBuild = 0; $Oopt_FB_Support = ''; @@ -974,6 +981,11 @@ arg: while($_ = $ARGV[0]) { && do { $Oopt_FB_Support = ''; next arg; }; + /^-fno-snapback-to-append$/ + && do { $Oopt_FoldrBuildInline .= ' -fdo-not-fold-back-append '; + #print "No Foldback of append\n"; + next arg; }; + # /^-ffoldr-build-ww$/ # && do { $Oopt_FoldrBuildWW = 1; next arg; }; @@ -1484,7 +1496,10 @@ It really really wants to be the last STG-to-STG pass that is run. '-fdo-eta-reduction', '-fdo-lambda-eta-expansion', '-freuse-con', - '-fdo-inline-foldr-build', # foldr/build done so inline + ($Oopt_FoldrBuildInline), + # you need to inline foldr and build + ($Oopt_FoldrBuild) ? ('-fdo-foldr-build') : (), + # but do reductions if you see them! "$Oopt_PedanticBottoms", "$Oopt_MonadEtaExpansion", "$Oopt_UnfoldingUseThreshold", @@ -1533,7 +1548,9 @@ It really really wants to be the last STG-to-STG pass that is run. '-freuse-con', '-flet-to-case', '-fignore-inline-pragma', # **** NB! - '-fdo-inline-foldr-build', # NB + $Oopt_FoldrBuildInline, + ($Oopt_FoldrBuild) ? ('-fdo-foldr-build') : (), + # but still do reductions if you see them! "$Oopt_PedanticBottoms", "$Oopt_MonadEtaExpansion", "$Oopt_UnfoldingUseThreshold", @@ -2019,7 +2036,7 @@ args: while ($a = shift(@ARGV)) { } } -exec "$SysMan $debug $nprocessors @nonPVM_args"; +exec "$SysMan $debug $pvm_executable $nprocessors @nonPVM_args"; print STDERR "Exec failed!!!: $SysMan $debug $nprocessors @nonPVM_args\n"; exit(1); EOSCRIPT2 diff --git a/ghc/includes/PEOpCodes.h b/ghc/includes/PEOpCodes.h index d1e6fadf0bc293f03b2caac952c64deab150e46f..8380f46dcf1defedbbb3c16ab3fa3d7f04219f3e 100644 --- a/ghc/includes/PEOpCodes.h +++ b/ghc/includes/PEOpCodes.h @@ -13,8 +13,8 @@ #define REPLY_OK 0x00 /*Startup + Shutdown*/ -#define PP_INIT 0x50 -#define PP_IO_INIT 0x51 +#define PP_SYSMAN_TID 0x50 +#define PP_MAIN_TASK 0x51 #define PP_FINISH 0x52 #define PP_PETIDS 0x53 diff --git a/ghc/includes/Parallel.lh b/ghc/includes/Parallel.lh index df37382be9253b359333c90180f08c9e96f9e1f7..cbf0e55660851b3f4b3b17b2592eac97bf316306 100644 --- a/ghc/includes/Parallel.lh +++ b/ghc/includes/Parallel.lh @@ -321,7 +321,7 @@ a distinguished info pointer. \begin{code} # define FMBQ_VHS BQ_VHS -# define FMBQ_HS BQ_HS +# define FMBQ_HS BQ_HS # define FMBQ_CLOSURE_SIZE(closure) BQ_CLOSURE_SIZE(closure) # define FMBQ_CLOSURE_NoPTRS(closure) BQ_CLOSURE_NoPTRS(closure) diff --git a/ghc/includes/SMinterface.lh b/ghc/includes/SMinterface.lh index 86279f1e2c62d45be80a6829394142086954db25..30699895f739d8bc91a8297731c4d38691a75ad8 100644 --- a/ghc/includes/SMinterface.lh +++ b/ghc/includes/SMinterface.lh @@ -433,6 +433,7 @@ same, but without the saved SuA pointer. We store the following information concerning the stacks in a global structure. (sequential only). \begin{code} +#ifndef CONCURRENT typedef struct { PP_ botA; /* Points to bottom-most word of A stack */ @@ -440,6 +441,8 @@ typedef struct { } stackData; extern stackData stackInfo; + +#endif /* !CONCURRENT */ \end{code} %************************************************************************ diff --git a/ghc/lib/Jmakefile b/ghc/lib/Jmakefile index b0bcb7892ceb80e653e649f62ccdf49a85065e77..b0baed015d2c4beaf05904852e28e951ef4df4cf 100644 --- a/ghc/lib/Jmakefile +++ b/ghc/lib/Jmakefile @@ -1065,7 +1065,7 @@ CompilePreludishly(prelude/Cls,hs, $(PREL_OPTS) -split-objs Cls -H24m -fmin-buil CompilePreludishly(prelude/Builtin,hs, $(PREL_OPTS) -split-objs Builtin -ohi prelude/Builtin.hi) CompilePreludishly(prelude/Core,hs, $(PREL_OPTS) -split-objs Core -H24m -ohi prelude/Core.hi) CompilePreludishly(prelude/IO,hs, $(PREL_OPTS) -split-objs IO -ohi prelude/IO.hi) -CompilePreludishly(prelude/List,hs, $(PREL_OPTS) -split-objs List -H24m -ohi prelude/List.hi) +CompilePreludishly(prelude/List,hs, $(PREL_OPTS) -split-objs List -H24m -ohi prelude/List.hi -fno-snapback-to-append) CompilePreludishly(prelude/PS,lhs, $(PREL_OPTS) -split-objs PS -ohi prelude/PS.hi -monly-2-regs) CompilePreludishly(prelude/Prel,hs, $(PREL_OPTS) -split-objs Prel -H14m -ohi prelude/Prel.hi -monly-2-regs) CompilePreludishly(prelude/Text,hs, $(PREL_OPTS) -split-objs Text -H30m -ohi prelude/Text.hi -monly-4-regs) diff --git a/ghc/lib/ghc/Bag.hi b/ghc/lib/ghc/Bag.hi index ba2a1ec1903a4a3b3a9a7573adf0ec0751bc0e5d..4ffe48724731b70d9de3c8914d4fb55385e0c298 100644 --- a/ghc/lib/ghc/Bag.hi +++ b/ghc/lib/ghc/Bag.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Bag where data Bag a {-# GHC_PRAGMA EmptyBag | UnitBag a | TwoBags (Bag a) (Bag a) | ListOfBags [Bag a] #-} bagToList :: Bag a -> [a] diff --git a/ghc/lib/ghc/Bag_mc.hi b/ghc/lib/ghc/Bag_mc.hi index ba2a1ec1903a4a3b3a9a7573adf0ec0751bc0e5d..4ffe48724731b70d9de3c8914d4fb55385e0c298 100644 --- a/ghc/lib/ghc/Bag_mc.hi +++ b/ghc/lib/ghc/Bag_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Bag where data Bag a {-# GHC_PRAGMA EmptyBag | UnitBag a | TwoBags (Bag a) (Bag a) | ListOfBags [Bag a] #-} bagToList :: Bag a -> [a] diff --git a/ghc/lib/ghc/Bag_mp.hi b/ghc/lib/ghc/Bag_mp.hi index ba2a1ec1903a4a3b3a9a7573adf0ec0751bc0e5d..4ffe48724731b70d9de3c8914d4fb55385e0c298 100644 --- a/ghc/lib/ghc/Bag_mp.hi +++ b/ghc/lib/ghc/Bag_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Bag where data Bag a {-# GHC_PRAGMA EmptyBag | UnitBag a | TwoBags (Bag a) (Bag a) | ListOfBags [Bag a] #-} bagToList :: Bag a -> [a] diff --git a/ghc/lib/ghc/Bag_p.hi b/ghc/lib/ghc/Bag_p.hi index ba2a1ec1903a4a3b3a9a7573adf0ec0751bc0e5d..4ffe48724731b70d9de3c8914d4fb55385e0c298 100644 --- a/ghc/lib/ghc/Bag_p.hi +++ b/ghc/lib/ghc/Bag_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Bag where data Bag a {-# GHC_PRAGMA EmptyBag | UnitBag a | TwoBags (Bag a) (Bag a) | ListOfBags [Bag a] #-} bagToList :: Bag a -> [a] diff --git a/ghc/lib/ghc/Bag_t.hi b/ghc/lib/ghc/Bag_t.hi index ba2a1ec1903a4a3b3a9a7573adf0ec0751bc0e5d..4ffe48724731b70d9de3c8914d4fb55385e0c298 100644 --- a/ghc/lib/ghc/Bag_t.hi +++ b/ghc/lib/ghc/Bag_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Bag where data Bag a {-# GHC_PRAGMA EmptyBag | UnitBag a | TwoBags (Bag a) (Bag a) | ListOfBags [Bag a] #-} bagToList :: Bag a -> [a] diff --git a/ghc/lib/ghc/BitSet.hi b/ghc/lib/ghc/BitSet.hi index 3642c0e5aefc18be56904e1bb04d699f1515aaa6..0df0842feba3f7f4f360db449e80d6fecd8ba020 100644 --- a/ghc/lib/ghc/BitSet.hi +++ b/ghc/lib/ghc/BitSet.hi @@ -1,10 +1,10 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface BitSet where data BitSet {-# GHC_PRAGMA MkBS Word# #-} elementBS :: Int -> BitSet -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} emptyBS :: BitSet - {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [0#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u0] } _N_ #-} + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} intersectBS :: BitSet -> BitSet -> BitSet {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: BitSet) (u1 :: BitSet) -> case u0 of { _ALG_ _ORIG_ BitSet MkBS (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ BitSet MkBS (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} isEmptyBS :: BitSet -> Bool diff --git a/ghc/lib/ghc/BitSet_mc.hi b/ghc/lib/ghc/BitSet_mc.hi index 3642c0e5aefc18be56904e1bb04d699f1515aaa6..0df0842feba3f7f4f360db449e80d6fecd8ba020 100644 --- a/ghc/lib/ghc/BitSet_mc.hi +++ b/ghc/lib/ghc/BitSet_mc.hi @@ -1,10 +1,10 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface BitSet where data BitSet {-# GHC_PRAGMA MkBS Word# #-} elementBS :: Int -> BitSet -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} emptyBS :: BitSet - {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [0#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u0] } _N_ #-} + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} intersectBS :: BitSet -> BitSet -> BitSet {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: BitSet) (u1 :: BitSet) -> case u0 of { _ALG_ _ORIG_ BitSet MkBS (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ BitSet MkBS (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} isEmptyBS :: BitSet -> Bool diff --git a/ghc/lib/ghc/BitSet_mp.hi b/ghc/lib/ghc/BitSet_mp.hi index 3642c0e5aefc18be56904e1bb04d699f1515aaa6..0df0842feba3f7f4f360db449e80d6fecd8ba020 100644 --- a/ghc/lib/ghc/BitSet_mp.hi +++ b/ghc/lib/ghc/BitSet_mp.hi @@ -1,10 +1,10 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface BitSet where data BitSet {-# GHC_PRAGMA MkBS Word# #-} elementBS :: Int -> BitSet -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} emptyBS :: BitSet - {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [0#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u0] } _N_ #-} + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} intersectBS :: BitSet -> BitSet -> BitSet {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: BitSet) (u1 :: BitSet) -> case u0 of { _ALG_ _ORIG_ BitSet MkBS (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ BitSet MkBS (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} isEmptyBS :: BitSet -> Bool diff --git a/ghc/lib/ghc/BitSet_p.hi b/ghc/lib/ghc/BitSet_p.hi index 3642c0e5aefc18be56904e1bb04d699f1515aaa6..0df0842feba3f7f4f360db449e80d6fecd8ba020 100644 --- a/ghc/lib/ghc/BitSet_p.hi +++ b/ghc/lib/ghc/BitSet_p.hi @@ -1,10 +1,10 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface BitSet where data BitSet {-# GHC_PRAGMA MkBS Word# #-} elementBS :: Int -> BitSet -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} emptyBS :: BitSet - {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [0#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u0] } _N_ #-} + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} intersectBS :: BitSet -> BitSet -> BitSet {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: BitSet) (u1 :: BitSet) -> case u0 of { _ALG_ _ORIG_ BitSet MkBS (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ BitSet MkBS (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} isEmptyBS :: BitSet -> Bool diff --git a/ghc/lib/ghc/BitSet_t.hi b/ghc/lib/ghc/BitSet_t.hi index 3642c0e5aefc18be56904e1bb04d699f1515aaa6..0df0842feba3f7f4f360db449e80d6fecd8ba020 100644 --- a/ghc/lib/ghc/BitSet_t.hi +++ b/ghc/lib/ghc/BitSet_t.hi @@ -1,10 +1,10 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface BitSet where data BitSet {-# GHC_PRAGMA MkBS Word# #-} elementBS :: Int -> BitSet -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} emptyBS :: BitSet - {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [0#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u0] } _N_ #-} + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} intersectBS :: BitSet -> BitSet -> BitSet {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: BitSet) (u1 :: BitSet) -> case u0 of { _ALG_ _ORIG_ BitSet MkBS (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ BitSet MkBS (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ BitSet MkBS [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} isEmptyBS :: BitSet -> Bool diff --git a/ghc/lib/ghc/CharSeq.hi b/ghc/lib/ghc/CharSeq.hi index a70b1430fe8152fae7133cffcf61fdcd64df5e99..19f6119888c4a8d2ad05a9f1b43f51a424cf7822 100644 --- a/ghc/lib/ghc/CharSeq.hi +++ b/ghc/lib/ghc/CharSeq.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface CharSeq where data CSeq {-# GHC_PRAGMA CNil | CAppend CSeq CSeq | CIndent Int CSeq | CNewline | CStr [Char] | CCh Char | CInt Int #-} cAppend :: CSeq -> CSeq -> CSeq diff --git a/ghc/lib/ghc/CharSeq_mc.hi b/ghc/lib/ghc/CharSeq_mc.hi index a70b1430fe8152fae7133cffcf61fdcd64df5e99..19f6119888c4a8d2ad05a9f1b43f51a424cf7822 100644 --- a/ghc/lib/ghc/CharSeq_mc.hi +++ b/ghc/lib/ghc/CharSeq_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface CharSeq where data CSeq {-# GHC_PRAGMA CNil | CAppend CSeq CSeq | CIndent Int CSeq | CNewline | CStr [Char] | CCh Char | CInt Int #-} cAppend :: CSeq -> CSeq -> CSeq diff --git a/ghc/lib/ghc/CharSeq_mp.hi b/ghc/lib/ghc/CharSeq_mp.hi index a70b1430fe8152fae7133cffcf61fdcd64df5e99..19f6119888c4a8d2ad05a9f1b43f51a424cf7822 100644 --- a/ghc/lib/ghc/CharSeq_mp.hi +++ b/ghc/lib/ghc/CharSeq_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface CharSeq where data CSeq {-# GHC_PRAGMA CNil | CAppend CSeq CSeq | CIndent Int CSeq | CNewline | CStr [Char] | CCh Char | CInt Int #-} cAppend :: CSeq -> CSeq -> CSeq diff --git a/ghc/lib/ghc/CharSeq_p.hi b/ghc/lib/ghc/CharSeq_p.hi index a70b1430fe8152fae7133cffcf61fdcd64df5e99..19f6119888c4a8d2ad05a9f1b43f51a424cf7822 100644 --- a/ghc/lib/ghc/CharSeq_p.hi +++ b/ghc/lib/ghc/CharSeq_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface CharSeq where data CSeq {-# GHC_PRAGMA CNil | CAppend CSeq CSeq | CIndent Int CSeq | CNewline | CStr [Char] | CCh Char | CInt Int #-} cAppend :: CSeq -> CSeq -> CSeq diff --git a/ghc/lib/ghc/CharSeq_t.hi b/ghc/lib/ghc/CharSeq_t.hi index a70b1430fe8152fae7133cffcf61fdcd64df5e99..19f6119888c4a8d2ad05a9f1b43f51a424cf7822 100644 --- a/ghc/lib/ghc/CharSeq_t.hi +++ b/ghc/lib/ghc/CharSeq_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface CharSeq where data CSeq {-# GHC_PRAGMA CNil | CAppend CSeq CSeq | CIndent Int CSeq | CNewline | CStr [Char] | CCh Char | CInt Int #-} cAppend :: CSeq -> CSeq -> CSeq diff --git a/ghc/lib/ghc/FiniteMap.hi b/ghc/lib/ghc/FiniteMap.hi index 1e3fa4478e049bf29be89d33272190012dd9dc50..c50dd5130a45338c53f1128d7ccdb2d9ec77ff38 100644 --- a/ghc/lib/ghc/FiniteMap.hi +++ b/ghc/lib/ghc/FiniteMap.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface FiniteMap where import PreludeStdIO(Maybe) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/FiniteMap_mc.hi b/ghc/lib/ghc/FiniteMap_mc.hi index 1e3fa4478e049bf29be89d33272190012dd9dc50..c50dd5130a45338c53f1128d7ccdb2d9ec77ff38 100644 --- a/ghc/lib/ghc/FiniteMap_mc.hi +++ b/ghc/lib/ghc/FiniteMap_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface FiniteMap where import PreludeStdIO(Maybe) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/FiniteMap_mp.hi b/ghc/lib/ghc/FiniteMap_mp.hi index 1e3fa4478e049bf29be89d33272190012dd9dc50..c50dd5130a45338c53f1128d7ccdb2d9ec77ff38 100644 --- a/ghc/lib/ghc/FiniteMap_mp.hi +++ b/ghc/lib/ghc/FiniteMap_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface FiniteMap where import PreludeStdIO(Maybe) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/FiniteMap_p.hi b/ghc/lib/ghc/FiniteMap_p.hi index 1e3fa4478e049bf29be89d33272190012dd9dc50..c50dd5130a45338c53f1128d7ccdb2d9ec77ff38 100644 --- a/ghc/lib/ghc/FiniteMap_p.hi +++ b/ghc/lib/ghc/FiniteMap_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface FiniteMap where import PreludeStdIO(Maybe) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/FiniteMap_t.hi b/ghc/lib/ghc/FiniteMap_t.hi index 1e3fa4478e049bf29be89d33272190012dd9dc50..c50dd5130a45338c53f1128d7ccdb2d9ec77ff38 100644 --- a/ghc/lib/ghc/FiniteMap_t.hi +++ b/ghc/lib/ghc/FiniteMap_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface FiniteMap where import PreludeStdIO(Maybe) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/ListSetOps.hi b/ghc/lib/ghc/ListSetOps.hi index 0b0224f84b28c7d42bad999933ddf6853a5e638c..f2c2986660cc72865a5d50105329e6f3763006cd 100644 --- a/ghc/lib/ghc/ListSetOps.hi +++ b/ghc/lib/ghc/ListSetOps.hi @@ -1,13 +1,13 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListSetOps where disjointLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectingLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} minusList :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} unionLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} diff --git a/ghc/lib/ghc/ListSetOps_mc.hi b/ghc/lib/ghc/ListSetOps_mc.hi index 0b0224f84b28c7d42bad999933ddf6853a5e638c..f2c2986660cc72865a5d50105329e6f3763006cd 100644 --- a/ghc/lib/ghc/ListSetOps_mc.hi +++ b/ghc/lib/ghc/ListSetOps_mc.hi @@ -1,13 +1,13 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListSetOps where disjointLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectingLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} minusList :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} unionLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} diff --git a/ghc/lib/ghc/ListSetOps_mp.hi b/ghc/lib/ghc/ListSetOps_mp.hi index 0b0224f84b28c7d42bad999933ddf6853a5e638c..f2c2986660cc72865a5d50105329e6f3763006cd 100644 --- a/ghc/lib/ghc/ListSetOps_mp.hi +++ b/ghc/lib/ghc/ListSetOps_mp.hi @@ -1,13 +1,13 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListSetOps where disjointLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectingLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} minusList :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} unionLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} diff --git a/ghc/lib/ghc/ListSetOps_p.hi b/ghc/lib/ghc/ListSetOps_p.hi index 0b0224f84b28c7d42bad999933ddf6853a5e638c..f2c2986660cc72865a5d50105329e6f3763006cd 100644 --- a/ghc/lib/ghc/ListSetOps_p.hi +++ b/ghc/lib/ghc/ListSetOps_p.hi @@ -1,13 +1,13 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListSetOps where disjointLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectingLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} minusList :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} unionLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} diff --git a/ghc/lib/ghc/ListSetOps_t.hi b/ghc/lib/ghc/ListSetOps_t.hi index 0b0224f84b28c7d42bad999933ddf6853a5e638c..f2c2986660cc72865a5d50105329e6f3763006cd 100644 --- a/ghc/lib/ghc/ListSetOps_t.hi +++ b/ghc/lib/ghc/ListSetOps_t.hi @@ -1,13 +1,13 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListSetOps where disjointLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} intersectingLists :: Eq a => [a] -> [a] -> Bool - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} minusList :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} unionLists :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} diff --git a/ghc/lib/ghc/Maybes.hi b/ghc/lib/ghc/Maybes.hi index cf5b8e0d1ace4f667c5d9e026635035110b23c44..cd3dcd09de778e7b5fbad169b9e9e8d03708873e 100644 --- a/ghc/lib/ghc/Maybes.hi +++ b/ghc/lib/ghc/Maybes.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Maybes where import Prelude(thenMaybe) import PreludeStdIO(Maybe(..)) diff --git a/ghc/lib/ghc/Maybes_mc.hi b/ghc/lib/ghc/Maybes_mc.hi index cf5b8e0d1ace4f667c5d9e026635035110b23c44..cd3dcd09de778e7b5fbad169b9e9e8d03708873e 100644 --- a/ghc/lib/ghc/Maybes_mc.hi +++ b/ghc/lib/ghc/Maybes_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Maybes where import Prelude(thenMaybe) import PreludeStdIO(Maybe(..)) diff --git a/ghc/lib/ghc/Maybes_mp.hi b/ghc/lib/ghc/Maybes_mp.hi index cf5b8e0d1ace4f667c5d9e026635035110b23c44..cd3dcd09de778e7b5fbad169b9e9e8d03708873e 100644 --- a/ghc/lib/ghc/Maybes_mp.hi +++ b/ghc/lib/ghc/Maybes_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Maybes where import Prelude(thenMaybe) import PreludeStdIO(Maybe(..)) diff --git a/ghc/lib/ghc/Maybes_p.hi b/ghc/lib/ghc/Maybes_p.hi index cf5b8e0d1ace4f667c5d9e026635035110b23c44..cd3dcd09de778e7b5fbad169b9e9e8d03708873e 100644 --- a/ghc/lib/ghc/Maybes_p.hi +++ b/ghc/lib/ghc/Maybes_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Maybes where import Prelude(thenMaybe) import PreludeStdIO(Maybe(..)) diff --git a/ghc/lib/ghc/Maybes_t.hi b/ghc/lib/ghc/Maybes_t.hi index cf5b8e0d1ace4f667c5d9e026635035110b23c44..cd3dcd09de778e7b5fbad169b9e9e8d03708873e 100644 --- a/ghc/lib/ghc/Maybes_t.hi +++ b/ghc/lib/ghc/Maybes_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Maybes where import Prelude(thenMaybe) import PreludeStdIO(Maybe(..)) diff --git a/ghc/lib/ghc/PackedString_mc.hi b/ghc/lib/ghc/PackedString_mc.hi index c7921866a3337da850247956d2a320542579a413..5e1fa9d5d56f24f3a49bfb4a2444348153544763 100644 --- a/ghc/lib/ghc/PackedString_mc.hi +++ b/ghc/lib/ghc/PackedString_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PackedString where import PreludeArray(_ByteArray) import PreludePS(_PackedString) diff --git a/ghc/lib/ghc/PackedString_mp.hi b/ghc/lib/ghc/PackedString_mp.hi index c7921866a3337da850247956d2a320542579a413..5e1fa9d5d56f24f3a49bfb4a2444348153544763 100644 --- a/ghc/lib/ghc/PackedString_mp.hi +++ b/ghc/lib/ghc/PackedString_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PackedString where import PreludeArray(_ByteArray) import PreludePS(_PackedString) diff --git a/ghc/lib/ghc/PackedString_p.hi b/ghc/lib/ghc/PackedString_p.hi index c7921866a3337da850247956d2a320542579a413..5e1fa9d5d56f24f3a49bfb4a2444348153544763 100644 --- a/ghc/lib/ghc/PackedString_p.hi +++ b/ghc/lib/ghc/PackedString_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PackedString where import PreludeArray(_ByteArray) import PreludePS(_PackedString) diff --git a/ghc/lib/ghc/PackedString_t.hi b/ghc/lib/ghc/PackedString_t.hi index c7921866a3337da850247956d2a320542579a413..5e1fa9d5d56f24f3a49bfb4a2444348153544763 100644 --- a/ghc/lib/ghc/PackedString_t.hi +++ b/ghc/lib/ghc/PackedString_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PackedString where import PreludeArray(_ByteArray) import PreludePS(_PackedString) diff --git a/ghc/lib/ghc/Pretty.hi b/ghc/lib/ghc/Pretty.hi index f09119b7fe1ee6fa3ef47432ae8ca9bc2a06ae44..da9e419a87dd27e01ebd08a04b7b04357564e94b 100644 --- a/ghc/lib/ghc/Pretty.hi +++ b/ghc/lib/ghc/Pretty.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where import CharSeq(CSeq) import PreludeRatio(Ratio(..)) @@ -7,7 +7,7 @@ data Delay a {-# GHC_PRAGMA MkDelay a #-} type Pretty = Int -> Bool -> PrettyRep data PrettyRep = MkPrettyRep CSeq (Delay Int) Bool Bool pp'SP :: Int -> Bool -> PrettyRep - {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _APP_ _ORIG_ Pretty ppStr [ _NOREP_S_ ", " ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _N_ _N_ #-} ppAbove :: (Int -> Bool -> PrettyRep) -> (Int -> Bool -> PrettyRep) -> Int -> Bool -> PrettyRep {-# GHC_PRAGMA _A_ 4 _U_ 1120 _N_ _S_ "SLLA" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} ppAboves :: [Int -> Bool -> PrettyRep] -> Int -> Bool -> PrettyRep diff --git a/ghc/lib/ghc/Pretty_mc.hi b/ghc/lib/ghc/Pretty_mc.hi index f09119b7fe1ee6fa3ef47432ae8ca9bc2a06ae44..da9e419a87dd27e01ebd08a04b7b04357564e94b 100644 --- a/ghc/lib/ghc/Pretty_mc.hi +++ b/ghc/lib/ghc/Pretty_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where import CharSeq(CSeq) import PreludeRatio(Ratio(..)) @@ -7,7 +7,7 @@ data Delay a {-# GHC_PRAGMA MkDelay a #-} type Pretty = Int -> Bool -> PrettyRep data PrettyRep = MkPrettyRep CSeq (Delay Int) Bool Bool pp'SP :: Int -> Bool -> PrettyRep - {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _APP_ _ORIG_ Pretty ppStr [ _NOREP_S_ ", " ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _N_ _N_ #-} ppAbove :: (Int -> Bool -> PrettyRep) -> (Int -> Bool -> PrettyRep) -> Int -> Bool -> PrettyRep {-# GHC_PRAGMA _A_ 4 _U_ 1120 _N_ _S_ "SLLA" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} ppAboves :: [Int -> Bool -> PrettyRep] -> Int -> Bool -> PrettyRep diff --git a/ghc/lib/ghc/Pretty_mp.hi b/ghc/lib/ghc/Pretty_mp.hi index f09119b7fe1ee6fa3ef47432ae8ca9bc2a06ae44..da9e419a87dd27e01ebd08a04b7b04357564e94b 100644 --- a/ghc/lib/ghc/Pretty_mp.hi +++ b/ghc/lib/ghc/Pretty_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where import CharSeq(CSeq) import PreludeRatio(Ratio(..)) @@ -7,7 +7,7 @@ data Delay a {-# GHC_PRAGMA MkDelay a #-} type Pretty = Int -> Bool -> PrettyRep data PrettyRep = MkPrettyRep CSeq (Delay Int) Bool Bool pp'SP :: Int -> Bool -> PrettyRep - {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _APP_ _ORIG_ Pretty ppStr [ _NOREP_S_ ", " ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _N_ _N_ #-} ppAbove :: (Int -> Bool -> PrettyRep) -> (Int -> Bool -> PrettyRep) -> Int -> Bool -> PrettyRep {-# GHC_PRAGMA _A_ 4 _U_ 1120 _N_ _S_ "SLLA" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} ppAboves :: [Int -> Bool -> PrettyRep] -> Int -> Bool -> PrettyRep diff --git a/ghc/lib/ghc/Pretty_p.hi b/ghc/lib/ghc/Pretty_p.hi index f09119b7fe1ee6fa3ef47432ae8ca9bc2a06ae44..da9e419a87dd27e01ebd08a04b7b04357564e94b 100644 --- a/ghc/lib/ghc/Pretty_p.hi +++ b/ghc/lib/ghc/Pretty_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where import CharSeq(CSeq) import PreludeRatio(Ratio(..)) @@ -7,7 +7,7 @@ data Delay a {-# GHC_PRAGMA MkDelay a #-} type Pretty = Int -> Bool -> PrettyRep data PrettyRep = MkPrettyRep CSeq (Delay Int) Bool Bool pp'SP :: Int -> Bool -> PrettyRep - {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _APP_ _ORIG_ Pretty ppStr [ _NOREP_S_ ", " ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _N_ _N_ #-} ppAbove :: (Int -> Bool -> PrettyRep) -> (Int -> Bool -> PrettyRep) -> Int -> Bool -> PrettyRep {-# GHC_PRAGMA _A_ 4 _U_ 1120 _N_ _S_ "SLLA" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} ppAboves :: [Int -> Bool -> PrettyRep] -> Int -> Bool -> PrettyRep diff --git a/ghc/lib/ghc/Pretty_t.hi b/ghc/lib/ghc/Pretty_t.hi index f09119b7fe1ee6fa3ef47432ae8ca9bc2a06ae44..da9e419a87dd27e01ebd08a04b7b04357564e94b 100644 --- a/ghc/lib/ghc/Pretty_t.hi +++ b/ghc/lib/ghc/Pretty_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where import CharSeq(CSeq) import PreludeRatio(Ratio(..)) @@ -7,7 +7,7 @@ data Delay a {-# GHC_PRAGMA MkDelay a #-} type Pretty = Int -> Bool -> PrettyRep data PrettyRep = MkPrettyRep CSeq (Delay Int) Bool Bool pp'SP :: Int -> Bool -> PrettyRep - {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _APP_ _ORIG_ Pretty ppStr [ _NOREP_S_ ", " ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 10 _N_ _N_ _N_ _N_ #-} ppAbove :: (Int -> Bool -> PrettyRep) -> (Int -> Bool -> PrettyRep) -> Int -> Bool -> PrettyRep {-# GHC_PRAGMA _A_ 4 _U_ 1120 _N_ _S_ "SLLA" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} ppAboves :: [Int -> Bool -> PrettyRep] -> Int -> Bool -> PrettyRep diff --git a/ghc/lib/ghc/Set.hi b/ghc/lib/ghc/Set.hi index ad1d9567dc29e218f30757c8f231b62ab36dba2b..e247da6c44451d517cabcfe89e6a501dfa5d6a63 100644 --- a/ghc/lib/ghc/Set.hi +++ b/ghc/lib/ghc/Set.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Set where import FiniteMap(FiniteMap, keysFM, sizeFM) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/Set_mc.hi b/ghc/lib/ghc/Set_mc.hi index ad1d9567dc29e218f30757c8f231b62ab36dba2b..e247da6c44451d517cabcfe89e6a501dfa5d6a63 100644 --- a/ghc/lib/ghc/Set_mc.hi +++ b/ghc/lib/ghc/Set_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Set where import FiniteMap(FiniteMap, keysFM, sizeFM) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/Set_mp.hi b/ghc/lib/ghc/Set_mp.hi index ad1d9567dc29e218f30757c8f231b62ab36dba2b..e247da6c44451d517cabcfe89e6a501dfa5d6a63 100644 --- a/ghc/lib/ghc/Set_mp.hi +++ b/ghc/lib/ghc/Set_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Set where import FiniteMap(FiniteMap, keysFM, sizeFM) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/Set_p.hi b/ghc/lib/ghc/Set_p.hi index ad1d9567dc29e218f30757c8f231b62ab36dba2b..e247da6c44451d517cabcfe89e6a501dfa5d6a63 100644 --- a/ghc/lib/ghc/Set_p.hi +++ b/ghc/lib/ghc/Set_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Set where import FiniteMap(FiniteMap, keysFM, sizeFM) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/Set_t.hi b/ghc/lib/ghc/Set_t.hi index ad1d9567dc29e218f30757c8f231b62ab36dba2b..e247da6c44451d517cabcfe89e6a501dfa5d6a63 100644 --- a/ghc/lib/ghc/Set_t.hi +++ b/ghc/lib/ghc/Set_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Set where import FiniteMap(FiniteMap, keysFM, sizeFM) data FiniteMap a b {-# GHC_PRAGMA EmptyFM | Branch a b Int# (FiniteMap a b) (FiniteMap a b) #-} diff --git a/ghc/lib/ghc/Util.hi b/ghc/lib/ghc/Util.hi index 1bab8f1f20a699ac73d7a8f8208870eb21bc58db..22566b6df021955d75bc5a514eb89e3431373b71 100644 --- a/ghc/lib/ghc/Util.hi +++ b/ghc/lib/ghc/Util.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Util where applyToFst :: (a -> b) -> (a, c) -> (b, c) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(LL)" {_A_ 3 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 3 3 XXX 6 _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: u0) (u5 :: u2) -> let {(u6 :: u1) = _APP_ u3 [ u4 ]} in _!_ _TUP_2 [u1, u2] [u6, u5] _N_} _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: (u0, u2)) -> case u4 of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: u2) -> let {(u7 :: u1) = _APP_ u3 [ u5 ]} in _!_ _TUP_2 [u1, u2] [u7, u6]; _NO_DEFLT_ } _N_ #-} @@ -21,7 +21,7 @@ foldPair :: (a -> a -> a, b -> b -> b) -> (a, b) -> [(a, b)] -> (a, b) forall :: (a -> Bool) -> [a] -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} hasNoDups :: Eq a => [a] -> Bool - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} isSingleton :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} lengthExceeds :: [a] -> Int -> Bool @@ -35,7 +35,7 @@ mapAccumR :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) mergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util mergeSortLe { u0 } [ ua ] _N_ #-} mergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} mergesort :: (a -> a -> _CMP_TAG) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} nOfThem :: Int -> a -> [a] @@ -43,7 +43,7 @@ nOfThem :: Int -> a -> [a] naturalMergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util naturalMergeSortLe { u0 } [ ua ] _N_ #-} naturalMergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} quicksort :: (a -> a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} removeDups :: (a -> a -> _CMP_TAG) -> [a] -> ([a], [[a]]) diff --git a/ghc/lib/ghc/Util.lhs b/ghc/lib/ghc/Util.lhs index 7f0d40680b12d5ad1592d3da969467c88acb4c44..4b00e9219c908865aaf63d11a5ce45475406ce6b 100644 --- a/ghc/lib/ghc/Util.lhs +++ b/ghc/lib/ghc/Util.lhs @@ -797,27 +797,28 @@ From: Carsten Kehler Holst <kehler@cs.chalmers.se> To: partain@dcs.gla.ac.uk Subject: natural merge sort beats quick sort [ and it is prettier ] - Here a piece of Haskell code that I'm rather fond of. See it as an -attempt to get rid of the ridiculous quick-sort rutine. group is quite -useful by itself I think it was John's idea originally though I +Here a piece of Haskell code that I'm rather fond of. See it as an +attempt to get rid of the ridiculous quick-sort routine. group is +quite useful by itself I think it was John's idea originally though I believe the lazy version is due to me [surprisingly complicated]. -gamma [used to be called] called gamma because I got inspired by the Gamma calculus. It -is not very close to the calculus but does behave less sequential that -both foldr and foldl. One could imagine a version of gamma that took a -unit element as well thereby avoiding the problem with empty lists. +gamma [used to be called] is called gamma because I got inspired by +the Gamma calculus. It is not very close to the calculus but does +behave less sequentially than both foldr and foldl. One could imagine a +version of gamma that took a unit element as well thereby avoiding the +problem with empty lists. I've tried this code against 1) insertion sort - as provided by haskell 2) the normal implementation of quick sort 3) a deforested version of quick sort due to Jan Sparud - 4) a super-optimized-quick-sort of Lennarts + 4) a super-optimized-quick-sort of Lennart's If the list is partially sorted both merge sort and in particular natural merge sort wins. If the list is random [ average length of rising subsequences = approx 2 ] mergesort still wins and natural -merge sort is marginally beeten by lennart's soqs. The space -consumption of merge sort is a bit worse than Lennarts quick sort +merge sort is marginally beaten by Lennart's soqs. The space +consumption of merge sort is a bit worse than Lennart's quick sort approx a factor of 2. And a lot worse if Sparud's bug-fix [see his fpca article ] isn't used because of group. @@ -827,6 +828,7 @@ Carsten \begin{code} group :: (a -> a -> Bool) -> [a] -> [[a]] + group p [] = [[]] group p (x:xs) = let ((h1:t1):tt1) = group p xs @@ -838,8 +840,8 @@ group p (x:xs) = generalMerge :: (a -> a -> Bool) -> [a] -> [a] -> [a] generalMerge p xs [] = xs generalMerge p [] ys = ys -generalMerge p (x:xs) (y:ys) | x `p` y = x : generalMerge p xs (y:ys) - | y `p` x = y : generalMerge p (x:xs) ys +generalMerge p (x:xs) (y:ys) | x `p` y = x : generalMerge p xs (y:ys) + | otherwise = y : generalMerge p (x:xs) ys -- gamma is now called balancedFold @@ -852,8 +854,11 @@ balancedFold' :: (a -> a -> a) -> [a] -> [a] balancedFold' f (x:y:xs) = f x y : balancedFold' f xs balancedFold' f xs = xs -generalMergeSort p = balancedFold (generalMerge p) . map (:[]) -generalNaturalMergeSort p = balancedFold (generalMerge p) . group p +generalMergeSort p [] = [] +generalMergeSort p xs = (balancedFold (generalMerge p) . map (: [])) xs + +generalNaturalMergeSort p [] = [] +generalNaturalMergeSort p xs = (balancedFold (generalMerge p) . group p) xs mergeSort, naturalMergeSort :: Ord a => [a] -> [a] diff --git a/ghc/lib/ghc/Util_mc.hi b/ghc/lib/ghc/Util_mc.hi index 1bab8f1f20a699ac73d7a8f8208870eb21bc58db..22566b6df021955d75bc5a514eb89e3431373b71 100644 --- a/ghc/lib/ghc/Util_mc.hi +++ b/ghc/lib/ghc/Util_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Util where applyToFst :: (a -> b) -> (a, c) -> (b, c) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(LL)" {_A_ 3 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 3 3 XXX 6 _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: u0) (u5 :: u2) -> let {(u6 :: u1) = _APP_ u3 [ u4 ]} in _!_ _TUP_2 [u1, u2] [u6, u5] _N_} _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: (u0, u2)) -> case u4 of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: u2) -> let {(u7 :: u1) = _APP_ u3 [ u5 ]} in _!_ _TUP_2 [u1, u2] [u7, u6]; _NO_DEFLT_ } _N_ #-} @@ -21,7 +21,7 @@ foldPair :: (a -> a -> a, b -> b -> b) -> (a, b) -> [(a, b)] -> (a, b) forall :: (a -> Bool) -> [a] -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} hasNoDups :: Eq a => [a] -> Bool - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} isSingleton :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} lengthExceeds :: [a] -> Int -> Bool @@ -35,7 +35,7 @@ mapAccumR :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) mergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util mergeSortLe { u0 } [ ua ] _N_ #-} mergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} mergesort :: (a -> a -> _CMP_TAG) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} nOfThem :: Int -> a -> [a] @@ -43,7 +43,7 @@ nOfThem :: Int -> a -> [a] naturalMergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util naturalMergeSortLe { u0 } [ ua ] _N_ #-} naturalMergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} quicksort :: (a -> a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} removeDups :: (a -> a -> _CMP_TAG) -> [a] -> ([a], [[a]]) diff --git a/ghc/lib/ghc/Util_mp.hi b/ghc/lib/ghc/Util_mp.hi index 1bab8f1f20a699ac73d7a8f8208870eb21bc58db..22566b6df021955d75bc5a514eb89e3431373b71 100644 --- a/ghc/lib/ghc/Util_mp.hi +++ b/ghc/lib/ghc/Util_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Util where applyToFst :: (a -> b) -> (a, c) -> (b, c) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(LL)" {_A_ 3 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 3 3 XXX 6 _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: u0) (u5 :: u2) -> let {(u6 :: u1) = _APP_ u3 [ u4 ]} in _!_ _TUP_2 [u1, u2] [u6, u5] _N_} _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: (u0, u2)) -> case u4 of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: u2) -> let {(u7 :: u1) = _APP_ u3 [ u5 ]} in _!_ _TUP_2 [u1, u2] [u7, u6]; _NO_DEFLT_ } _N_ #-} @@ -21,7 +21,7 @@ foldPair :: (a -> a -> a, b -> b -> b) -> (a, b) -> [(a, b)] -> (a, b) forall :: (a -> Bool) -> [a] -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} hasNoDups :: Eq a => [a] -> Bool - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} isSingleton :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} lengthExceeds :: [a] -> Int -> Bool @@ -35,7 +35,7 @@ mapAccumR :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) mergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util mergeSortLe { u0 } [ ua ] _N_ #-} mergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} mergesort :: (a -> a -> _CMP_TAG) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} nOfThem :: Int -> a -> [a] @@ -43,7 +43,7 @@ nOfThem :: Int -> a -> [a] naturalMergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util naturalMergeSortLe { u0 } [ ua ] _N_ #-} naturalMergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} quicksort :: (a -> a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} removeDups :: (a -> a -> _CMP_TAG) -> [a] -> ([a], [[a]]) diff --git a/ghc/lib/ghc/Util_p.hi b/ghc/lib/ghc/Util_p.hi index 1bab8f1f20a699ac73d7a8f8208870eb21bc58db..22566b6df021955d75bc5a514eb89e3431373b71 100644 --- a/ghc/lib/ghc/Util_p.hi +++ b/ghc/lib/ghc/Util_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Util where applyToFst :: (a -> b) -> (a, c) -> (b, c) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(LL)" {_A_ 3 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 3 3 XXX 6 _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: u0) (u5 :: u2) -> let {(u6 :: u1) = _APP_ u3 [ u4 ]} in _!_ _TUP_2 [u1, u2] [u6, u5] _N_} _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: (u0, u2)) -> case u4 of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: u2) -> let {(u7 :: u1) = _APP_ u3 [ u5 ]} in _!_ _TUP_2 [u1, u2] [u7, u6]; _NO_DEFLT_ } _N_ #-} @@ -21,7 +21,7 @@ foldPair :: (a -> a -> a, b -> b -> b) -> (a, b) -> [(a, b)] -> (a, b) forall :: (a -> Bool) -> [a] -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} hasNoDups :: Eq a => [a] -> Bool - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} isSingleton :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} lengthExceeds :: [a] -> Int -> Bool @@ -35,7 +35,7 @@ mapAccumR :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) mergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util mergeSortLe { u0 } [ ua ] _N_ #-} mergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} mergesort :: (a -> a -> _CMP_TAG) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} nOfThem :: Int -> a -> [a] @@ -43,7 +43,7 @@ nOfThem :: Int -> a -> [a] naturalMergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util naturalMergeSortLe { u0 } [ ua ] _N_ #-} naturalMergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} quicksort :: (a -> a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} removeDups :: (a -> a -> _CMP_TAG) -> [a] -> ([a], [[a]]) diff --git a/ghc/lib/ghc/Util_t.hi b/ghc/lib/ghc/Util_t.hi index 1bab8f1f20a699ac73d7a8f8208870eb21bc58db..22566b6df021955d75bc5a514eb89e3431373b71 100644 --- a/ghc/lib/ghc/Util_t.hi +++ b/ghc/lib/ghc/Util_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Util where applyToFst :: (a -> b) -> (a, c) -> (b, c) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(LL)" {_A_ 3 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 3 3 XXX 6 _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: u0) (u5 :: u2) -> let {(u6 :: u1) = _APP_ u3 [ u4 ]} in _!_ _TUP_2 [u1, u2] [u6, u5] _N_} _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: u0 -> u1) (u4 :: (u0, u2)) -> case u4 of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: u2) -> let {(u7 :: u1) = _APP_ u3 [ u5 ]} in _!_ _TUP_2 [u1, u2] [u7, u6]; _NO_DEFLT_ } _N_ #-} @@ -21,7 +21,7 @@ foldPair :: (a -> a -> a, b -> b -> b) -> (a, b) -> [(a, b)] -> (a, b) forall :: (a -> Bool) -> [a] -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} hasNoDups :: Eq a => [a] -> Bool - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} isSingleton :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} lengthExceeds :: [a] -> Int -> Bool @@ -35,7 +35,7 @@ mapAccumR :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) mergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util mergeSortLe { u0 } [ ua ] _N_ #-} mergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} mergesort :: (a -> a -> _CMP_TAG) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} nOfThem :: Int -> a -> [a] @@ -43,7 +43,7 @@ nOfThem :: Int -> a -> [a] naturalMergeSort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: {{Ord u0}}) -> let {(ua :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_8 (u2 :: {{Eq u0}}) (u3 :: u0 -> u0 -> Bool) (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) (u6 :: u0 -> u0 -> Bool) (u7 :: u0 -> u0 -> u0) (u8 :: u0 -> u0 -> u0) (u9 :: u0 -> u0 -> _CMP_TAG) -> u4; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ Util naturalMergeSortLe { u0 } [ ua ] _N_ #-} naturalMergeSortLe :: (a -> a -> Bool) -> [a] -> [a] - {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ #-} quicksort :: (a -> a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} removeDups :: (a -> a -> _CMP_TAG) -> [a] -> ([a], [[a]]) diff --git a/ghc/lib/glaExts/PreludeErrIO.hi b/ghc/lib/glaExts/PreludeErrIO.hi index 352a49beff00fe434f60498742386b1fc4038f5c..55d5a0c7dca892019f9a8d0198aec8279be055da 100644 --- a/ghc/lib/glaExts/PreludeErrIO.hi +++ b/ghc/lib/glaExts/PreludeErrIO.hi @@ -1,6 +1,6 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeErrIO where import PreludeBuiltin(Tuple0, Tuple2, _RealWorld(..), _State(..)) errorIO :: (_State _RealWorld -> ((), _State _RealWorld)) -> a - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 4 _/\_ u0 -> \ (u1 :: _State _RealWorld -> ((), _State _RealWorld)) -> _LETREC_ {(u2 :: _forall_ a$z1 =>a$z1) = u2} in case _#_ errorIO# [] [u1] of { _PRIM_ (u3 :: State# _RealWorld) -> _TYAPP_ u2 { u0 } } _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} diff --git a/ghc/lib/glaExts/PreludeErrIO_mc.hi b/ghc/lib/glaExts/PreludeErrIO_mc.hi index 352a49beff00fe434f60498742386b1fc4038f5c..55d5a0c7dca892019f9a8d0198aec8279be055da 100644 --- a/ghc/lib/glaExts/PreludeErrIO_mc.hi +++ b/ghc/lib/glaExts/PreludeErrIO_mc.hi @@ -1,6 +1,6 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeErrIO where import PreludeBuiltin(Tuple0, Tuple2, _RealWorld(..), _State(..)) errorIO :: (_State _RealWorld -> ((), _State _RealWorld)) -> a - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 4 _/\_ u0 -> \ (u1 :: _State _RealWorld -> ((), _State _RealWorld)) -> _LETREC_ {(u2 :: _forall_ a$z1 =>a$z1) = u2} in case _#_ errorIO# [] [u1] of { _PRIM_ (u3 :: State# _RealWorld) -> _TYAPP_ u2 { u0 } } _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} diff --git a/ghc/lib/glaExts/PreludeErrIO_mp.hi b/ghc/lib/glaExts/PreludeErrIO_mp.hi index 352a49beff00fe434f60498742386b1fc4038f5c..55d5a0c7dca892019f9a8d0198aec8279be055da 100644 --- a/ghc/lib/glaExts/PreludeErrIO_mp.hi +++ b/ghc/lib/glaExts/PreludeErrIO_mp.hi @@ -1,6 +1,6 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeErrIO where import PreludeBuiltin(Tuple0, Tuple2, _RealWorld(..), _State(..)) errorIO :: (_State _RealWorld -> ((), _State _RealWorld)) -> a - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 4 _/\_ u0 -> \ (u1 :: _State _RealWorld -> ((), _State _RealWorld)) -> _LETREC_ {(u2 :: _forall_ a$z1 =>a$z1) = u2} in case _#_ errorIO# [] [u1] of { _PRIM_ (u3 :: State# _RealWorld) -> _TYAPP_ u2 { u0 } } _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} diff --git a/ghc/lib/glaExts/PreludeErrIO_p.hi b/ghc/lib/glaExts/PreludeErrIO_p.hi index 352a49beff00fe434f60498742386b1fc4038f5c..55d5a0c7dca892019f9a8d0198aec8279be055da 100644 --- a/ghc/lib/glaExts/PreludeErrIO_p.hi +++ b/ghc/lib/glaExts/PreludeErrIO_p.hi @@ -1,6 +1,6 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeErrIO where import PreludeBuiltin(Tuple0, Tuple2, _RealWorld(..), _State(..)) errorIO :: (_State _RealWorld -> ((), _State _RealWorld)) -> a - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 4 _/\_ u0 -> \ (u1 :: _State _RealWorld -> ((), _State _RealWorld)) -> _LETREC_ {(u2 :: _forall_ a$z1 =>a$z1) = u2} in case _#_ errorIO# [] [u1] of { _PRIM_ (u3 :: State# _RealWorld) -> _TYAPP_ u2 { u0 } } _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} diff --git a/ghc/lib/glaExts/PreludeErrIO_t.hi b/ghc/lib/glaExts/PreludeErrIO_t.hi index 352a49beff00fe434f60498742386b1fc4038f5c..55d5a0c7dca892019f9a8d0198aec8279be055da 100644 --- a/ghc/lib/glaExts/PreludeErrIO_t.hi +++ b/ghc/lib/glaExts/PreludeErrIO_t.hi @@ -1,6 +1,6 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeErrIO where import PreludeBuiltin(Tuple0, Tuple2, _RealWorld(..), _State(..)) errorIO :: (_State _RealWorld -> ((), _State _RealWorld)) -> a - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 4 _/\_ u0 -> \ (u1 :: _State _RealWorld -> ((), _State _RealWorld)) -> _LETREC_ {(u2 :: _forall_ a$z1 =>a$z1) = u2} in case _#_ errorIO# [] [u1] of { _PRIM_ (u3 :: State# _RealWorld) -> _TYAPP_ u2 { u0 } } _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} diff --git a/ghc/lib/glaExts/PreludeGlaST.hi b/ghc/lib/glaExts/PreludeGlaST.hi index 9a59a6453a5587a2a2d1bb3253f10bbc8a31f567..190557e1c9d5f1963a42f4777d010d2e26abdd22 100644 --- a/ghc/lib/glaExts/PreludeGlaST.hi +++ b/ghc/lib/glaExts/PreludeGlaST.hi @@ -18,6 +18,10 @@ data _ByteArray a = _ByteArray (a, a) ByteArray# data _FILE = _FILE Addr# data _MutableArray a b c = _MutableArray (b, b) (MutableArray# a c) data _MutableByteArray a b = _MutableByteArray (b, b) (MutableByteArray# a) +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendChanPrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} appendFilePrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) @@ -37,7 +41,7 @@ forkST :: (_State a -> (b, _State a)) -> _State a -> (b, _State a) freezeAddrArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ #-} freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) - {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _freezeArray _N_ #-} freezeCharArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} freezeDoubleArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) @@ -83,7 +87,7 @@ mapST :: (a -> _State b -> (c, _State b)) -> [a] -> _State b -> ([c], _State b) newAddrArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) - {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _newArray _N_ #-} newCharArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newDoubleArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) @@ -97,7 +101,7 @@ newVar :: b -> _State a -> (_MutableArray a Int b, _State a) readAddrArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (_Addr, _State b) {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readArray :: Ix a => _MutableArray b a c -> a -> _State b -> (c, _State b) - {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 22212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 11212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readChanPrimIO :: [Char] -> _State _RealWorld -> ([Char], _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} readCharArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (Char, _State b) @@ -128,6 +132,8 @@ seqST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b {-# GHC_PRAGMA _A_ 2 _U_ 112 _N_ _S_ "LS" _N_ _N_ #-} seqStrictlyST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b -> (c, _State b) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: _State u1 -> (u0, _State u1)) (u4 :: _State u1 -> (u2, _State u1)) (u5 :: _State u1) -> case _APP_ u3 [ u5 ] of { _ALG_ _TUP_2 (u6 :: u0) (u7 :: _State u1) -> _APP_ u4 [ u7 ]; _NO_DEFLT_ } _N_ #-} +thawArray :: Ix a => Array a b -> _State c -> (_MutableArray c a b, _State c) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ } #-} thenPrimIO :: (_State _RealWorld -> (a, _State _RealWorld)) -> (a -> _State _RealWorld -> (b, _State _RealWorld)) -> _State _RealWorld -> (b, _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: _State _RealWorld -> (u0, _State _RealWorld)) (u3 :: u0 -> _State _RealWorld -> (u1, _State _RealWorld)) (u4 :: _State _RealWorld) -> case _APP_ u2 [ u4 ] of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: _State _RealWorld) -> _APP_ u3 [ u5, u6 ]; _NO_DEFLT_ } _N_ #-} thenST :: (_State b -> (a, _State b)) -> (a -> _State b -> (c, _State b)) -> _State b -> (c, _State b) diff --git a/ghc/lib/glaExts/PreludeGlaST.lhs b/ghc/lib/glaExts/PreludeGlaST.lhs index 98cfb1b66ef8f9ec0cce1b9db44beb218e4bdb6b..db4255e635602ada3d6b85d7a7ed2019c665d285 100644 --- a/ghc/lib/glaExts/PreludeGlaST.lhs +++ b/ghc/lib/glaExts/PreludeGlaST.lhs @@ -1,5 +1,5 @@ % -% (c) The AQUA Project, Glasgow University, 1994 +% (c) The AQUA Project, Glasgow University, 1994-1996 % \section[PreludeGlaST]{Basic ``state transformer'' monad, mutable arrays and variables} @@ -209,11 +209,12 @@ instance _CCallable (_MutableByteArray s ix) \end{code} \begin{code} -newArray :: Ix ix => (ix,ix) -> elt -> _ST s (_MutableArray s ix elt) +newArray, _newArray + :: Ix ix => (ix,ix) -> elt -> _ST s (_MutableArray s ix elt) newCharArray, newIntArray, newAddrArray, newFloatArray, newDoubleArray - :: Ix ix => (ix,ix) -> _ST s (_MutableByteArray s ix) + :: Ix ix => (ix,ix) -> _ST s (_MutableByteArray s ix) -{-# SPECIALIZE newArray :: IPr -> elt -> _ST s (_MutableArray s Int elt), +{-# SPECIALIZE _newArray :: IPr -> elt -> _ST s (_MutableArray s Int elt), (IPr,IPr) -> elt -> _ST s (_MutableArray s IPr elt) #-} {-# SPECIALIZE newCharArray :: IPr -> _ST s (_MutableByteArray s Int) #-} @@ -222,7 +223,9 @@ newCharArray, newIntArray, newAddrArray, newFloatArray, newDoubleArray {-# SPECIALIZE newFloatArray :: IPr -> _ST s (_MutableByteArray s Int) #-} {-# SPECIALIZE newDoubleArray :: IPr -> _ST s (_MutableByteArray s Int) #-} -newArray ixs@(ix_start, ix_end) init (S# s#) +newArray = _newArray + +_newArray ixs@(ix_start, ix_end) init (S# s#) = let n# = case (if null (range ixs) then 0 else (index ixs ix_end) + 1) of { I# x -> x } @@ -460,19 +463,21 @@ writeDoubleArray (_MutableByteArray ixs barr#) n (D# ele) (S# s#) \end{code} \begin{code} -freezeArray :: Ix ix => _MutableArray s ix elt -> _ST s (Array ix elt) +freezeArray, _freezeArray :: Ix ix => _MutableArray s ix elt -> _ST s (Array ix elt) freezeCharArray :: Ix ix => _MutableByteArray s ix -> _ST s (_ByteArray ix) freezeIntArray :: Ix ix => _MutableByteArray s ix -> _ST s (_ByteArray ix) freezeAddrArray :: Ix ix => _MutableByteArray s ix -> _ST s (_ByteArray ix) freezeFloatArray :: Ix ix => _MutableByteArray s ix -> _ST s (_ByteArray ix) freezeDoubleArray :: Ix ix => _MutableByteArray s ix -> _ST s (_ByteArray ix) -{-# SPECIALISE freezeArray :: _MutableArray s Int elt -> _ST s (Array Int elt), - _MutableArray s IPr elt -> _ST s (Array IPr elt) +{-# SPECIALISE _freezeArray :: _MutableArray s Int elt -> _ST s (Array Int elt), + _MutableArray s IPr elt -> _ST s (Array IPr elt) #-} {-# SPECIALISE freezeCharArray :: _MutableByteArray s Int -> _ST s (_ByteArray Int) #-} -freezeArray (_MutableArray ixs@(ix_start, ix_end) arr#) (S# s#) +freezeArray = _freezeArray + +_freezeArray (_MutableArray ixs@(ix_start, ix_end) arr#) (S# s#) = let n# = case (if null (range ixs) then 0 else (index ixs ix_end) + 1) of { I# x -> x } @@ -689,6 +694,49 @@ unsafeFreezeByteArray (_MutableByteArray ixs arr#) (S# s#) (_ByteArray ixs frozen#, S# s2#) } \end{code} +This takes a immutable array, and copies it into a mutable array, in a +hurry. + +\begin{code} +{-# SPECIALISE thawArray :: Array Int elt -> _ST s (_MutableArray s Int elt), + Array IPr elt -> _ST s (_MutableArray s IPr elt) + #-} + +thawArray (_Array ixs@(ix_start, ix_end) arr#) (S# s#) + = let n# = case (if null (range ixs) + then 0 + else (index ixs ix_end) + 1) of { I# x -> x } + in + case thaw arr# n# s# of { StateAndMutableArray# s2# thawed# -> + (_MutableArray ixs thawed#, S# s2#)} + where + thaw :: Array# ele -- the thing + -> Int# -- size of thing to be thawed + -> State# s -- the Universe and everything + -> StateAndMutableArray# s ele + + thaw arr# n# s# + = case newArray# n# init s# of { StateAndMutableArray# s2# newarr1# -> + copy 0# n# arr# newarr1# s2# } + where + init = error "thawArr: element not copied" + + copy :: Int# -> Int# + -> Array# ele + -> MutableArray# s ele + -> State# s + -> StateAndMutableArray# s ele + + copy cur# end# from# to# s# + | cur# ==# end# + = StateAndMutableArray# s# to# + | True + = case indexArray# from# cur# of { _Lift ele -> + case writeArray# to# cur# ele s# of { s1# -> + copy (cur# +# 1#) end# from# to# s1# + }} +\end{code} + \begin{code} sameMutableArray :: _MutableArray s ix elt -> _MutableArray s ix elt -> Bool sameMutableByteArray :: _MutableByteArray s ix -> _MutableByteArray s ix -> Bool diff --git a/ghc/lib/glaExts/PreludeGlaST_mc.hi b/ghc/lib/glaExts/PreludeGlaST_mc.hi index 0b54e9ad49f25184e439a4f6f767c9ca8962d7fb..a04ff4e629cf34c68fcefea1833e72da0c2064fd 100644 --- a/ghc/lib/glaExts/PreludeGlaST_mc.hi +++ b/ghc/lib/glaExts/PreludeGlaST_mc.hi @@ -18,6 +18,10 @@ data _ByteArray a = _ByteArray (a, a) ByteArray# data _FILE = _FILE Addr# data _MutableArray a b c = _MutableArray (b, b) (MutableArray# a c) data _MutableByteArray a b = _MutableByteArray (b, b) (MutableByteArray# a) +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendChanPrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} appendFilePrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) @@ -37,7 +41,7 @@ forkST :: (_State a -> (b, _State a)) -> _State a -> (b, _State a) freezeAddrArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ #-} freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) - {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _freezeArray _N_ #-} freezeCharArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} freezeDoubleArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) @@ -83,7 +87,7 @@ mapST :: (a -> _State b -> (c, _State b)) -> [a] -> _State b -> ([c], _State b) newAddrArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) - {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _newArray _N_ #-} newCharArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newDoubleArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) @@ -97,7 +101,7 @@ newVar :: b -> _State a -> (_MutableArray a Int b, _State a) readAddrArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (_Addr, _State b) {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readArray :: Ix a => _MutableArray b a c -> a -> _State b -> (c, _State b) - {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 22212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 11212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readChanPrimIO :: [Char] -> _State _RealWorld -> ([Char], _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} readCharArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (Char, _State b) @@ -128,6 +132,8 @@ seqST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b {-# GHC_PRAGMA _A_ 2 _U_ 112 _N_ _S_ "LS" _N_ _N_ #-} seqStrictlyST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b -> (c, _State b) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: _State u1 -> (u0, _State u1)) (u4 :: _State u1 -> (u2, _State u1)) (u5 :: _State u1) -> case _APP_ u3 [ u5 ] of { _ALG_ _TUP_2 (u6 :: u0) (u7 :: _State u1) -> _APP_ u4 [ u7 ]; _NO_DEFLT_ } _N_ #-} +thawArray :: Ix a => Array a b -> _State c -> (_MutableArray c a b, _State c) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ } #-} thenPrimIO :: (_State _RealWorld -> (a, _State _RealWorld)) -> (a -> _State _RealWorld -> (b, _State _RealWorld)) -> _State _RealWorld -> (b, _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: _State _RealWorld -> (u0, _State _RealWorld)) (u3 :: u0 -> _State _RealWorld -> (u1, _State _RealWorld)) (u4 :: _State _RealWorld) -> case _APP_ u2 [ u4 ] of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: _State _RealWorld) -> _APP_ u3 [ u5, u6 ]; _NO_DEFLT_ } _N_ #-} thenST :: (_State b -> (a, _State b)) -> (a -> _State b -> (c, _State b)) -> _State b -> (c, _State b) diff --git a/ghc/lib/glaExts/PreludeGlaST_mp.hi b/ghc/lib/glaExts/PreludeGlaST_mp.hi index 9a59a6453a5587a2a2d1bb3253f10bbc8a31f567..190557e1c9d5f1963a42f4777d010d2e26abdd22 100644 --- a/ghc/lib/glaExts/PreludeGlaST_mp.hi +++ b/ghc/lib/glaExts/PreludeGlaST_mp.hi @@ -18,6 +18,10 @@ data _ByteArray a = _ByteArray (a, a) ByteArray# data _FILE = _FILE Addr# data _MutableArray a b c = _MutableArray (b, b) (MutableArray# a c) data _MutableByteArray a b = _MutableByteArray (b, b) (MutableByteArray# a) +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendChanPrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} appendFilePrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) @@ -37,7 +41,7 @@ forkST :: (_State a -> (b, _State a)) -> _State a -> (b, _State a) freezeAddrArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ #-} freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) - {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _freezeArray _N_ #-} freezeCharArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} freezeDoubleArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) @@ -83,7 +87,7 @@ mapST :: (a -> _State b -> (c, _State b)) -> [a] -> _State b -> ([c], _State b) newAddrArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) - {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _newArray _N_ #-} newCharArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newDoubleArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) @@ -97,7 +101,7 @@ newVar :: b -> _State a -> (_MutableArray a Int b, _State a) readAddrArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (_Addr, _State b) {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readArray :: Ix a => _MutableArray b a c -> a -> _State b -> (c, _State b) - {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 22212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 11212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readChanPrimIO :: [Char] -> _State _RealWorld -> ([Char], _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} readCharArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (Char, _State b) @@ -128,6 +132,8 @@ seqST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b {-# GHC_PRAGMA _A_ 2 _U_ 112 _N_ _S_ "LS" _N_ _N_ #-} seqStrictlyST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b -> (c, _State b) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: _State u1 -> (u0, _State u1)) (u4 :: _State u1 -> (u2, _State u1)) (u5 :: _State u1) -> case _APP_ u3 [ u5 ] of { _ALG_ _TUP_2 (u6 :: u0) (u7 :: _State u1) -> _APP_ u4 [ u7 ]; _NO_DEFLT_ } _N_ #-} +thawArray :: Ix a => Array a b -> _State c -> (_MutableArray c a b, _State c) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ } #-} thenPrimIO :: (_State _RealWorld -> (a, _State _RealWorld)) -> (a -> _State _RealWorld -> (b, _State _RealWorld)) -> _State _RealWorld -> (b, _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: _State _RealWorld -> (u0, _State _RealWorld)) (u3 :: u0 -> _State _RealWorld -> (u1, _State _RealWorld)) (u4 :: _State _RealWorld) -> case _APP_ u2 [ u4 ] of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: _State _RealWorld) -> _APP_ u3 [ u5, u6 ]; _NO_DEFLT_ } _N_ #-} thenST :: (_State b -> (a, _State b)) -> (a -> _State b -> (c, _State b)) -> _State b -> (c, _State b) diff --git a/ghc/lib/glaExts/PreludeGlaST_p.hi b/ghc/lib/glaExts/PreludeGlaST_p.hi index 9a59a6453a5587a2a2d1bb3253f10bbc8a31f567..190557e1c9d5f1963a42f4777d010d2e26abdd22 100644 --- a/ghc/lib/glaExts/PreludeGlaST_p.hi +++ b/ghc/lib/glaExts/PreludeGlaST_p.hi @@ -18,6 +18,10 @@ data _ByteArray a = _ByteArray (a, a) ByteArray# data _FILE = _FILE Addr# data _MutableArray a b c = _MutableArray (b, b) (MutableArray# a c) data _MutableByteArray a b = _MutableByteArray (b, b) (MutableByteArray# a) +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendChanPrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} appendFilePrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) @@ -37,7 +41,7 @@ forkST :: (_State a -> (b, _State a)) -> _State a -> (b, _State a) freezeAddrArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ #-} freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) - {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _freezeArray _N_ #-} freezeCharArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} freezeDoubleArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) @@ -83,7 +87,7 @@ mapST :: (a -> _State b -> (c, _State b)) -> [a] -> _State b -> ([c], _State b) newAddrArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) - {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _newArray _N_ #-} newCharArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newDoubleArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) @@ -97,7 +101,7 @@ newVar :: b -> _State a -> (_MutableArray a Int b, _State a) readAddrArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (_Addr, _State b) {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readArray :: Ix a => _MutableArray b a c -> a -> _State b -> (c, _State b) - {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 22212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 11212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readChanPrimIO :: [Char] -> _State _RealWorld -> ([Char], _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} readCharArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (Char, _State b) @@ -128,6 +132,8 @@ seqST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b {-# GHC_PRAGMA _A_ 2 _U_ 112 _N_ _S_ "LS" _N_ _N_ #-} seqStrictlyST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b -> (c, _State b) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: _State u1 -> (u0, _State u1)) (u4 :: _State u1 -> (u2, _State u1)) (u5 :: _State u1) -> case _APP_ u3 [ u5 ] of { _ALG_ _TUP_2 (u6 :: u0) (u7 :: _State u1) -> _APP_ u4 [ u7 ]; _NO_DEFLT_ } _N_ #-} +thawArray :: Ix a => Array a b -> _State c -> (_MutableArray c a b, _State c) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ } #-} thenPrimIO :: (_State _RealWorld -> (a, _State _RealWorld)) -> (a -> _State _RealWorld -> (b, _State _RealWorld)) -> _State _RealWorld -> (b, _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: _State _RealWorld -> (u0, _State _RealWorld)) (u3 :: u0 -> _State _RealWorld -> (u1, _State _RealWorld)) (u4 :: _State _RealWorld) -> case _APP_ u2 [ u4 ] of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: _State _RealWorld) -> _APP_ u3 [ u5, u6 ]; _NO_DEFLT_ } _N_ #-} thenST :: (_State b -> (a, _State b)) -> (a -> _State b -> (c, _State b)) -> _State b -> (c, _State b) diff --git a/ghc/lib/glaExts/PreludeGlaST_t.hi b/ghc/lib/glaExts/PreludeGlaST_t.hi index 9a59a6453a5587a2a2d1bb3253f10bbc8a31f567..190557e1c9d5f1963a42f4777d010d2e26abdd22 100644 --- a/ghc/lib/glaExts/PreludeGlaST_t.hi +++ b/ghc/lib/glaExts/PreludeGlaST_t.hi @@ -18,6 +18,10 @@ data _ByteArray a = _ByteArray (a, a) ByteArray# data _FILE = _FILE Addr# data _MutableArray a b c = _MutableArray (b, b) (MutableArray# a c) data _MutableByteArray a b = _MutableByteArray (b, b) (MutableByteArray# a) +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendChanPrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} appendFilePrimIO :: [Char] -> [Char] -> _State _RealWorld -> ((), _State _RealWorld) @@ -37,7 +41,7 @@ forkST :: (_State a -> (b, _State a)) -> _State a -> (b, _State a) freezeAddrArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ #-} freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) - {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _freezeArray _N_ #-} freezeCharArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} freezeDoubleArray :: Ix b => _MutableByteArray a b -> _State a -> (_ByteArray b, _State a) @@ -83,7 +87,7 @@ mapST :: (a -> _State b -> (c, _State b)) -> [a] -> _State b -> ([c], _State b) newAddrArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) - {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeGlaST _newArray _N_ #-} newCharArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(LL)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} newDoubleArray :: Ix b => (b, b) -> _State a -> (_MutableByteArray a b, _State a) @@ -97,7 +101,7 @@ newVar :: b -> _State a -> (_MutableArray a Int b, _State a) readAddrArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (_Addr, _State b) {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readArray :: Ix a => _MutableArray b a c -> a -> _State b -> (c, _State b) - {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 22212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 4 _U_ 1121 _N_ _S_ "U(AASA)U(LP)LU(P)" {_A_ 5 _U_ 12222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(U(P)U(P))P)U(P)U(P)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 3 _U_ 111 _N_ _S_ "U(U(SS)P)U(U(P)U(P))U(P)" {_A_ 5 _U_ 11212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} readChanPrimIO :: [Char] -> _State _RealWorld -> ([Char], _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} readCharArray :: Ix a => _MutableByteArray b a -> a -> _State b -> (Char, _State b) @@ -128,6 +132,8 @@ seqST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b {-# GHC_PRAGMA _A_ 2 _U_ 112 _N_ _S_ "LS" _N_ _N_ #-} seqStrictlyST :: (_State b -> (a, _State b)) -> (_State b -> (c, _State b)) -> _State b -> (c, _State b) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 u2 -> \ (u3 :: _State u1 -> (u0, _State u1)) (u4 :: _State u1 -> (u2, _State u1)) (u5 :: _State u1) -> case _APP_ u3 [ u5 ] of { _ALG_ _TUP_2 (u6 :: u0) (u7 :: _State u1) -> _APP_ u4 [ u7 ]; _NO_DEFLT_ } _N_ #-} +thawArray :: Ix a => Array a b -> _State c -> (_MutableArray c a b, _State c) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _N_ _N_ _SPECIALISE_ [ Int, _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ }, [ (Int, Int), _N_, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ } #-} thenPrimIO :: (_State _RealWorld -> (a, _State _RealWorld)) -> (a -> _State _RealWorld -> (b, _State _RealWorld)) -> _State _RealWorld -> (b, _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "SSL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: _State _RealWorld -> (u0, _State _RealWorld)) (u3 :: u0 -> _State _RealWorld -> (u1, _State _RealWorld)) (u4 :: _State _RealWorld) -> case _APP_ u2 [ u4 ] of { _ALG_ _TUP_2 (u5 :: u0) (u6 :: _State _RealWorld) -> _APP_ u3 [ u5, u6 ]; _NO_DEFLT_ } _N_ #-} thenST :: (_State b -> (a, _State b)) -> (a -> _State b -> (c, _State b)) -> _State b -> (c, _State b) diff --git a/ghc/lib/haskell-1.3/LibPosix.hi b/ghc/lib/haskell-1.3/LibPosix.hi index d264cd33888b50cb2af0e011aacda477186f3894..028eacd5a40e6806a2c40cb809f51aad241123e4 100644 --- a/ghc/lib/haskell-1.3/LibPosix.hi +++ b/ghc/lib/haskell-1.3/LibPosix.hi @@ -517,7 +517,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/haskell-1.3/LibPosixProcPrim.hi b/ghc/lib/haskell-1.3/LibPosixProcPrim.hi index 79b3a528abe7ea21135119732e9b00de9be8df34..ff3d5db2c1388dd357e2f3941feb5b58bab68bf3 100644 --- a/ghc/lib/haskell-1.3/LibPosixProcPrim.hi +++ b/ghc/lib/haskell-1.3/LibPosixProcPrim.hi @@ -87,7 +87,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/haskell-1.3/LibPosixProcPrim_mc.hi b/ghc/lib/haskell-1.3/LibPosixProcPrim_mc.hi index 79b3a528abe7ea21135119732e9b00de9be8df34..ff3d5db2c1388dd357e2f3941feb5b58bab68bf3 100644 --- a/ghc/lib/haskell-1.3/LibPosixProcPrim_mc.hi +++ b/ghc/lib/haskell-1.3/LibPosixProcPrim_mc.hi @@ -87,7 +87,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/haskell-1.3/LibPosixProcPrim_mp.hi b/ghc/lib/haskell-1.3/LibPosixProcPrim_mp.hi index ce4e8a09b519900b227595585156f6db36ceb818..7b9e2a8d4709009083e06784eba7d54ef4f8ac96 100644 --- a/ghc/lib/haskell-1.3/LibPosixProcPrim_mp.hi +++ b/ghc/lib/haskell-1.3/LibPosixProcPrim_mp.hi @@ -87,7 +87,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/haskell-1.3/LibPosixProcPrim_p.hi b/ghc/lib/haskell-1.3/LibPosixProcPrim_p.hi index 79b3a528abe7ea21135119732e9b00de9be8df34..ff3d5db2c1388dd357e2f3941feb5b58bab68bf3 100644 --- a/ghc/lib/haskell-1.3/LibPosixProcPrim_p.hi +++ b/ghc/lib/haskell-1.3/LibPosixProcPrim_p.hi @@ -87,7 +87,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/haskell-1.3/LibPosixProcPrim_t.hi b/ghc/lib/haskell-1.3/LibPosixProcPrim_t.hi index 79b3a528abe7ea21135119732e9b00de9be8df34..ff3d5db2c1388dd357e2f3941feb5b58bab68bf3 100644 --- a/ghc/lib/haskell-1.3/LibPosixProcPrim_t.hi +++ b/ghc/lib/haskell-1.3/LibPosixProcPrim_t.hi @@ -87,7 +87,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/haskell-1.3/LibPosix_mc.hi b/ghc/lib/haskell-1.3/LibPosix_mc.hi index d264cd33888b50cb2af0e011aacda477186f3894..028eacd5a40e6806a2c40cb809f51aad241123e4 100644 --- a/ghc/lib/haskell-1.3/LibPosix_mc.hi +++ b/ghc/lib/haskell-1.3/LibPosix_mc.hi @@ -517,7 +517,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/haskell-1.3/LibPosix_mp.hi b/ghc/lib/haskell-1.3/LibPosix_mp.hi index 10a3876e55db30036f1b5f4d7c02323d61eedf9d..0a1a8388d6ea60b639f4c5ccdd2f2100480af2db 100644 --- a/ghc/lib/haskell-1.3/LibPosix_mp.hi +++ b/ghc/lib/haskell-1.3/LibPosix_mp.hi @@ -517,7 +517,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/haskell-1.3/LibPosix_p.hi b/ghc/lib/haskell-1.3/LibPosix_p.hi index d264cd33888b50cb2af0e011aacda477186f3894..028eacd5a40e6806a2c40cb809f51aad241123e4 100644 --- a/ghc/lib/haskell-1.3/LibPosix_p.hi +++ b/ghc/lib/haskell-1.3/LibPosix_p.hi @@ -517,7 +517,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/haskell-1.3/LibPosix_t.hi b/ghc/lib/haskell-1.3/LibPosix_t.hi index d264cd33888b50cb2af0e011aacda477186f3894..028eacd5a40e6806a2c40cb809f51aad241123e4 100644 --- a/ghc/lib/haskell-1.3/LibPosix_t.hi +++ b/ghc/lib/haskell-1.3/LibPosix_t.hi @@ -517,7 +517,7 @@ scheduleAlarm :: Int -> _State _RealWorld -> (Either IOError13 Int, _State _Real segmentationViolation :: Int {-# GHC_PRAGMA _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} setEnvVar :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) - {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "SLL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SLL" _N_ _N_ #-} setEnvironment :: [([Char], [Char])] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} setSignalMask :: _ByteArray () -> _State _RealWorld -> (Either IOError13 (_ByteArray ()), _State _RealWorld) diff --git a/ghc/lib/hbc/Algebra.hi b/ghc/lib/hbc/Algebra.hi index 38788abfbb22976d6eaf4ccbc28bedcb56741f2b..87c939d16e4b0bbca2f79003baa3bb2fb4afb31e 100644 --- a/ghc/lib/hbc/Algebra.hi +++ b/ghc/lib/hbc/Algebra.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Algebra where import PreludeRatio(Ratio(..)) infixl 7 *. @@ -10,7 +10,7 @@ class (Ring a) => CommutativeRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N class (UnityRing a) => DivisionRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{Ring u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where inv :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.DivisionRing.inv\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (/.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 CXXX 7 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> case u1 of { _ALG_ _TUP_2 (u5 :: {{AbelianGroup u0}}) (u6 :: u0 -> u0 -> u0) -> let {(u7 :: u0) = _APP_ u2 [ u4 ]} in _APP_ u6 [ u3, u7 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{UnityRing u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{Ring u0}}) (u8 :: u0) -> case u7 of { _ALG_ _TUP_2 (u9 :: {{AbelianGroup u0}}) (ua :: u0 -> u0 -> u0) -> let {(ub :: u0) = _APP_ u5 [ u3 ]} in _APP_ ua [ u2, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -18,7 +18,7 @@ class (DivisionRing a, CommutativeRing a) => Field a {-# GHC_PRAGMA {-superdicts class (Monoid a) => Group a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{SemiGroup u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where neg :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Group.neg\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (-.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 XXXX 6 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> let {(u5 :: u0) = _APP_ u2 [ u4 ]} in _APP_ u1 [ u3, u5 ] _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{Monoid u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{SemiGroup u0}}) (u8 :: u0) -> let {(u9 :: u0) = _APP_ u5 [ u3 ]} in _APP_ u7 [ u2, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -26,21 +26,21 @@ class (CommutativeRing a, UnityRing a) => IntegralDomain a {-# GHC_PRAGMA {-supe class (SemiGroup a) => Monoid a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where zero :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.Monoid.zero\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => PID a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (AbelianGroup a) => Ring a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LLL)A)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) (u2 :: u0 -> u0) (u3 :: u0 -> u0 -> u0) -> _!_ _TUP_3 [{{Monoid u0}}, (u0 -> u0), (u0 -> u0 -> u0)] [u1, u2, u3] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where (*.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Ring.(*.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class SemiGroup a where (+.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.SemiGroup.(+.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => UFD a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (Ring a) => UnityRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{Ring u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where one :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{UnityRing u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.UnityRing.one\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} data Q = Q (Ratio Integer) instance AbelianGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ #-} @@ -60,103 +60,103 @@ instance CommutativeRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ #-} instance DivisionRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ UnityRing (Q), _CONSTM_ DivisionRing inv (Q), _CONSTM_ DivisionRing (/.) (Q)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance DivisionRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ UnityRing (Bool), _CONSTM_ DivisionRing inv (Bool), _CONSTM_ DivisionRing (/.) (Bool)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Field Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{DivisionRing Q}}, {{CommutativeRing Q}}] [_DFUN_ DivisionRing (Q), _DFUN_ CommutativeRing (Q)] _N_ #-} instance Group Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ Monoid (Bool), _ORIG_ Prelude not, _CONSTM_ Group (-.) (Bool)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> case u1 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Int}}, (Int -> Int), (Int -> Int -> Int)] [_DFUN_ Monoid (Int), _CONSTM_ Num negate (Int), _CONSTM_ Group (-.) (Int)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CC 6 \ (u0 :: Int) (u1 :: Int) -> case u0 of { _ALG_ I# (u2 :: Int#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ negateInt# [] [u3] of { _PRIM_ (u4 :: Int#) -> case _#_ plusInt# [] [u2, u4] of { _PRIM_ (u5 :: Int#) -> _!_ I# [] [u5] } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Integer}}, (Integer -> Integer), (Integer -> Integer -> Integer)] [_DFUN_ Monoid (Integer), _CONSTM_ Num negate (Integer), _CONSTM_ Group (-.) (Integer)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_, - (-.) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance IntegralDomain Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Q}}, {{UnityRing Q}}] [_DFUN_ CommutativeRing (Q), _DFUN_ UnityRing (Q)] _N_ #-} instance IntegralDomain Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Integer}}, {{UnityRing Integer}}] [_DFUN_ CommutativeRing (Integer), _DFUN_ UnityRing (Integer)] _N_ #-} instance Monoid Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Q}}, Q] [_CONSTM_ SemiGroup (+.) (Q), _CONSTM_ Monoid zero (Q)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Bool}}, Bool] [_ORIG_ Prelude (||), _CONSTM_ Monoid zero (Bool)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ } #-} instance Monoid Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Int}}, Int] [_CONSTM_ Num (+) (Int), _CONSTM_ Monoid zero (Int)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ } #-} instance Monoid Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Integer}}, Integer] [_CONSTM_ Num (+) (Integer), _CONSTM_ Monoid zero (Integer)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid [a] {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} instance Ring Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Q}}, (Q -> Q -> Q)] [_DFUN_ AbelianGroup (Q), _CONSTM_ Ring (*.) (Q)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ring Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Bool}}, (Bool -> Bool -> Bool)] [_DFUN_ AbelianGroup (Bool), _ORIG_ Prelude (&&)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ } #-} instance Ring Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Int}}, (Int -> Int -> Int)] [_DFUN_ AbelianGroup (Int), _CONSTM_ Num (*) (Int)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ } #-} instance Ring Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ } #-} instance SemiGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ SemiGroup (+.) (Q) _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance SemiGroup Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ } #-} instance SemiGroup Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ } #-} instance SemiGroup Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ } #-} instance SemiGroup [a] - {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeList (++) _N_ #-} + {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 (++) _N_ #-} instance UnityRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Q}}, Q] [_DFUN_ Ring (Q), _CONSTM_ UnityRing one (Q)] _N_ - one = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance UnityRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Bool}}, Bool] [_DFUN_ Ring (Bool), _CONSTM_ UnityRing one (Bool)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ } #-} instance UnityRing Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Int}}, Int] [_DFUN_ Ring (Int), _CONSTM_ UnityRing one (Int)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ } #-} instance UnityRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Integer}}, Integer] [_DFUN_ Ring (Integer), _CONSTM_ UnityRing one (Integer)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Eq Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Q -> Q -> Bool), (Q -> Q -> Bool)] [_CONSTM_ Eq (==) (Q), _CONSTM_ Eq (/=) (Q)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Q}}, (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Q), (Q -> Q -> Q), (Q -> Q -> _CMP_TAG)] [_DFUN_ Eq (Q), _CONSTM_ Ord (<) (Q), _CONSTM_ Ord (<=) (Q), _CONSTM_ Ord (>=) (Q), _CONSTM_ Ord (>) (Q), _CONSTM_ Ord max (Q), _CONSTM_ Ord min (Q), _CONSTM_ Ord _tagCmp (Q)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Q, [Char])]), (Int -> Q -> [Char] -> [Char]), ([Char] -> [([Q], [Char])]), ([Q] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Q), _CONSTM_ Text showsPrec (Q), _CONSTM_ Text readList (Q), _CONSTM_ Text showList (Q)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Q, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Algebra_mc.hi b/ghc/lib/hbc/Algebra_mc.hi index 38788abfbb22976d6eaf4ccbc28bedcb56741f2b..87c939d16e4b0bbca2f79003baa3bb2fb4afb31e 100644 --- a/ghc/lib/hbc/Algebra_mc.hi +++ b/ghc/lib/hbc/Algebra_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Algebra where import PreludeRatio(Ratio(..)) infixl 7 *. @@ -10,7 +10,7 @@ class (Ring a) => CommutativeRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N class (UnityRing a) => DivisionRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{Ring u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where inv :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.DivisionRing.inv\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (/.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 CXXX 7 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> case u1 of { _ALG_ _TUP_2 (u5 :: {{AbelianGroup u0}}) (u6 :: u0 -> u0 -> u0) -> let {(u7 :: u0) = _APP_ u2 [ u4 ]} in _APP_ u6 [ u3, u7 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{UnityRing u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{Ring u0}}) (u8 :: u0) -> case u7 of { _ALG_ _TUP_2 (u9 :: {{AbelianGroup u0}}) (ua :: u0 -> u0 -> u0) -> let {(ub :: u0) = _APP_ u5 [ u3 ]} in _APP_ ua [ u2, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -18,7 +18,7 @@ class (DivisionRing a, CommutativeRing a) => Field a {-# GHC_PRAGMA {-superdicts class (Monoid a) => Group a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{SemiGroup u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where neg :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Group.neg\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (-.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 XXXX 6 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> let {(u5 :: u0) = _APP_ u2 [ u4 ]} in _APP_ u1 [ u3, u5 ] _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{Monoid u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{SemiGroup u0}}) (u8 :: u0) -> let {(u9 :: u0) = _APP_ u5 [ u3 ]} in _APP_ u7 [ u2, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -26,21 +26,21 @@ class (CommutativeRing a, UnityRing a) => IntegralDomain a {-# GHC_PRAGMA {-supe class (SemiGroup a) => Monoid a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where zero :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.Monoid.zero\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => PID a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (AbelianGroup a) => Ring a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LLL)A)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) (u2 :: u0 -> u0) (u3 :: u0 -> u0 -> u0) -> _!_ _TUP_3 [{{Monoid u0}}, (u0 -> u0), (u0 -> u0 -> u0)] [u1, u2, u3] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where (*.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Ring.(*.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class SemiGroup a where (+.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.SemiGroup.(+.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => UFD a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (Ring a) => UnityRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{Ring u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where one :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{UnityRing u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.UnityRing.one\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} data Q = Q (Ratio Integer) instance AbelianGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ #-} @@ -60,103 +60,103 @@ instance CommutativeRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ #-} instance DivisionRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ UnityRing (Q), _CONSTM_ DivisionRing inv (Q), _CONSTM_ DivisionRing (/.) (Q)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance DivisionRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ UnityRing (Bool), _CONSTM_ DivisionRing inv (Bool), _CONSTM_ DivisionRing (/.) (Bool)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Field Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{DivisionRing Q}}, {{CommutativeRing Q}}] [_DFUN_ DivisionRing (Q), _DFUN_ CommutativeRing (Q)] _N_ #-} instance Group Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ Monoid (Bool), _ORIG_ Prelude not, _CONSTM_ Group (-.) (Bool)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> case u1 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Int}}, (Int -> Int), (Int -> Int -> Int)] [_DFUN_ Monoid (Int), _CONSTM_ Num negate (Int), _CONSTM_ Group (-.) (Int)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CC 6 \ (u0 :: Int) (u1 :: Int) -> case u0 of { _ALG_ I# (u2 :: Int#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ negateInt# [] [u3] of { _PRIM_ (u4 :: Int#) -> case _#_ plusInt# [] [u2, u4] of { _PRIM_ (u5 :: Int#) -> _!_ I# [] [u5] } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Integer}}, (Integer -> Integer), (Integer -> Integer -> Integer)] [_DFUN_ Monoid (Integer), _CONSTM_ Num negate (Integer), _CONSTM_ Group (-.) (Integer)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_, - (-.) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance IntegralDomain Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Q}}, {{UnityRing Q}}] [_DFUN_ CommutativeRing (Q), _DFUN_ UnityRing (Q)] _N_ #-} instance IntegralDomain Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Integer}}, {{UnityRing Integer}}] [_DFUN_ CommutativeRing (Integer), _DFUN_ UnityRing (Integer)] _N_ #-} instance Monoid Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Q}}, Q] [_CONSTM_ SemiGroup (+.) (Q), _CONSTM_ Monoid zero (Q)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Bool}}, Bool] [_ORIG_ Prelude (||), _CONSTM_ Monoid zero (Bool)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ } #-} instance Monoid Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Int}}, Int] [_CONSTM_ Num (+) (Int), _CONSTM_ Monoid zero (Int)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ } #-} instance Monoid Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Integer}}, Integer] [_CONSTM_ Num (+) (Integer), _CONSTM_ Monoid zero (Integer)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid [a] {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} instance Ring Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Q}}, (Q -> Q -> Q)] [_DFUN_ AbelianGroup (Q), _CONSTM_ Ring (*.) (Q)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ring Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Bool}}, (Bool -> Bool -> Bool)] [_DFUN_ AbelianGroup (Bool), _ORIG_ Prelude (&&)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ } #-} instance Ring Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Int}}, (Int -> Int -> Int)] [_DFUN_ AbelianGroup (Int), _CONSTM_ Num (*) (Int)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ } #-} instance Ring Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ } #-} instance SemiGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ SemiGroup (+.) (Q) _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance SemiGroup Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ } #-} instance SemiGroup Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ } #-} instance SemiGroup Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ } #-} instance SemiGroup [a] - {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeList (++) _N_ #-} + {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 (++) _N_ #-} instance UnityRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Q}}, Q] [_DFUN_ Ring (Q), _CONSTM_ UnityRing one (Q)] _N_ - one = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance UnityRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Bool}}, Bool] [_DFUN_ Ring (Bool), _CONSTM_ UnityRing one (Bool)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ } #-} instance UnityRing Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Int}}, Int] [_DFUN_ Ring (Int), _CONSTM_ UnityRing one (Int)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ } #-} instance UnityRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Integer}}, Integer] [_DFUN_ Ring (Integer), _CONSTM_ UnityRing one (Integer)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Eq Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Q -> Q -> Bool), (Q -> Q -> Bool)] [_CONSTM_ Eq (==) (Q), _CONSTM_ Eq (/=) (Q)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Q}}, (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Q), (Q -> Q -> Q), (Q -> Q -> _CMP_TAG)] [_DFUN_ Eq (Q), _CONSTM_ Ord (<) (Q), _CONSTM_ Ord (<=) (Q), _CONSTM_ Ord (>=) (Q), _CONSTM_ Ord (>) (Q), _CONSTM_ Ord max (Q), _CONSTM_ Ord min (Q), _CONSTM_ Ord _tagCmp (Q)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Q, [Char])]), (Int -> Q -> [Char] -> [Char]), ([Char] -> [([Q], [Char])]), ([Q] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Q), _CONSTM_ Text showsPrec (Q), _CONSTM_ Text readList (Q), _CONSTM_ Text showList (Q)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Q, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Algebra_mp.hi b/ghc/lib/hbc/Algebra_mp.hi index 38788abfbb22976d6eaf4ccbc28bedcb56741f2b..87c939d16e4b0bbca2f79003baa3bb2fb4afb31e 100644 --- a/ghc/lib/hbc/Algebra_mp.hi +++ b/ghc/lib/hbc/Algebra_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Algebra where import PreludeRatio(Ratio(..)) infixl 7 *. @@ -10,7 +10,7 @@ class (Ring a) => CommutativeRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N class (UnityRing a) => DivisionRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{Ring u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where inv :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.DivisionRing.inv\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (/.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 CXXX 7 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> case u1 of { _ALG_ _TUP_2 (u5 :: {{AbelianGroup u0}}) (u6 :: u0 -> u0 -> u0) -> let {(u7 :: u0) = _APP_ u2 [ u4 ]} in _APP_ u6 [ u3, u7 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{UnityRing u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{Ring u0}}) (u8 :: u0) -> case u7 of { _ALG_ _TUP_2 (u9 :: {{AbelianGroup u0}}) (ua :: u0 -> u0 -> u0) -> let {(ub :: u0) = _APP_ u5 [ u3 ]} in _APP_ ua [ u2, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -18,7 +18,7 @@ class (DivisionRing a, CommutativeRing a) => Field a {-# GHC_PRAGMA {-superdicts class (Monoid a) => Group a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{SemiGroup u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where neg :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Group.neg\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (-.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 XXXX 6 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> let {(u5 :: u0) = _APP_ u2 [ u4 ]} in _APP_ u1 [ u3, u5 ] _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{Monoid u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{SemiGroup u0}}) (u8 :: u0) -> let {(u9 :: u0) = _APP_ u5 [ u3 ]} in _APP_ u7 [ u2, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -26,21 +26,21 @@ class (CommutativeRing a, UnityRing a) => IntegralDomain a {-# GHC_PRAGMA {-supe class (SemiGroup a) => Monoid a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where zero :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.Monoid.zero\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => PID a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (AbelianGroup a) => Ring a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LLL)A)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) (u2 :: u0 -> u0) (u3 :: u0 -> u0 -> u0) -> _!_ _TUP_3 [{{Monoid u0}}, (u0 -> u0), (u0 -> u0 -> u0)] [u1, u2, u3] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where (*.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Ring.(*.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class SemiGroup a where (+.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.SemiGroup.(+.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => UFD a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (Ring a) => UnityRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{Ring u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where one :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{UnityRing u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.UnityRing.one\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} data Q = Q (Ratio Integer) instance AbelianGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ #-} @@ -60,103 +60,103 @@ instance CommutativeRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ #-} instance DivisionRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ UnityRing (Q), _CONSTM_ DivisionRing inv (Q), _CONSTM_ DivisionRing (/.) (Q)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance DivisionRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ UnityRing (Bool), _CONSTM_ DivisionRing inv (Bool), _CONSTM_ DivisionRing (/.) (Bool)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Field Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{DivisionRing Q}}, {{CommutativeRing Q}}] [_DFUN_ DivisionRing (Q), _DFUN_ CommutativeRing (Q)] _N_ #-} instance Group Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ Monoid (Bool), _ORIG_ Prelude not, _CONSTM_ Group (-.) (Bool)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> case u1 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Int}}, (Int -> Int), (Int -> Int -> Int)] [_DFUN_ Monoid (Int), _CONSTM_ Num negate (Int), _CONSTM_ Group (-.) (Int)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CC 6 \ (u0 :: Int) (u1 :: Int) -> case u0 of { _ALG_ I# (u2 :: Int#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ negateInt# [] [u3] of { _PRIM_ (u4 :: Int#) -> case _#_ plusInt# [] [u2, u4] of { _PRIM_ (u5 :: Int#) -> _!_ I# [] [u5] } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Integer}}, (Integer -> Integer), (Integer -> Integer -> Integer)] [_DFUN_ Monoid (Integer), _CONSTM_ Num negate (Integer), _CONSTM_ Group (-.) (Integer)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_, - (-.) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance IntegralDomain Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Q}}, {{UnityRing Q}}] [_DFUN_ CommutativeRing (Q), _DFUN_ UnityRing (Q)] _N_ #-} instance IntegralDomain Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Integer}}, {{UnityRing Integer}}] [_DFUN_ CommutativeRing (Integer), _DFUN_ UnityRing (Integer)] _N_ #-} instance Monoid Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Q}}, Q] [_CONSTM_ SemiGroup (+.) (Q), _CONSTM_ Monoid zero (Q)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Bool}}, Bool] [_ORIG_ Prelude (||), _CONSTM_ Monoid zero (Bool)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ } #-} instance Monoid Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Int}}, Int] [_CONSTM_ Num (+) (Int), _CONSTM_ Monoid zero (Int)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ } #-} instance Monoid Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Integer}}, Integer] [_CONSTM_ Num (+) (Integer), _CONSTM_ Monoid zero (Integer)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid [a] {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} instance Ring Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Q}}, (Q -> Q -> Q)] [_DFUN_ AbelianGroup (Q), _CONSTM_ Ring (*.) (Q)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ring Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Bool}}, (Bool -> Bool -> Bool)] [_DFUN_ AbelianGroup (Bool), _ORIG_ Prelude (&&)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ } #-} instance Ring Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Int}}, (Int -> Int -> Int)] [_DFUN_ AbelianGroup (Int), _CONSTM_ Num (*) (Int)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ } #-} instance Ring Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ } #-} instance SemiGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ SemiGroup (+.) (Q) _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance SemiGroup Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ } #-} instance SemiGroup Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ } #-} instance SemiGroup Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ } #-} instance SemiGroup [a] - {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeList (++) _N_ #-} + {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 (++) _N_ #-} instance UnityRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Q}}, Q] [_DFUN_ Ring (Q), _CONSTM_ UnityRing one (Q)] _N_ - one = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance UnityRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Bool}}, Bool] [_DFUN_ Ring (Bool), _CONSTM_ UnityRing one (Bool)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ } #-} instance UnityRing Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Int}}, Int] [_DFUN_ Ring (Int), _CONSTM_ UnityRing one (Int)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ } #-} instance UnityRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Integer}}, Integer] [_DFUN_ Ring (Integer), _CONSTM_ UnityRing one (Integer)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Eq Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Q -> Q -> Bool), (Q -> Q -> Bool)] [_CONSTM_ Eq (==) (Q), _CONSTM_ Eq (/=) (Q)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Q}}, (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Q), (Q -> Q -> Q), (Q -> Q -> _CMP_TAG)] [_DFUN_ Eq (Q), _CONSTM_ Ord (<) (Q), _CONSTM_ Ord (<=) (Q), _CONSTM_ Ord (>=) (Q), _CONSTM_ Ord (>) (Q), _CONSTM_ Ord max (Q), _CONSTM_ Ord min (Q), _CONSTM_ Ord _tagCmp (Q)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Q, [Char])]), (Int -> Q -> [Char] -> [Char]), ([Char] -> [([Q], [Char])]), ([Q] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Q), _CONSTM_ Text showsPrec (Q), _CONSTM_ Text readList (Q), _CONSTM_ Text showList (Q)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Q, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Algebra_p.hi b/ghc/lib/hbc/Algebra_p.hi index e8097b566212791f98c42a0c843c50109e92aa99..230f8e2a1666bc6922d32242561082bd4b7063f5 100644 --- a/ghc/lib/hbc/Algebra_p.hi +++ b/ghc/lib/hbc/Algebra_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Algebra where import PreludeRatio(Ratio(..)) infixl 7 *. @@ -10,7 +10,7 @@ class (Ring a) => CommutativeRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N class (UnityRing a) => DivisionRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{Ring u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where inv :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.DivisionRing.inv\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (/.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 CXXX 7 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> case u1 of { _ALG_ _TUP_2 (u5 :: {{AbelianGroup u0}}) (u6 :: u0 -> u0 -> u0) -> let {(u7 :: u0) = _APP_ u2 [ u4 ]} in _APP_ u6 [ u3, u7 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{UnityRing u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{Ring u0}}) (u8 :: u0) -> case u7 of { _ALG_ _TUP_2 (u9 :: {{AbelianGroup u0}}) (ua :: u0 -> u0 -> u0) -> let {(ub :: u0) = _APP_ u5 [ u3 ]} in _APP_ ua [ u2, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -18,7 +18,7 @@ class (DivisionRing a, CommutativeRing a) => Field a {-# GHC_PRAGMA {-superdicts class (Monoid a) => Group a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{SemiGroup u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where neg :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Group.neg\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (-.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 XXXX 6 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> let {(u5 :: u0) = _APP_ u2 [ u4 ]} in _scc_ { _ALL_DICTS_CC_ "Algebra" "Prelude" _N_ } _APP_ u1 [ u3, u5 ] _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{Monoid u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{SemiGroup u0}}) (u8 :: u0) -> let {(u9 :: u0) = _APP_ u5 [ u3 ]} in _scc_ { _ALL_DICTS_CC_ "Algebra" "Prelude" _N_ } _APP_ u7 [ u2, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -26,21 +26,21 @@ class (CommutativeRing a, UnityRing a) => IntegralDomain a {-# GHC_PRAGMA {-supe class (SemiGroup a) => Monoid a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where zero :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.Monoid.zero\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => PID a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (AbelianGroup a) => Ring a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LLL)A)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) (u2 :: u0 -> u0) (u3 :: u0 -> u0 -> u0) -> _!_ _TUP_3 [{{Monoid u0}}, (u0 -> u0), (u0 -> u0 -> u0)] [u1, u2, u3] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where (*.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Ring.(*.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class SemiGroup a where (+.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.SemiGroup.(+.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => UFD a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (Ring a) => UnityRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{Ring u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where one :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{UnityRing u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.UnityRing.one\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} data Q = Q (Ratio Integer) instance AbelianGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ #-} @@ -60,103 +60,103 @@ instance CommutativeRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ #-} instance DivisionRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ UnityRing (Q), _CONSTM_ DivisionRing inv (Q), _CONSTM_ DivisionRing (/.) (Q)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance DivisionRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ UnityRing (Bool), _CONSTM_ DivisionRing inv (Bool), _CONSTM_ DivisionRing (/.) (Bool)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Field Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{DivisionRing Q}}, {{CommutativeRing Q}}] [_DFUN_ DivisionRing (Q), _DFUN_ CommutativeRing (Q)] _N_ #-} instance Group Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ Monoid (Bool), _ORIG_ Prelude not, _CONSTM_ Group (-.) (Bool)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CC 9 \ (u0 :: Bool) (u1 :: Bool) -> let {(u2 :: Bool) = case u1 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }} in _scc_ { _ALL_DICTS_CC_ "Algebra" "Prelude" _N_ } case u0 of { _ALG_ True -> _!_ True [] []; False -> u2; _NO_DEFLT_ } _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Int}}, (Int -> Int), (Int -> Int -> Int)] [_DFUN_ Monoid (Int), _CONSTM_ Num negate (Int), _CONSTM_ Group (-.) (Int)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Integer}}, (Integer -> Integer), (Integer -> Integer -> Integer)] [_DFUN_ Monoid (Integer), _CONSTM_ Num negate (Integer), _CONSTM_ Group (-.) (Integer)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_, - (-.) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance IntegralDomain Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Q}}, {{UnityRing Q}}] [_DFUN_ CommutativeRing (Q), _DFUN_ UnityRing (Q)] _N_ #-} instance IntegralDomain Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Integer}}, {{UnityRing Integer}}] [_DFUN_ CommutativeRing (Integer), _DFUN_ UnityRing (Integer)] _N_ #-} instance Monoid Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Q}}, Q] [_CONSTM_ SemiGroup (+.) (Q), _CONSTM_ Monoid zero (Q)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Bool}}, Bool] [_ORIG_ Prelude (||), _CONSTM_ Monoid zero (Bool)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ } #-} instance Monoid Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Int}}, Int] [_CONSTM_ Num (+) (Int), _CONSTM_ Monoid zero (Int)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ } #-} instance Monoid Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Integer}}, Integer] [_CONSTM_ Num (+) (Integer), _CONSTM_ Monoid zero (Integer)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid [a] {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} instance Ring Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Q}}, (Q -> Q -> Q)] [_DFUN_ AbelianGroup (Q), _CONSTM_ Ring (*.) (Q)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ring Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Bool}}, (Bool -> Bool -> Bool)] [_DFUN_ AbelianGroup (Bool), _ORIG_ Prelude (&&)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ } #-} instance Ring Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Int}}, (Int -> Int -> Int)] [_DFUN_ AbelianGroup (Int), _CONSTM_ Num (*) (Int)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ } #-} instance Ring Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ } #-} instance SemiGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ SemiGroup (+.) (Q) _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance SemiGroup Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ } #-} instance SemiGroup Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ } #-} instance SemiGroup Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ } #-} instance SemiGroup [a] - {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeList (++) _N_ #-} + {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 (++) _N_ #-} instance UnityRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Q}}, Q] [_DFUN_ Ring (Q), _CONSTM_ UnityRing one (Q)] _N_ - one = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance UnityRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Bool}}, Bool] [_DFUN_ Ring (Bool), _CONSTM_ UnityRing one (Bool)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ } #-} instance UnityRing Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Int}}, Int] [_DFUN_ Ring (Int), _CONSTM_ UnityRing one (Int)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ } #-} instance UnityRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Integer}}, Integer] [_DFUN_ Ring (Integer), _CONSTM_ UnityRing one (Integer)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Eq Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Q -> Q -> Bool), (Q -> Q -> Bool)] [_CONSTM_ Eq (==) (Q), _CONSTM_ Eq (/=) (Q)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Q}}, (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Q), (Q -> Q -> Q), (Q -> Q -> _CMP_TAG)] [_DFUN_ Eq (Q), _CONSTM_ Ord (<) (Q), _CONSTM_ Ord (<=) (Q), _CONSTM_ Ord (>=) (Q), _CONSTM_ Ord (>) (Q), _CONSTM_ Ord max (Q), _CONSTM_ Ord min (Q), _CONSTM_ Ord _tagCmp (Q)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Q, [Char])]), (Int -> Q -> [Char] -> [Char]), ([Char] -> [([Q], [Char])]), ([Q] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Q), _CONSTM_ Text showsPrec (Q), _CONSTM_ Text readList (Q), _CONSTM_ Text showList (Q)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Q, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Algebra_t.hi b/ghc/lib/hbc/Algebra_t.hi index 38788abfbb22976d6eaf4ccbc28bedcb56741f2b..87c939d16e4b0bbca2f79003baa3bb2fb4afb31e 100644 --- a/ghc/lib/hbc/Algebra_t.hi +++ b/ghc/lib/hbc/Algebra_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Algebra where import PreludeRatio(Ratio(..)) infixl 7 *. @@ -10,7 +10,7 @@ class (Ring a) => CommutativeRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N class (UnityRing a) => DivisionRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{Ring u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where inv :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.DivisionRing.inv\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (/.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{UnityRing u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{UnityRing u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 CXXX 7 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> case u1 of { _ALG_ _TUP_2 (u5 :: {{AbelianGroup u0}}) (u6 :: u0 -> u0 -> u0) -> let {(u7 :: u0) = _APP_ u2 [ u4 ]} in _APP_ u6 [ u3, u7 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{DivisionRing u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{UnityRing u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{Ring u0}}) (u8 :: u0) -> case u7 of { _ALG_ _TUP_2 (u9 :: {{AbelianGroup u0}}) (ua :: u0 -> u0 -> u0) -> let {(ub :: u0) = _APP_ u5 [ u3 ]} in _APP_ ua [ u2, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -18,7 +18,7 @@ class (DivisionRing a, CommutativeRing a) => Field a {-# GHC_PRAGMA {-superdicts class (Monoid a) => Group a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)AA)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) -> _!_ _TUP_2 [{{SemiGroup u0}}, u0] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where neg :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(ASA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Group.neg\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} (-.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Monoid u0}}, u0 -> u0, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_3 (u2 :: {{Monoid u0}}) (u3 :: u0 -> u0) (u4 :: u0 -> u0 -> u0) -> u4; _NO_DEFLT_ } _N_ {-defm-} _A_ 3 _U_ 122 _N_ _S_ "U(U(SA)LA)LL" {_A_ 4 _U_ 1122 _N_ _N_ _F_ _IF_ARGS_ 1 4 XXXX 6 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0 -> u0) (u3 :: u0) (u4 :: u0) -> let {(u5 :: u0) = _APP_ u2 [ u4 ]} in _APP_ u1 [ u3, u5 ] _N_} _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Group u0}}) (u2 :: u0) (u3 :: u0) -> case u1 of { _ALG_ _TUP_3 (u4 :: {{Monoid u0}}) (u5 :: u0 -> u0) (u6 :: u0 -> u0 -> u0) -> case u4 of { _ALG_ _TUP_2 (u7 :: {{SemiGroup u0}}) (u8 :: u0) -> let {(u9 :: u0) = _APP_ u5 [ u3 ]} in _APP_ u7 [ u2, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} @@ -26,21 +26,21 @@ class (CommutativeRing a, UnityRing a) => IntegralDomain a {-# GHC_PRAGMA {-supe class (SemiGroup a) => Monoid a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where zero :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{SemiGroup u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{SemiGroup u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.Monoid.zero\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => PID a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (AbelianGroup a) => Ring a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(U(LLL)A)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Monoid u0}}) (u2 :: u0 -> u0) (u3 :: u0 -> u0 -> u0) -> _!_ _TUP_3 [{{Monoid u0}}, (u0 -> u0), (u0 -> u0 -> u0)] [u1, u2, u3] _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u2; _NO_DEFLT_ } _N_ #-} where (*.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AS)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{AbelianGroup u0}}, u0 -> u0 -> u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{AbelianGroup u0}}) (u3 :: u0 -> u0 -> u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Ring u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.Ring.(*.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class SemiGroup a where (+.) :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{SemiGroup u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DAlgebra.SemiGroup.(+.)\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} class (IntegralDomain a) => UFD a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{CommutativeRing u0}}) (u2 :: {{UnityRing u0}}) -> _!_ _TUP_2 [{{CommutativeRing u0}}, {{UnityRing u0}}] [u1, u2] _N_} _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{IntegralDomain u0}}) -> u1 _N_ #-} class (Ring a) => UnityRing a {-# GHC_PRAGMA {-superdicts-} _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: {{Ring u0}}) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} where one :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AS)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: ({{Ring u0}}, u0)) -> case u1 of { _ALG_ _TUP_2 (u2 :: {{Ring u0}}) (u3 :: u0) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{UnityRing u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DAlgebra.UnityRing.one\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} data Q = Q (Ratio Integer) instance AbelianGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ #-} @@ -60,103 +60,103 @@ instance CommutativeRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ #-} instance DivisionRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ UnityRing (Q), _CONSTM_ DivisionRing inv (Q), _CONSTM_ DivisionRing (/.) (Q)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance DivisionRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{UnityRing Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ UnityRing (Bool), _CONSTM_ DivisionRing inv (Bool), _CONSTM_ DivisionRing (/.) (Bool)] _N_ - inv = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_, - (/.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + inv = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Bool) -> u0 _N_ }, + (/.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Field Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{DivisionRing Q}}, {{CommutativeRing Q}}] [_DFUN_ DivisionRing (Q), _DFUN_ CommutativeRing (Q)] _N_ #-} instance Group Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Q}}, (Q -> Q), (Q -> Q -> Q)] [_DFUN_ Monoid (Q), _CONSTM_ Group neg (Q), _CONSTM_ Group (-.) (Q)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "U(L)" {_A_ 1 _U_ 1 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Bool}}, (Bool -> Bool), (Bool -> Bool -> Bool)] [_DFUN_ Monoid (Bool), _ORIG_ Prelude not, _CONSTM_ Group (-.) (Bool)] _N_ - neg = _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> case u1 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + neg = { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Bool) -> case u0 of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Int}}, (Int -> Int), (Int -> Int -> Int)] [_DFUN_ Monoid (Int), _CONSTM_ Num negate (Int), _CONSTM_ Group (-.) (Int)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_, - (-.) = _A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 0 2 CC 6 \ (u0 :: Int) (u1 :: Int) -> case u0 of { _ALG_ I# (u2 :: Int#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ negateInt# [] [u3] of { _PRIM_ (u4 :: Int#) -> case _#_ plusInt# [] [u2, u4] of { _PRIM_ (u5 :: Int#) -> _!_ I# [] [u5] } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Int) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Group Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Monoid Integer}}, (Integer -> Integer), (Integer -> Integer -> Integer)] [_DFUN_ Monoid (Integer), _CONSTM_ Num negate (Integer), _CONSTM_ Group (-.) (Integer)] _N_ - neg = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_, - (-.) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + neg = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num negate (Integer) _N_ }, + (-.) = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance IntegralDomain Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Q}}, {{UnityRing Q}}] [_DFUN_ CommutativeRing (Q), _DFUN_ UnityRing (Q)] _N_ #-} instance IntegralDomain Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{CommutativeRing Integer}}, {{UnityRing Integer}}] [_DFUN_ CommutativeRing (Integer), _DFUN_ UnityRing (Integer)] _N_ #-} instance Monoid Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Q}}, Q] [_CONSTM_ SemiGroup (+.) (Q), _CONSTM_ Monoid zero (Q)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Bool}}, Bool] [_ORIG_ Prelude (||), _CONSTM_ Monoid zero (Bool)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ False [] [] _N_ } #-} instance Monoid Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Int}}, Int] [_CONSTM_ Num (+) (Int), _CONSTM_ Monoid zero (Int)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_ } #-} instance Monoid Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{SemiGroup Integer}}, Integer] [_CONSTM_ Num (+) (Integer), _CONSTM_ Monoid zero (Integer)] _N_ - zero = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [0#] _N_ #-} + zero = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Monoid [a] {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} instance Ring Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Q}}, (Q -> Q -> Q)] [_DFUN_ AbelianGroup (Q), _CONSTM_ Ring (*.) (Q)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ring Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Bool}}, (Bool -> Bool -> Bool)] [_DFUN_ AbelianGroup (Bool), _ORIG_ Prelude (&&)] _N_ - (*.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ #-} + (*.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> u1; False -> _!_ False [] []; _NO_DEFLT_ } _N_ } #-} instance Ring Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Int}}, (Int -> Int -> Int)] [_DFUN_ AbelianGroup (Int), _CONSTM_ Num (*) (Int)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Int) _N_ } #-} instance Ring Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{AbelianGroup Integer}}, (Integer -> Integer -> Integer)] [_DFUN_ AbelianGroup (Integer), _CONSTM_ Num (*) (Integer)] _N_ - (*.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ #-} + (*.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (*) (Integer) _N_ } #-} instance SemiGroup Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ SemiGroup (+.) (Q) _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "U(L)U(L)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance SemiGroup Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ - (+.) = _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} + (+.) = { _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ } #-} instance SemiGroup Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Int) _N_ } #-} instance SemiGroup Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ - (+.) = _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ #-} + (+.) = { _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Num (+) (Integer) _N_ } #-} instance SemiGroup [a] - {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _ORIG_ PreludeList (++) _N_ #-} + {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 2 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 (++) _N_ #-} instance UnityRing Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Q}}, Q] [_DFUN_ Ring (Q), _CONSTM_ UnityRing one (Q)] _N_ - one = _A_ 0 _N_ _N_ _N_ _N_ _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance UnityRing Bool {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Bool}}, Bool] [_DFUN_ Ring (Bool), _CONSTM_ UnityRing one (Bool)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _!_ True [] [] _N_ } #-} instance UnityRing Int {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Int}}, Int] [_DFUN_ Ring (Int), _CONSTM_ UnityRing one (Int)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [1#] _N_ } #-} instance UnityRing Integer {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [{{Ring Integer}}, Integer] [_DFUN_ Ring (Integer), _CONSTM_ UnityRing one (Integer)] _N_ - one = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [1#] _N_ #-} + one = { _A_ 0 _N_ _N_ _N_ _N_ _N_ } #-} instance Eq Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Q -> Q -> Bool), (Q -> Q -> Bool)] [_CONSTM_ Eq (==) (Q), _CONSTM_ Eq (/=) (Q)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)L))U(U(U(PPP)L))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Q}}, (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Bool), (Q -> Q -> Q), (Q -> Q -> Q), (Q -> Q -> _CMP_TAG)] [_DFUN_ Eq (Q), _CONSTM_ Ord (<) (Q), _CONSTM_ Ord (<=) (Q), _CONSTM_ Ord (>=) (Q), _CONSTM_ Ord (>) (Q), _CONSTM_ Ord max (Q), _CONSTM_ Ord min (Q), _CONSTM_ Ord _tagCmp (Q)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(PPP)U(PPP)))U(U(U(PPP)U(PPP)))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Q {-# GHC_PRAGMA _M_ Algebra {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Q, [Char])]), (Int -> Q -> [Char] -> [Char]), ([Char] -> [([Q], [Char])]), ([Q] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Q), _CONSTM_ Text showsPrec (Q), _CONSTM_ Text readList (Q), _CONSTM_ Text showList (Q)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Q, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LU(U(LL))" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Hash_mc.hi b/ghc/lib/hbc/Hash_mc.hi index 25edd2ce8bbb6449c1a0d7fc9dffb9f85244e2f5..b576e4cc2e50f3faf8046d4e8d9c9fd3c900276b 100644 --- a/ghc/lib/hbc/Hash_mc.hi +++ b/ghc/lib/hbc/Hash_mc.hi @@ -39,11 +39,11 @@ instance Hashable Char instance (RealFloat a, Hashable a) => Hashable (Complex a) {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 3 _U_ 22 _N_ _S_ "LSS" _N_ _N_ #-} instance Hashable Double - {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ - hash = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (Double) _N_ + hash = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 4 \ (u0 :: Double#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Double) [ (Int) ] [ u0 ] of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Double) -> u1; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Double) -> case u0 of { _ALG_ D# (u1 :: Double#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Double) [ (Int) ] [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Double) -> u2; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Hashable Float - {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ - hash = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (Float) _N_ + hash = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 4 \ (u0 :: Float#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Float) [ (Int) ] [ u0 ] of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Float) -> u1; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Float) -> case u0 of { _ALG_ F# (u1 :: Float#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Float) [ (Int) ] [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Float) -> u2; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Hashable IOError {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (IOError) _N_ hash = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: IOError) -> _!_ I# [] [0#] _N_ } #-} diff --git a/ghc/lib/hbc/Hash_mp.hi b/ghc/lib/hbc/Hash_mp.hi index 25edd2ce8bbb6449c1a0d7fc9dffb9f85244e2f5..b576e4cc2e50f3faf8046d4e8d9c9fd3c900276b 100644 --- a/ghc/lib/hbc/Hash_mp.hi +++ b/ghc/lib/hbc/Hash_mp.hi @@ -39,11 +39,11 @@ instance Hashable Char instance (RealFloat a, Hashable a) => Hashable (Complex a) {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 3 _U_ 22 _N_ _S_ "LSS" _N_ _N_ #-} instance Hashable Double - {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ - hash = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (Double) _N_ + hash = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 4 \ (u0 :: Double#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Double) [ (Int) ] [ u0 ] of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Double) -> u1; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Double) -> case u0 of { _ALG_ D# (u1 :: Double#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Double) [ (Int) ] [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Double) -> u2; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Hashable Float - {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ - hash = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (Float) _N_ + hash = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 4 \ (u0 :: Float#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Float) [ (Int) ] [ u0 ] of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Float) -> u1; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Float) -> case u0 of { _ALG_ F# (u1 :: Float#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Float) [ (Int) ] [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Float) -> u2; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Hashable IOError {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (IOError) _N_ hash = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: IOError) -> _!_ I# [] [0#] _N_ } #-} diff --git a/ghc/lib/hbc/Hash_p.hi b/ghc/lib/hbc/Hash_p.hi index 25edd2ce8bbb6449c1a0d7fc9dffb9f85244e2f5..b576e4cc2e50f3faf8046d4e8d9c9fd3c900276b 100644 --- a/ghc/lib/hbc/Hash_p.hi +++ b/ghc/lib/hbc/Hash_p.hi @@ -39,11 +39,11 @@ instance Hashable Char instance (RealFloat a, Hashable a) => Hashable (Complex a) {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 3 _U_ 22 _N_ _S_ "LSS" _N_ _N_ #-} instance Hashable Double - {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ - hash = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (Double) _N_ + hash = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 4 \ (u0 :: Double#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Double) [ (Int) ] [ u0 ] of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Double) -> u1; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Double) -> case u0 of { _ALG_ D# (u1 :: Double#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Double) [ (Int) ] [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Double) -> u2; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Hashable Float - {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ - hash = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (Float) _N_ + hash = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 4 \ (u0 :: Float#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Float) [ (Int) ] [ u0 ] of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Float) -> u1; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Float) -> case u0 of { _ALG_ F# (u1 :: Float#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Float) [ (Int) ] [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Float) -> u2; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Hashable IOError {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (IOError) _N_ hash = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: IOError) -> _!_ I# [] [0#] _N_ } #-} diff --git a/ghc/lib/hbc/Hash_t.hi b/ghc/lib/hbc/Hash_t.hi index 25edd2ce8bbb6449c1a0d7fc9dffb9f85244e2f5..b576e4cc2e50f3faf8046d4e8d9c9fd3c900276b 100644 --- a/ghc/lib/hbc/Hash_t.hi +++ b/ghc/lib/hbc/Hash_t.hi @@ -39,11 +39,11 @@ instance Hashable Char instance (RealFloat a, Hashable a) => Hashable (Complex a) {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 3 _U_ 22 _N_ _S_ "LSS" _N_ _N_ #-} instance Hashable Double - {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ - hash = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (Double) _N_ + hash = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 4 \ (u0 :: Double#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Double) [ (Int) ] [ u0 ] of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Double) -> u1; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Double) -> case u0 of { _ALG_ D# (u1 :: Double#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Double) [ (Int) ] [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Double) -> u2; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Hashable Float - {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 0 _N_ _N_ _N_ _N_ _N_ - hash = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (Float) _N_ + hash = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 4 \ (u0 :: Float#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Float) [ (Int) ] [ u0 ] of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Float) -> u1; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Float) -> case u0 of { _ALG_ F# (u1 :: Float#) -> case _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac properFraction (Float) [ (Int) ] [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Float) -> u2; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Hashable IOError {-# GHC_PRAGMA _M_ Hash {-dfun-} _A_ 1 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Hashable hash (IOError) _N_ hash = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [0#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: IOError) -> _!_ I# [] [0#] _N_ } #-} diff --git a/ghc/lib/hbc/ListUtil.hi b/ghc/lib/hbc/ListUtil.hi index 05034a4243447154b86501fce7fcda39d9099176..678185effa066808ced393ae9d36095c0640c534 100644 --- a/ghc/lib/hbc/ListUtil.hi +++ b/ghc/lib/hbc/ListUtil.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListUtil where import PreludeStdIO(Maybe) assoc :: Eq b => (a -> c) -> c -> [(b, a)] -> b -> c @@ -16,7 +16,7 @@ group :: Eq a => [a] -> [[a]] groupEq :: (a -> a -> Bool) -> [a] -> [[a]] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} intersection :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} lookup :: Eq a => [(a, b)] -> a -> Maybe b {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} mapAccuml :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) diff --git a/ghc/lib/hbc/ListUtil_mc.hi b/ghc/lib/hbc/ListUtil_mc.hi index 05034a4243447154b86501fce7fcda39d9099176..678185effa066808ced393ae9d36095c0640c534 100644 --- a/ghc/lib/hbc/ListUtil_mc.hi +++ b/ghc/lib/hbc/ListUtil_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListUtil where import PreludeStdIO(Maybe) assoc :: Eq b => (a -> c) -> c -> [(b, a)] -> b -> c @@ -16,7 +16,7 @@ group :: Eq a => [a] -> [[a]] groupEq :: (a -> a -> Bool) -> [a] -> [[a]] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} intersection :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} lookup :: Eq a => [(a, b)] -> a -> Maybe b {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} mapAccuml :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) diff --git a/ghc/lib/hbc/ListUtil_mp.hi b/ghc/lib/hbc/ListUtil_mp.hi index 05034a4243447154b86501fce7fcda39d9099176..678185effa066808ced393ae9d36095c0640c534 100644 --- a/ghc/lib/hbc/ListUtil_mp.hi +++ b/ghc/lib/hbc/ListUtil_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListUtil where import PreludeStdIO(Maybe) assoc :: Eq b => (a -> c) -> c -> [(b, a)] -> b -> c @@ -16,7 +16,7 @@ group :: Eq a => [a] -> [[a]] groupEq :: (a -> a -> Bool) -> [a] -> [[a]] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} intersection :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} lookup :: Eq a => [(a, b)] -> a -> Maybe b {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} mapAccuml :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) diff --git a/ghc/lib/hbc/ListUtil_p.hi b/ghc/lib/hbc/ListUtil_p.hi index 05034a4243447154b86501fce7fcda39d9099176..678185effa066808ced393ae9d36095c0640c534 100644 --- a/ghc/lib/hbc/ListUtil_p.hi +++ b/ghc/lib/hbc/ListUtil_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListUtil where import PreludeStdIO(Maybe) assoc :: Eq b => (a -> c) -> c -> [(b, a)] -> b -> c @@ -16,7 +16,7 @@ group :: Eq a => [a] -> [[a]] groupEq :: (a -> a -> Bool) -> [a] -> [[a]] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} intersection :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} lookup :: Eq a => [(a, b)] -> a -> Maybe b {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} mapAccuml :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) diff --git a/ghc/lib/hbc/ListUtil_t.hi b/ghc/lib/hbc/ListUtil_t.hi index 05034a4243447154b86501fce7fcda39d9099176..678185effa066808ced393ae9d36095c0640c534 100644 --- a/ghc/lib/hbc/ListUtil_t.hi +++ b/ghc/lib/hbc/ListUtil_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface ListUtil where import PreludeStdIO(Maybe) assoc :: Eq b => (a -> c) -> c -> [(b, a)] -> b -> c @@ -16,7 +16,7 @@ group :: Eq a => [a] -> [[a]] groupEq :: (a -> a -> Bool) -> [a] -> [[a]] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} intersection :: Eq a => [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "LSL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 212 _N_ _N_ _N_ _N_ #-} lookup :: Eq a => [(a, b)] -> a -> Maybe b {-# GHC_PRAGMA _A_ 1 _U_ 112 _N_ _N_ _N_ _N_ #-} mapAccuml :: (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) diff --git a/ghc/lib/hbc/Miranda.hi b/ghc/lib/hbc/Miranda.hi index 4c61089c7110a61b92c76118141db71abd03c163..6e4d20417d1a5f1e6ef03dd976451282afbb9805 100644 --- a/ghc/lib/hbc/Miranda.hi +++ b/ghc/lib/hbc/Miranda.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Miranda where import QSort(sort) cjustify :: Int -> [Char] -> [Char] diff --git a/ghc/lib/hbc/Miranda_mc.hi b/ghc/lib/hbc/Miranda_mc.hi index 4c61089c7110a61b92c76118141db71abd03c163..6e4d20417d1a5f1e6ef03dd976451282afbb9805 100644 --- a/ghc/lib/hbc/Miranda_mc.hi +++ b/ghc/lib/hbc/Miranda_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Miranda where import QSort(sort) cjustify :: Int -> [Char] -> [Char] diff --git a/ghc/lib/hbc/Miranda_mp.hi b/ghc/lib/hbc/Miranda_mp.hi index 4c61089c7110a61b92c76118141db71abd03c163..6e4d20417d1a5f1e6ef03dd976451282afbb9805 100644 --- a/ghc/lib/hbc/Miranda_mp.hi +++ b/ghc/lib/hbc/Miranda_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Miranda where import QSort(sort) cjustify :: Int -> [Char] -> [Char] diff --git a/ghc/lib/hbc/Miranda_p.hi b/ghc/lib/hbc/Miranda_p.hi index 4c61089c7110a61b92c76118141db71abd03c163..6e4d20417d1a5f1e6ef03dd976451282afbb9805 100644 --- a/ghc/lib/hbc/Miranda_p.hi +++ b/ghc/lib/hbc/Miranda_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Miranda where import QSort(sort) cjustify :: Int -> [Char] -> [Char] diff --git a/ghc/lib/hbc/Miranda_t.hi b/ghc/lib/hbc/Miranda_t.hi index 4c61089c7110a61b92c76118141db71abd03c163..6e4d20417d1a5f1e6ef03dd976451282afbb9805 100644 --- a/ghc/lib/hbc/Miranda_t.hi +++ b/ghc/lib/hbc/Miranda_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Miranda where import QSort(sort) cjustify :: Int -> [Char] -> [Char] diff --git a/ghc/lib/hbc/Number.hi b/ghc/lib/hbc/Number.hi index eb5642f7500826c1c4a8773ca00c94b07afbe7c9..cd98fd5f656a1e12a90225d90c3b2ee17c0df100 100644 --- a/ghc/lib/hbc/Number.hi +++ b/ghc/lib/hbc/Number.hi @@ -1,103 +1,103 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Number where data Number {-# GHC_PRAGMA I Integer | F Double #-} isInteger :: Number -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} instance Enum Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Number}}, (Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> Number -> [Number])] [_DFUN_ Ord (Number), _CONSTM_ Enum enumFrom (Number), _CONSTM_ Enum enumFromThen (Number), _CONSTM_ Enum enumFromTo (Number), _CONSTM_ Enum enumFromThenTo (Number)] _N_ - enumFrom = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - enumFromThen = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - enumFromTo = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - enumFromThenTo = _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} + enumFrom = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + enumFromThen = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + enumFromTo = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + enumFromThenTo = { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} instance Eq Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Number -> Number -> Bool), (Number -> Number -> Bool)] [_CONSTM_ Eq (==) (Number), _CONSTM_ Eq (/=) (Number)] _N_ - (==) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (/=) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Floating Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 20 _!_ _TUP_19 [{{Fractional Number}}, Number, (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number)] [_DFUN_ Fractional (Number), _CONSTM_ Floating pi (Number), _CONSTM_ Floating exp (Number), _CONSTM_ Floating log (Number), _CONSTM_ Floating sqrt (Number), _CONSTM_ Floating (**) (Number), _CONSTM_ Floating logBase (Number), _CONSTM_ Floating sin (Number), _CONSTM_ Floating cos (Number), _CONSTM_ Floating tan (Number), _CONSTM_ Floating asin (Number), _CONSTM_ Floating acos (Number), _CONSTM_ Floating atan (Number), _CONSTM_ Floating sinh (Number), _CONSTM_ Floating cosh (Number), _CONSTM_ Floating tanh (Number), _CONSTM_ Floating asinh (Number), _CONSTM_ Floating acosh (Number), _CONSTM_ Floating atanh (Number)] _N_ - pi = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_, - exp = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - log = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sqrt = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - (**) = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - logBase = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - sin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + pi = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_ }, + exp = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + log = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sqrt = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + (**) = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + logBase = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + sin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance Fractional Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Num Number}}, (Number -> Number -> Number), (Number -> Number), (Ratio Integer -> Number)] [_DFUN_ Num (Number), _CONSTM_ Fractional (/) (Number), _CONSTM_ Fractional recip (Number), _CONSTM_ Fractional fromRational (Number)] _N_ - (/) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - recip = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - fromRational = _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (/) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + recip = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + fromRational = { _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Integral Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 13 _!_ _TUP_12 [{{Real Number}}, {{Ix Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> (Number, Number)), (Number -> Number -> (Number, Number)), (Number -> Bool), (Number -> Bool), (Number -> Integer), (Number -> Int)] [_DFUN_ Real (Number), _DFUN_ Ix (Number), _CONSTM_ Integral quot (Number), _CONSTM_ Integral rem (Number), _CONSTM_ Integral div (Number), _CONSTM_ Integral mod (Number), _CONSTM_ Integral quotRem (Number), _CONSTM_ Integral divMod (Number), _CONSTM_ Integral even (Number), _CONSTM_ Integral odd (Number), _CONSTM_ Integral toInteger (Number), _CONSTM_ Integral toInt (Number)] _N_ - quot = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_, - rem = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_, - div = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - mod = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - quotRem = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - divMod = _A_ 0 _U_ 22 _N_ _N_ _N_ _N_, - even = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - odd = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - toInteger = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - toInt = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Number) -> _APP_ _TYAPP_ patError# { (Number -> Int) } [ _NOREP_S_ "%DPreludeCore.Integral.toInt\"", u0 ] _N_ #-} + quot = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_ }, + rem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_ }, + div = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + mod = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + quotRem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + divMod = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ }, + even = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + odd = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + toInteger = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 C 6 \ (u0 :: Number) -> case u0 of { _ALG_ _ORIG_ Number I (u1 :: Integer) -> u1; _ORIG_ Number F (u2 :: Double) -> case u2 of { _ALG_ D# (u3 :: Double#) -> _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac round (Double) [ (Integer) ] [ u3 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + toInt = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ } #-} instance Ix Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Number}}, ((Number, Number) -> [Number]), ((Number, Number) -> Number -> Int), ((Number, Number) -> Number -> Bool)] [_DFUN_ Ord (Number), _CONSTM_ Ix range (Number), _CONSTM_ Ix index (Number), _CONSTM_ Ix inRange (Number)] _N_ - range = _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - index = _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - inRange = _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + inRange = { _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Number}}, {{Text Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Integer -> Number), (Int -> Number)] [_DFUN_ Eq (Number), _DFUN_ Text (Number), _CONSTM_ Num (+) (Number), _CONSTM_ Num (-) (Number), _CONSTM_ Num (*) (Number), _CONSTM_ Num negate (Number), _CONSTM_ Num abs (Number), _CONSTM_ Num signum (Number), _CONSTM_ Num fromInteger (Number), _CONSTM_ Num fromInt (Number)] _N_ - (+) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (-) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (*) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - fromInteger = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_, - fromInt = _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ #-} + (+) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (-) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (*) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ } #-} instance Ord Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Number}}, (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> _CMP_TAG)] [_DFUN_ Eq (Number), _CONSTM_ Ord (<) (Number), _CONSTM_ Ord (<=) (Number), _CONSTM_ Ord (>=) (Number), _CONSTM_ Ord (>) (Number), _CONSTM_ Ord max (Number), _CONSTM_ Ord min (Number), _CONSTM_ Ord _tagCmp (Number)] _N_ - (<) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - (<=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (>=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_, - (>) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - _tagCmp = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (<) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + (<=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_ }, + (>) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Real Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Num Number}}, {{Enum Number}}, (Number -> Ratio Integer)] [_DFUN_ Num (Number), _DFUN_ Enum (Number), _CONSTM_ Real toRational (Number)] _N_ - toRational = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + toRational = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance RealFloat Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{RealFrac Number}}, {{Floating Number}}, (Number -> Integer), (Number -> Int), (Number -> (Int, Int)), (Number -> (Integer, Int)), (Integer -> Int -> Number), (Number -> Int), (Number -> Number), (Int -> Number -> Number)] [_DFUN_ RealFrac (Number), _DFUN_ Floating (Number), _CONSTM_ RealFloat floatRadix (Number), _CONSTM_ RealFloat floatDigits (Number), _CONSTM_ RealFloat floatRange (Number), _CONSTM_ RealFloat decodeFloat (Number), _CONSTM_ RealFloat encodeFloat (Number), _CONSTM_ RealFloat exponent (Number), _CONSTM_ RealFloat significand (Number), _CONSTM_ RealFloat scaleFloat (Number)] _N_ - floatRadix = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [2#] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Number) -> _#_ int2Integer# [] [2#] _N_, - floatDigits = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_, - floatRange = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_, - decodeFloat = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - encodeFloat = _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - exponent = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - significand = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - scaleFloat = _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} + floatRadix = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + floatDigits = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_ }, + floatRange = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + decodeFloat = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + encodeFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + exponent = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + significand = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + scaleFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(P)S" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance RealFrac Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 8 _!_ _TUP_7 [{{Real Number}}, {{Fractional Number}}, _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> (a$z1, Number)), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1)] [_DFUN_ Real (Number), _DFUN_ Fractional (Number), _CONSTM_ RealFrac properFraction (Number), _CONSTM_ RealFrac truncate (Number), _CONSTM_ RealFrac round (Number), _CONSTM_ RealFrac ceiling (Number), _CONSTM_ RealFrac floor (Number)] _N_ - properFraction = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - truncate = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - round = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - ceiling = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - floor = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + properFraction = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + truncate = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + round = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + ceiling = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + floor = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ } #-} instance Text Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Number, [Char])]), (Int -> Number -> [Char] -> [Char]), ([Char] -> [([Number], [Char])]), ([Number] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Number), _CONSTM_ Text showsPrec (Number), _CONSTM_ Text readList (Number), _CONSTM_ Text showList (Number)] _N_ - readsPrec = _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Number_mc.hi b/ghc/lib/hbc/Number_mc.hi index eb5642f7500826c1c4a8773ca00c94b07afbe7c9..cd98fd5f656a1e12a90225d90c3b2ee17c0df100 100644 --- a/ghc/lib/hbc/Number_mc.hi +++ b/ghc/lib/hbc/Number_mc.hi @@ -1,103 +1,103 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Number where data Number {-# GHC_PRAGMA I Integer | F Double #-} isInteger :: Number -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} instance Enum Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Number}}, (Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> Number -> [Number])] [_DFUN_ Ord (Number), _CONSTM_ Enum enumFrom (Number), _CONSTM_ Enum enumFromThen (Number), _CONSTM_ Enum enumFromTo (Number), _CONSTM_ Enum enumFromThenTo (Number)] _N_ - enumFrom = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - enumFromThen = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - enumFromTo = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - enumFromThenTo = _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} + enumFrom = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + enumFromThen = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + enumFromTo = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + enumFromThenTo = { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} instance Eq Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Number -> Number -> Bool), (Number -> Number -> Bool)] [_CONSTM_ Eq (==) (Number), _CONSTM_ Eq (/=) (Number)] _N_ - (==) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (/=) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Floating Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 20 _!_ _TUP_19 [{{Fractional Number}}, Number, (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number)] [_DFUN_ Fractional (Number), _CONSTM_ Floating pi (Number), _CONSTM_ Floating exp (Number), _CONSTM_ Floating log (Number), _CONSTM_ Floating sqrt (Number), _CONSTM_ Floating (**) (Number), _CONSTM_ Floating logBase (Number), _CONSTM_ Floating sin (Number), _CONSTM_ Floating cos (Number), _CONSTM_ Floating tan (Number), _CONSTM_ Floating asin (Number), _CONSTM_ Floating acos (Number), _CONSTM_ Floating atan (Number), _CONSTM_ Floating sinh (Number), _CONSTM_ Floating cosh (Number), _CONSTM_ Floating tanh (Number), _CONSTM_ Floating asinh (Number), _CONSTM_ Floating acosh (Number), _CONSTM_ Floating atanh (Number)] _N_ - pi = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_, - exp = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - log = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sqrt = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - (**) = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - logBase = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - sin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + pi = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_ }, + exp = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + log = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sqrt = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + (**) = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + logBase = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + sin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance Fractional Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Num Number}}, (Number -> Number -> Number), (Number -> Number), (Ratio Integer -> Number)] [_DFUN_ Num (Number), _CONSTM_ Fractional (/) (Number), _CONSTM_ Fractional recip (Number), _CONSTM_ Fractional fromRational (Number)] _N_ - (/) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - recip = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - fromRational = _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (/) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + recip = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + fromRational = { _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Integral Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 13 _!_ _TUP_12 [{{Real Number}}, {{Ix Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> (Number, Number)), (Number -> Number -> (Number, Number)), (Number -> Bool), (Number -> Bool), (Number -> Integer), (Number -> Int)] [_DFUN_ Real (Number), _DFUN_ Ix (Number), _CONSTM_ Integral quot (Number), _CONSTM_ Integral rem (Number), _CONSTM_ Integral div (Number), _CONSTM_ Integral mod (Number), _CONSTM_ Integral quotRem (Number), _CONSTM_ Integral divMod (Number), _CONSTM_ Integral even (Number), _CONSTM_ Integral odd (Number), _CONSTM_ Integral toInteger (Number), _CONSTM_ Integral toInt (Number)] _N_ - quot = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_, - rem = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_, - div = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - mod = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - quotRem = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - divMod = _A_ 0 _U_ 22 _N_ _N_ _N_ _N_, - even = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - odd = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - toInteger = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - toInt = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Number) -> _APP_ _TYAPP_ patError# { (Number -> Int) } [ _NOREP_S_ "%DPreludeCore.Integral.toInt\"", u0 ] _N_ #-} + quot = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_ }, + rem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_ }, + div = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + mod = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + quotRem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + divMod = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ }, + even = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + odd = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + toInteger = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 C 6 \ (u0 :: Number) -> case u0 of { _ALG_ _ORIG_ Number I (u1 :: Integer) -> u1; _ORIG_ Number F (u2 :: Double) -> case u2 of { _ALG_ D# (u3 :: Double#) -> _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac round (Double) [ (Integer) ] [ u3 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + toInt = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ } #-} instance Ix Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Number}}, ((Number, Number) -> [Number]), ((Number, Number) -> Number -> Int), ((Number, Number) -> Number -> Bool)] [_DFUN_ Ord (Number), _CONSTM_ Ix range (Number), _CONSTM_ Ix index (Number), _CONSTM_ Ix inRange (Number)] _N_ - range = _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - index = _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - inRange = _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + inRange = { _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Number}}, {{Text Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Integer -> Number), (Int -> Number)] [_DFUN_ Eq (Number), _DFUN_ Text (Number), _CONSTM_ Num (+) (Number), _CONSTM_ Num (-) (Number), _CONSTM_ Num (*) (Number), _CONSTM_ Num negate (Number), _CONSTM_ Num abs (Number), _CONSTM_ Num signum (Number), _CONSTM_ Num fromInteger (Number), _CONSTM_ Num fromInt (Number)] _N_ - (+) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (-) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (*) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - fromInteger = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_, - fromInt = _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ #-} + (+) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (-) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (*) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ } #-} instance Ord Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Number}}, (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> _CMP_TAG)] [_DFUN_ Eq (Number), _CONSTM_ Ord (<) (Number), _CONSTM_ Ord (<=) (Number), _CONSTM_ Ord (>=) (Number), _CONSTM_ Ord (>) (Number), _CONSTM_ Ord max (Number), _CONSTM_ Ord min (Number), _CONSTM_ Ord _tagCmp (Number)] _N_ - (<) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - (<=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (>=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_, - (>) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - _tagCmp = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (<) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + (<=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_ }, + (>) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Real Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Num Number}}, {{Enum Number}}, (Number -> Ratio Integer)] [_DFUN_ Num (Number), _DFUN_ Enum (Number), _CONSTM_ Real toRational (Number)] _N_ - toRational = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + toRational = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance RealFloat Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{RealFrac Number}}, {{Floating Number}}, (Number -> Integer), (Number -> Int), (Number -> (Int, Int)), (Number -> (Integer, Int)), (Integer -> Int -> Number), (Number -> Int), (Number -> Number), (Int -> Number -> Number)] [_DFUN_ RealFrac (Number), _DFUN_ Floating (Number), _CONSTM_ RealFloat floatRadix (Number), _CONSTM_ RealFloat floatDigits (Number), _CONSTM_ RealFloat floatRange (Number), _CONSTM_ RealFloat decodeFloat (Number), _CONSTM_ RealFloat encodeFloat (Number), _CONSTM_ RealFloat exponent (Number), _CONSTM_ RealFloat significand (Number), _CONSTM_ RealFloat scaleFloat (Number)] _N_ - floatRadix = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [2#] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Number) -> _#_ int2Integer# [] [2#] _N_, - floatDigits = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_, - floatRange = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_, - decodeFloat = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - encodeFloat = _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - exponent = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - significand = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - scaleFloat = _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} + floatRadix = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + floatDigits = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_ }, + floatRange = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + decodeFloat = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + encodeFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + exponent = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + significand = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + scaleFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(P)S" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance RealFrac Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 8 _!_ _TUP_7 [{{Real Number}}, {{Fractional Number}}, _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> (a$z1, Number)), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1)] [_DFUN_ Real (Number), _DFUN_ Fractional (Number), _CONSTM_ RealFrac properFraction (Number), _CONSTM_ RealFrac truncate (Number), _CONSTM_ RealFrac round (Number), _CONSTM_ RealFrac ceiling (Number), _CONSTM_ RealFrac floor (Number)] _N_ - properFraction = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - truncate = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - round = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - ceiling = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - floor = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + properFraction = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + truncate = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + round = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + ceiling = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + floor = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ } #-} instance Text Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Number, [Char])]), (Int -> Number -> [Char] -> [Char]), ([Char] -> [([Number], [Char])]), ([Number] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Number), _CONSTM_ Text showsPrec (Number), _CONSTM_ Text readList (Number), _CONSTM_ Text showList (Number)] _N_ - readsPrec = _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Number_mp.hi b/ghc/lib/hbc/Number_mp.hi index eb5642f7500826c1c4a8773ca00c94b07afbe7c9..cd98fd5f656a1e12a90225d90c3b2ee17c0df100 100644 --- a/ghc/lib/hbc/Number_mp.hi +++ b/ghc/lib/hbc/Number_mp.hi @@ -1,103 +1,103 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Number where data Number {-# GHC_PRAGMA I Integer | F Double #-} isInteger :: Number -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} instance Enum Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Number}}, (Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> Number -> [Number])] [_DFUN_ Ord (Number), _CONSTM_ Enum enumFrom (Number), _CONSTM_ Enum enumFromThen (Number), _CONSTM_ Enum enumFromTo (Number), _CONSTM_ Enum enumFromThenTo (Number)] _N_ - enumFrom = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - enumFromThen = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - enumFromTo = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - enumFromThenTo = _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} + enumFrom = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + enumFromThen = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + enumFromTo = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + enumFromThenTo = { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} instance Eq Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Number -> Number -> Bool), (Number -> Number -> Bool)] [_CONSTM_ Eq (==) (Number), _CONSTM_ Eq (/=) (Number)] _N_ - (==) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (/=) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Floating Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 20 _!_ _TUP_19 [{{Fractional Number}}, Number, (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number)] [_DFUN_ Fractional (Number), _CONSTM_ Floating pi (Number), _CONSTM_ Floating exp (Number), _CONSTM_ Floating log (Number), _CONSTM_ Floating sqrt (Number), _CONSTM_ Floating (**) (Number), _CONSTM_ Floating logBase (Number), _CONSTM_ Floating sin (Number), _CONSTM_ Floating cos (Number), _CONSTM_ Floating tan (Number), _CONSTM_ Floating asin (Number), _CONSTM_ Floating acos (Number), _CONSTM_ Floating atan (Number), _CONSTM_ Floating sinh (Number), _CONSTM_ Floating cosh (Number), _CONSTM_ Floating tanh (Number), _CONSTM_ Floating asinh (Number), _CONSTM_ Floating acosh (Number), _CONSTM_ Floating atanh (Number)] _N_ - pi = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_, - exp = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - log = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sqrt = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - (**) = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - logBase = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - sin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + pi = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_ }, + exp = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + log = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sqrt = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + (**) = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + logBase = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + sin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance Fractional Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Num Number}}, (Number -> Number -> Number), (Number -> Number), (Ratio Integer -> Number)] [_DFUN_ Num (Number), _CONSTM_ Fractional (/) (Number), _CONSTM_ Fractional recip (Number), _CONSTM_ Fractional fromRational (Number)] _N_ - (/) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - recip = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - fromRational = _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (/) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + recip = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + fromRational = { _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Integral Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 13 _!_ _TUP_12 [{{Real Number}}, {{Ix Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> (Number, Number)), (Number -> Number -> (Number, Number)), (Number -> Bool), (Number -> Bool), (Number -> Integer), (Number -> Int)] [_DFUN_ Real (Number), _DFUN_ Ix (Number), _CONSTM_ Integral quot (Number), _CONSTM_ Integral rem (Number), _CONSTM_ Integral div (Number), _CONSTM_ Integral mod (Number), _CONSTM_ Integral quotRem (Number), _CONSTM_ Integral divMod (Number), _CONSTM_ Integral even (Number), _CONSTM_ Integral odd (Number), _CONSTM_ Integral toInteger (Number), _CONSTM_ Integral toInt (Number)] _N_ - quot = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_, - rem = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_, - div = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - mod = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - quotRem = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - divMod = _A_ 0 _U_ 22 _N_ _N_ _N_ _N_, - even = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - odd = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - toInteger = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - toInt = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Number) -> _APP_ _TYAPP_ patError# { (Number -> Int) } [ _NOREP_S_ "%DPreludeCore.Integral.toInt\"", u0 ] _N_ #-} + quot = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_ }, + rem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_ }, + div = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + mod = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + quotRem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + divMod = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ }, + even = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + odd = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + toInteger = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 C 6 \ (u0 :: Number) -> case u0 of { _ALG_ _ORIG_ Number I (u1 :: Integer) -> u1; _ORIG_ Number F (u2 :: Double) -> case u2 of { _ALG_ D# (u3 :: Double#) -> _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac round (Double) [ (Integer) ] [ u3 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + toInt = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ } #-} instance Ix Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Number}}, ((Number, Number) -> [Number]), ((Number, Number) -> Number -> Int), ((Number, Number) -> Number -> Bool)] [_DFUN_ Ord (Number), _CONSTM_ Ix range (Number), _CONSTM_ Ix index (Number), _CONSTM_ Ix inRange (Number)] _N_ - range = _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - index = _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - inRange = _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + inRange = { _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Number}}, {{Text Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Integer -> Number), (Int -> Number)] [_DFUN_ Eq (Number), _DFUN_ Text (Number), _CONSTM_ Num (+) (Number), _CONSTM_ Num (-) (Number), _CONSTM_ Num (*) (Number), _CONSTM_ Num negate (Number), _CONSTM_ Num abs (Number), _CONSTM_ Num signum (Number), _CONSTM_ Num fromInteger (Number), _CONSTM_ Num fromInt (Number)] _N_ - (+) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (-) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (*) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - fromInteger = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_, - fromInt = _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ #-} + (+) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (-) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (*) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ } #-} instance Ord Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Number}}, (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> _CMP_TAG)] [_DFUN_ Eq (Number), _CONSTM_ Ord (<) (Number), _CONSTM_ Ord (<=) (Number), _CONSTM_ Ord (>=) (Number), _CONSTM_ Ord (>) (Number), _CONSTM_ Ord max (Number), _CONSTM_ Ord min (Number), _CONSTM_ Ord _tagCmp (Number)] _N_ - (<) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - (<=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (>=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_, - (>) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - _tagCmp = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (<) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + (<=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_ }, + (>) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Real Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Num Number}}, {{Enum Number}}, (Number -> Ratio Integer)] [_DFUN_ Num (Number), _DFUN_ Enum (Number), _CONSTM_ Real toRational (Number)] _N_ - toRational = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + toRational = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance RealFloat Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{RealFrac Number}}, {{Floating Number}}, (Number -> Integer), (Number -> Int), (Number -> (Int, Int)), (Number -> (Integer, Int)), (Integer -> Int -> Number), (Number -> Int), (Number -> Number), (Int -> Number -> Number)] [_DFUN_ RealFrac (Number), _DFUN_ Floating (Number), _CONSTM_ RealFloat floatRadix (Number), _CONSTM_ RealFloat floatDigits (Number), _CONSTM_ RealFloat floatRange (Number), _CONSTM_ RealFloat decodeFloat (Number), _CONSTM_ RealFloat encodeFloat (Number), _CONSTM_ RealFloat exponent (Number), _CONSTM_ RealFloat significand (Number), _CONSTM_ RealFloat scaleFloat (Number)] _N_ - floatRadix = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [2#] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Number) -> _#_ int2Integer# [] [2#] _N_, - floatDigits = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_, - floatRange = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_, - decodeFloat = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - encodeFloat = _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - exponent = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - significand = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - scaleFloat = _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} + floatRadix = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + floatDigits = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_ }, + floatRange = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + decodeFloat = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + encodeFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + exponent = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + significand = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + scaleFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(P)S" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance RealFrac Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 8 _!_ _TUP_7 [{{Real Number}}, {{Fractional Number}}, _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> (a$z1, Number)), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1)] [_DFUN_ Real (Number), _DFUN_ Fractional (Number), _CONSTM_ RealFrac properFraction (Number), _CONSTM_ RealFrac truncate (Number), _CONSTM_ RealFrac round (Number), _CONSTM_ RealFrac ceiling (Number), _CONSTM_ RealFrac floor (Number)] _N_ - properFraction = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - truncate = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - round = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - ceiling = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - floor = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + properFraction = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + truncate = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + round = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + ceiling = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + floor = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ } #-} instance Text Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Number, [Char])]), (Int -> Number -> [Char] -> [Char]), ([Char] -> [([Number], [Char])]), ([Number] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Number), _CONSTM_ Text showsPrec (Number), _CONSTM_ Text readList (Number), _CONSTM_ Text showList (Number)] _N_ - readsPrec = _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Number_p.hi b/ghc/lib/hbc/Number_p.hi index eb5642f7500826c1c4a8773ca00c94b07afbe7c9..cd98fd5f656a1e12a90225d90c3b2ee17c0df100 100644 --- a/ghc/lib/hbc/Number_p.hi +++ b/ghc/lib/hbc/Number_p.hi @@ -1,103 +1,103 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Number where data Number {-# GHC_PRAGMA I Integer | F Double #-} isInteger :: Number -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} instance Enum Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Number}}, (Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> Number -> [Number])] [_DFUN_ Ord (Number), _CONSTM_ Enum enumFrom (Number), _CONSTM_ Enum enumFromThen (Number), _CONSTM_ Enum enumFromTo (Number), _CONSTM_ Enum enumFromThenTo (Number)] _N_ - enumFrom = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - enumFromThen = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - enumFromTo = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - enumFromThenTo = _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} + enumFrom = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + enumFromThen = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + enumFromTo = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + enumFromThenTo = { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} instance Eq Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Number -> Number -> Bool), (Number -> Number -> Bool)] [_CONSTM_ Eq (==) (Number), _CONSTM_ Eq (/=) (Number)] _N_ - (==) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (/=) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Floating Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 20 _!_ _TUP_19 [{{Fractional Number}}, Number, (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number)] [_DFUN_ Fractional (Number), _CONSTM_ Floating pi (Number), _CONSTM_ Floating exp (Number), _CONSTM_ Floating log (Number), _CONSTM_ Floating sqrt (Number), _CONSTM_ Floating (**) (Number), _CONSTM_ Floating logBase (Number), _CONSTM_ Floating sin (Number), _CONSTM_ Floating cos (Number), _CONSTM_ Floating tan (Number), _CONSTM_ Floating asin (Number), _CONSTM_ Floating acos (Number), _CONSTM_ Floating atan (Number), _CONSTM_ Floating sinh (Number), _CONSTM_ Floating cosh (Number), _CONSTM_ Floating tanh (Number), _CONSTM_ Floating asinh (Number), _CONSTM_ Floating acosh (Number), _CONSTM_ Floating atanh (Number)] _N_ - pi = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_, - exp = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - log = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sqrt = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - (**) = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - logBase = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - sin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + pi = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_ }, + exp = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + log = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sqrt = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + (**) = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + logBase = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + sin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance Fractional Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Num Number}}, (Number -> Number -> Number), (Number -> Number), (Ratio Integer -> Number)] [_DFUN_ Num (Number), _CONSTM_ Fractional (/) (Number), _CONSTM_ Fractional recip (Number), _CONSTM_ Fractional fromRational (Number)] _N_ - (/) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - recip = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - fromRational = _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (/) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + recip = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + fromRational = { _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Integral Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 13 _!_ _TUP_12 [{{Real Number}}, {{Ix Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> (Number, Number)), (Number -> Number -> (Number, Number)), (Number -> Bool), (Number -> Bool), (Number -> Integer), (Number -> Int)] [_DFUN_ Real (Number), _DFUN_ Ix (Number), _CONSTM_ Integral quot (Number), _CONSTM_ Integral rem (Number), _CONSTM_ Integral div (Number), _CONSTM_ Integral mod (Number), _CONSTM_ Integral quotRem (Number), _CONSTM_ Integral divMod (Number), _CONSTM_ Integral even (Number), _CONSTM_ Integral odd (Number), _CONSTM_ Integral toInteger (Number), _CONSTM_ Integral toInt (Number)] _N_ - quot = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_, - rem = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_, - div = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - mod = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - quotRem = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - divMod = _A_ 0 _U_ 22 _N_ _N_ _N_ _N_, - even = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - odd = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - toInteger = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - toInt = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Number) -> _APP_ _TYAPP_ patError# { (Number -> Int) } [ _NOREP_S_ "%DPreludeCore.Integral.toInt\"", u0 ] _N_ #-} + quot = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_ }, + rem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_ }, + div = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + mod = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + quotRem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + divMod = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ }, + even = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + odd = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + toInteger = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 C 6 \ (u0 :: Number) -> case u0 of { _ALG_ _ORIG_ Number I (u1 :: Integer) -> u1; _ORIG_ Number F (u2 :: Double) -> case u2 of { _ALG_ D# (u3 :: Double#) -> _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac round (Double) [ (Integer) ] [ u3 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + toInt = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ } #-} instance Ix Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Number}}, ((Number, Number) -> [Number]), ((Number, Number) -> Number -> Int), ((Number, Number) -> Number -> Bool)] [_DFUN_ Ord (Number), _CONSTM_ Ix range (Number), _CONSTM_ Ix index (Number), _CONSTM_ Ix inRange (Number)] _N_ - range = _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - index = _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - inRange = _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + inRange = { _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Number}}, {{Text Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Integer -> Number), (Int -> Number)] [_DFUN_ Eq (Number), _DFUN_ Text (Number), _CONSTM_ Num (+) (Number), _CONSTM_ Num (-) (Number), _CONSTM_ Num (*) (Number), _CONSTM_ Num negate (Number), _CONSTM_ Num abs (Number), _CONSTM_ Num signum (Number), _CONSTM_ Num fromInteger (Number), _CONSTM_ Num fromInt (Number)] _N_ - (+) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (-) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (*) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - fromInteger = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_, - fromInt = _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ #-} + (+) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (-) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (*) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ } #-} instance Ord Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Number}}, (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> _CMP_TAG)] [_DFUN_ Eq (Number), _CONSTM_ Ord (<) (Number), _CONSTM_ Ord (<=) (Number), _CONSTM_ Ord (>=) (Number), _CONSTM_ Ord (>) (Number), _CONSTM_ Ord max (Number), _CONSTM_ Ord min (Number), _CONSTM_ Ord _tagCmp (Number)] _N_ - (<) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - (<=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (>=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_, - (>) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - _tagCmp = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (<) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + (<=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_ }, + (>) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Real Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Num Number}}, {{Enum Number}}, (Number -> Ratio Integer)] [_DFUN_ Num (Number), _DFUN_ Enum (Number), _CONSTM_ Real toRational (Number)] _N_ - toRational = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + toRational = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance RealFloat Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{RealFrac Number}}, {{Floating Number}}, (Number -> Integer), (Number -> Int), (Number -> (Int, Int)), (Number -> (Integer, Int)), (Integer -> Int -> Number), (Number -> Int), (Number -> Number), (Int -> Number -> Number)] [_DFUN_ RealFrac (Number), _DFUN_ Floating (Number), _CONSTM_ RealFloat floatRadix (Number), _CONSTM_ RealFloat floatDigits (Number), _CONSTM_ RealFloat floatRange (Number), _CONSTM_ RealFloat decodeFloat (Number), _CONSTM_ RealFloat encodeFloat (Number), _CONSTM_ RealFloat exponent (Number), _CONSTM_ RealFloat significand (Number), _CONSTM_ RealFloat scaleFloat (Number)] _N_ - floatRadix = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [2#] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Number) -> _#_ int2Integer# [] [2#] _N_, - floatDigits = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_, - floatRange = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_, - decodeFloat = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - encodeFloat = _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - exponent = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - significand = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - scaleFloat = _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} + floatRadix = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + floatDigits = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_ }, + floatRange = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + decodeFloat = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + encodeFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + exponent = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + significand = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + scaleFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(P)S" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance RealFrac Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 8 _!_ _TUP_7 [{{Real Number}}, {{Fractional Number}}, _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> (a$z1, Number)), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1)] [_DFUN_ Real (Number), _DFUN_ Fractional (Number), _CONSTM_ RealFrac properFraction (Number), _CONSTM_ RealFrac truncate (Number), _CONSTM_ RealFrac round (Number), _CONSTM_ RealFrac ceiling (Number), _CONSTM_ RealFrac floor (Number)] _N_ - properFraction = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - truncate = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - round = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - ceiling = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - floor = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + properFraction = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + truncate = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + round = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + ceiling = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + floor = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ } #-} instance Text Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Number, [Char])]), (Int -> Number -> [Char] -> [Char]), ([Char] -> [([Number], [Char])]), ([Number] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Number), _CONSTM_ Text showsPrec (Number), _CONSTM_ Text readList (Number), _CONSTM_ Text showList (Number)] _N_ - readsPrec = _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Number_t.hi b/ghc/lib/hbc/Number_t.hi index eb5642f7500826c1c4a8773ca00c94b07afbe7c9..cd98fd5f656a1e12a90225d90c3b2ee17c0df100 100644 --- a/ghc/lib/hbc/Number_t.hi +++ b/ghc/lib/hbc/Number_t.hi @@ -1,103 +1,103 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Number where data Number {-# GHC_PRAGMA I Integer | F Double #-} isInteger :: Number -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} instance Enum Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Number}}, (Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> [Number]), (Number -> Number -> Number -> [Number])] [_DFUN_ Ord (Number), _CONSTM_ Enum enumFrom (Number), _CONSTM_ Enum enumFromThen (Number), _CONSTM_ Enum enumFromTo (Number), _CONSTM_ Enum enumFromThenTo (Number)] _N_ - enumFrom = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - enumFromThen = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - enumFromTo = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - enumFromThenTo = _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} + enumFrom = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + enumFromThen = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + enumFromTo = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + enumFromThenTo = { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} instance Eq Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Number -> Number -> Bool), (Number -> Number -> Bool)] [_CONSTM_ Eq (==) (Number), _CONSTM_ Eq (/=) (Number)] _N_ - (==) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (/=) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Floating Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 20 _!_ _TUP_19 [{{Fractional Number}}, Number, (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number)] [_DFUN_ Fractional (Number), _CONSTM_ Floating pi (Number), _CONSTM_ Floating exp (Number), _CONSTM_ Floating log (Number), _CONSTM_ Floating sqrt (Number), _CONSTM_ Floating (**) (Number), _CONSTM_ Floating logBase (Number), _CONSTM_ Floating sin (Number), _CONSTM_ Floating cos (Number), _CONSTM_ Floating tan (Number), _CONSTM_ Floating asin (Number), _CONSTM_ Floating acos (Number), _CONSTM_ Floating atan (Number), _CONSTM_ Floating sinh (Number), _CONSTM_ Floating cosh (Number), _CONSTM_ Floating tanh (Number), _CONSTM_ Floating asinh (Number), _CONSTM_ Floating acosh (Number), _CONSTM_ Floating atanh (Number)] _N_ - pi = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_, - exp = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - log = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sqrt = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - (**) = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - logBase = _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_, - sin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asin = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acos = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atan = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - sinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - cosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - tanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - asinh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - acosh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - atanh = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + pi = { _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ _ORIG_ Number F [] [_CONSTM_ Floating pi (Double)] _N_ }, + exp = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + log = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sqrt = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + (**) = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + logBase = { _A_ 2 _U_ 11 _N_ _S_ "SS" _N_ _N_ }, + sin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asin = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acos = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atan = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + sinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + cosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + tanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + asinh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + acosh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + atanh = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance Fractional Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Num Number}}, (Number -> Number -> Number), (Number -> Number), (Ratio Integer -> Number)] [_DFUN_ Num (Number), _CONSTM_ Fractional (/) (Number), _CONSTM_ Fractional recip (Number), _CONSTM_ Fractional fromRational (Number)] _N_ - (/) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - recip = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - fromRational = _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (/) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + recip = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + fromRational = { _A_ 1 _U_ 1 _N_ _S_ "U(LU(PPP))" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Integral Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 13 _!_ _TUP_12 [{{Real Number}}, {{Ix Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> (Number, Number)), (Number -> Number -> (Number, Number)), (Number -> Bool), (Number -> Bool), (Number -> Integer), (Number -> Int)] [_DFUN_ Real (Number), _DFUN_ Ix (Number), _CONSTM_ Integral quot (Number), _CONSTM_ Integral rem (Number), _CONSTM_ Integral div (Number), _CONSTM_ Integral mod (Number), _CONSTM_ Integral quotRem (Number), _CONSTM_ Integral divMod (Number), _CONSTM_ Integral even (Number), _CONSTM_ Integral odd (Number), _CONSTM_ Integral toInteger (Number), _CONSTM_ Integral toInt (Number)] _N_ - quot = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_, - rem = _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_, - div = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - mod = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - quotRem = _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_, - divMod = _A_ 0 _U_ 22 _N_ _N_ _N_ _N_, - even = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - odd = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - toInteger = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - toInt = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Number) -> _APP_ _TYAPP_ patError# { (Number -> Int) } [ _NOREP_S_ "%DPreludeCore.Integral.toInt\"", u0 ] _N_ #-} + quot = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u2; _NO_DEFLT_ } _N_ }, + rem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Number) (u1 :: Number) -> case _APP_ _CONSTM_ Integral quotRem (Number) [ u0, u1 ] of { _ALG_ _TUP_2 (u2 :: Number) (u3 :: Number) -> u3; _NO_DEFLT_ } _N_ }, + div = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + mod = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + quotRem = { _A_ 2 _U_ 22 _N_ _S_ "SL" _N_ _N_ }, + divMod = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ }, + even = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + odd = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + toInteger = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 C 6 \ (u0 :: Number) -> case u0 of { _ALG_ _ORIG_ Number I (u1 :: Integer) -> u1; _ORIG_ Number F (u2 :: Double) -> case u2 of { _ALG_ D# (u3 :: Double#) -> _APP_ _WRKR_ _SPEC_ _CONSTM_ RealFrac round (Double) [ (Integer) ] [ u3 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + toInt = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ } #-} instance Ix Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Number}}, ((Number, Number) -> [Number]), ((Number, Number) -> Number -> Int), ((Number, Number) -> Number -> Bool)] [_DFUN_ Ord (Number), _CONSTM_ Ix range (Number), _CONSTM_ Ix index (Number), _CONSTM_ Ix inRange (Number)] _N_ - range = _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - index = _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_, - inRange = _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "U(SA)S" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, + inRange = { _A_ 2 _U_ 12 _N_ _S_ "U(SL)S" {_A_ 3 _U_ 112 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Number}}, {{Text Number}}, (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number), (Number -> Number), (Number -> Number), (Integer -> Number), (Int -> Number)] [_DFUN_ Eq (Number), _DFUN_ Text (Number), _CONSTM_ Num (+) (Number), _CONSTM_ Num (-) (Number), _CONSTM_ Num (*) (Number), _CONSTM_ Num negate (Number), _CONSTM_ Num abs (Number), _CONSTM_ Num signum (Number), _CONSTM_ Num fromInteger (Number), _CONSTM_ Num fromInt (Number)] _N_ - (+) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (-) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (*) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_, - fromInteger = _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_, - fromInt = _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ #-} + (+) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (-) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (*) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Integer) -> _!_ _ORIG_ Number I [] [u0] _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Int) -> let {(u2 :: Integer) = case u0 of { _ALG_ I# (u1 :: Int#) -> _#_ int2Integer# [] [u1]; _NO_DEFLT_ }} in _!_ _ORIG_ Number I [] [u2] _N_ } #-} instance Ord Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Number}}, (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Bool), (Number -> Number -> Number), (Number -> Number -> Number), (Number -> Number -> _CMP_TAG)] [_DFUN_ Eq (Number), _CONSTM_ Ord (<) (Number), _CONSTM_ Ord (<=) (Number), _CONSTM_ Ord (>=) (Number), _CONSTM_ Ord (>) (Number), _CONSTM_ Ord max (Number), _CONSTM_ Ord min (Number), _CONSTM_ Ord _tagCmp (Number)] _N_ - (<) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - (<=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_, - (>=) = _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_, - (>) = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_, - _tagCmp = _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ #-} + (<) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + (<=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Number) (u1 :: Number) -> _APP_ _CONSTM_ Ord (<=) (Number) [ u1, u0 ] _N_ }, + (>) = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ } #-} instance Real Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 4 _!_ _TUP_3 [{{Num Number}}, {{Enum Number}}, (Number -> Ratio Integer)] [_DFUN_ Num (Number), _DFUN_ Enum (Number), _CONSTM_ Real toRational (Number)] _N_ - toRational = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + toRational = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} instance RealFloat Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{RealFrac Number}}, {{Floating Number}}, (Number -> Integer), (Number -> Int), (Number -> (Int, Int)), (Number -> (Integer, Int)), (Integer -> Int -> Number), (Number -> Int), (Number -> Number), (Int -> Number -> Number)] [_DFUN_ RealFrac (Number), _DFUN_ Floating (Number), _CONSTM_ RealFloat floatRadix (Number), _CONSTM_ RealFloat floatDigits (Number), _CONSTM_ RealFloat floatRange (Number), _CONSTM_ RealFloat decodeFloat (Number), _CONSTM_ RealFloat encodeFloat (Number), _CONSTM_ RealFloat exponent (Number), _CONSTM_ RealFloat significand (Number), _CONSTM_ RealFloat scaleFloat (Number)] _N_ - floatRadix = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _#_ int2Integer# [] [2#] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Number) -> _#_ int2Integer# [] [2#] _N_, - floatDigits = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_, - floatRange = _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_, - decodeFloat = _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_, - encodeFloat = _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_, - exponent = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - significand = _A_ 1 _U_ 1 _N_ _N_ _N_ _N_, - scaleFloat = _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} + floatRadix = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + floatDigits = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 2 _!_ I# [] [53#] _N_} _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Number) -> _!_ I# [] [53#] _N_ }, + floatRange = { _A_ 1 _U_ 0 _N_ _S_ "A" {_A_ 0 _N_ _N_ _N_ _N_ _N_} _N_ _N_ }, + decodeFloat = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + encodeFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(PPP)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, + exponent = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + significand = { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, + scaleFloat = { _A_ 2 _U_ 11 _N_ _S_ "U(P)S" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance RealFrac Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 8 _!_ _TUP_7 [{{Real Number}}, {{Fractional Number}}, _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> (a$z1, Number)), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1), _forall_ a$z1 =>{{Integral a$z1}} -> (Number -> a$z1)] [_DFUN_ Real (Number), _DFUN_ Fractional (Number), _CONSTM_ RealFrac properFraction (Number), _CONSTM_ RealFrac truncate (Number), _CONSTM_ RealFrac round (Number), _CONSTM_ RealFrac ceiling (Number), _CONSTM_ RealFrac floor (Number)] _N_ - properFraction = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - truncate = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - round = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - ceiling = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_, - floor = _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ #-} + properFraction = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + truncate = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + round = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + ceiling = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ }, + floor = { _A_ 1 _U_ 21 _N_ _N_ _N_ _N_ } #-} instance Text Number {-# GHC_PRAGMA _M_ Number {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Number, [Char])]), (Int -> Number -> [Char] -> [Char]), ([Char] -> [([Number], [Char])]), ([Number] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Number), _CONSTM_ Text showsPrec (Number), _CONSTM_ Text readList (Number), _CONSTM_ Text showList (Number)] _N_ - readsPrec = _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 02 _N_ _S_ "AL" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 22 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Parse.hi b/ghc/lib/hbc/Parse.hi index 9727fa58cc41c5a8c9d04f92c0187b4da1a888cb..47155a33a68685f1866995bbf717cacf78af6755 100644 --- a/ghc/lib/hbc/Parse.hi +++ b/ghc/lib/hbc/Parse.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parse where import PreludeMonadicIO(Either) import PreludeStdIO(Maybe) diff --git a/ghc/lib/hbc/Parse_mc.hi b/ghc/lib/hbc/Parse_mc.hi index 9727fa58cc41c5a8c9d04f92c0187b4da1a888cb..47155a33a68685f1866995bbf717cacf78af6755 100644 --- a/ghc/lib/hbc/Parse_mc.hi +++ b/ghc/lib/hbc/Parse_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parse where import PreludeMonadicIO(Either) import PreludeStdIO(Maybe) diff --git a/ghc/lib/hbc/Parse_mp.hi b/ghc/lib/hbc/Parse_mp.hi index 9727fa58cc41c5a8c9d04f92c0187b4da1a888cb..47155a33a68685f1866995bbf717cacf78af6755 100644 --- a/ghc/lib/hbc/Parse_mp.hi +++ b/ghc/lib/hbc/Parse_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parse where import PreludeMonadicIO(Either) import PreludeStdIO(Maybe) diff --git a/ghc/lib/hbc/Parse_p.hi b/ghc/lib/hbc/Parse_p.hi index 9727fa58cc41c5a8c9d04f92c0187b4da1a888cb..47155a33a68685f1866995bbf717cacf78af6755 100644 --- a/ghc/lib/hbc/Parse_p.hi +++ b/ghc/lib/hbc/Parse_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parse where import PreludeMonadicIO(Either) import PreludeStdIO(Maybe) diff --git a/ghc/lib/hbc/Parse_t.hi b/ghc/lib/hbc/Parse_t.hi index 9727fa58cc41c5a8c9d04f92c0187b4da1a888cb..47155a33a68685f1866995bbf717cacf78af6755 100644 --- a/ghc/lib/hbc/Parse_t.hi +++ b/ghc/lib/hbc/Parse_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parse where import PreludeMonadicIO(Either) import PreludeStdIO(Maybe) diff --git a/ghc/lib/hbc/Pretty.hi b/ghc/lib/hbc/Pretty.hi index 9f165c46d4ff7e60b423ae51720d918d96076913..34a4645c6a788c3483ab722a8afd5a53044df5fc 100644 --- a/ghc/lib/hbc/Pretty.hi +++ b/ghc/lib/hbc/Pretty.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where infixr 8 ^. infixr 8 ~. diff --git a/ghc/lib/hbc/Pretty_mc.hi b/ghc/lib/hbc/Pretty_mc.hi index 9f165c46d4ff7e60b423ae51720d918d96076913..34a4645c6a788c3483ab722a8afd5a53044df5fc 100644 --- a/ghc/lib/hbc/Pretty_mc.hi +++ b/ghc/lib/hbc/Pretty_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where infixr 8 ^. infixr 8 ~. diff --git a/ghc/lib/hbc/Pretty_mp.hi b/ghc/lib/hbc/Pretty_mp.hi index 9f165c46d4ff7e60b423ae51720d918d96076913..34a4645c6a788c3483ab722a8afd5a53044df5fc 100644 --- a/ghc/lib/hbc/Pretty_mp.hi +++ b/ghc/lib/hbc/Pretty_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where infixr 8 ^. infixr 8 ~. diff --git a/ghc/lib/hbc/Pretty_p.hi b/ghc/lib/hbc/Pretty_p.hi index 9f165c46d4ff7e60b423ae51720d918d96076913..34a4645c6a788c3483ab722a8afd5a53044df5fc 100644 --- a/ghc/lib/hbc/Pretty_p.hi +++ b/ghc/lib/hbc/Pretty_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where infixr 8 ^. infixr 8 ~. diff --git a/ghc/lib/hbc/Pretty_t.hi b/ghc/lib/hbc/Pretty_t.hi index 9f165c46d4ff7e60b423ae51720d918d96076913..34a4645c6a788c3483ab722a8afd5a53044df5fc 100644 --- a/ghc/lib/hbc/Pretty_t.hi +++ b/ghc/lib/hbc/Pretty_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Pretty where infixr 8 ^. infixr 8 ~. diff --git a/ghc/lib/hbc/QSort.hi b/ghc/lib/hbc/QSort.hi index d2016d643e1686ce2b8502eba9e65ac023607a9c..44ab1c563a0b7fb9640e28ca8ff6b3e51b269555 100644 --- a/ghc/lib/hbc/QSort.hi +++ b/ghc/lib/hbc/QSort.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface QSort where sort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} diff --git a/ghc/lib/hbc/QSort_mc.hi b/ghc/lib/hbc/QSort_mc.hi index d2016d643e1686ce2b8502eba9e65ac023607a9c..44ab1c563a0b7fb9640e28ca8ff6b3e51b269555 100644 --- a/ghc/lib/hbc/QSort_mc.hi +++ b/ghc/lib/hbc/QSort_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface QSort where sort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} diff --git a/ghc/lib/hbc/QSort_mp.hi b/ghc/lib/hbc/QSort_mp.hi index d2016d643e1686ce2b8502eba9e65ac023607a9c..44ab1c563a0b7fb9640e28ca8ff6b3e51b269555 100644 --- a/ghc/lib/hbc/QSort_mp.hi +++ b/ghc/lib/hbc/QSort_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface QSort where sort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} diff --git a/ghc/lib/hbc/QSort_p.hi b/ghc/lib/hbc/QSort_p.hi index d2016d643e1686ce2b8502eba9e65ac023607a9c..44ab1c563a0b7fb9640e28ca8ff6b3e51b269555 100644 --- a/ghc/lib/hbc/QSort_p.hi +++ b/ghc/lib/hbc/QSort_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface QSort where sort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} diff --git a/ghc/lib/hbc/QSort_t.hi b/ghc/lib/hbc/QSort_t.hi index d2016d643e1686ce2b8502eba9e65ac023607a9c..44ab1c563a0b7fb9640e28ca8ff6b3e51b269555 100644 --- a/ghc/lib/hbc/QSort_t.hi +++ b/ghc/lib/hbc/QSort_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface QSort where sort :: Ord a => [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _N_ #-} diff --git a/ghc/lib/hbc/Random.hi b/ghc/lib/hbc/Random.hi index cf2ee358f08ffc8687372d37fb13028d8add806d..2183a66d493f0060a07b8da9f003b9fe8be92057 100644 --- a/ghc/lib/hbc/Random.hi +++ b/ghc/lib/hbc/Random.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Random where normalRandomDoubles :: Int -> Int -> [Double] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} diff --git a/ghc/lib/hbc/Random_mc.hi b/ghc/lib/hbc/Random_mc.hi index cf2ee358f08ffc8687372d37fb13028d8add806d..2183a66d493f0060a07b8da9f003b9fe8be92057 100644 --- a/ghc/lib/hbc/Random_mc.hi +++ b/ghc/lib/hbc/Random_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Random where normalRandomDoubles :: Int -> Int -> [Double] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} diff --git a/ghc/lib/hbc/Random_mp.hi b/ghc/lib/hbc/Random_mp.hi index cf2ee358f08ffc8687372d37fb13028d8add806d..2183a66d493f0060a07b8da9f003b9fe8be92057 100644 --- a/ghc/lib/hbc/Random_mp.hi +++ b/ghc/lib/hbc/Random_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Random where normalRandomDoubles :: Int -> Int -> [Double] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} diff --git a/ghc/lib/hbc/Random_p.hi b/ghc/lib/hbc/Random_p.hi index cf2ee358f08ffc8687372d37fb13028d8add806d..2183a66d493f0060a07b8da9f003b9fe8be92057 100644 --- a/ghc/lib/hbc/Random_p.hi +++ b/ghc/lib/hbc/Random_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Random where normalRandomDoubles :: Int -> Int -> [Double] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} diff --git a/ghc/lib/hbc/Random_t.hi b/ghc/lib/hbc/Random_t.hi index cf2ee358f08ffc8687372d37fb13028d8add806d..2183a66d493f0060a07b8da9f003b9fe8be92057 100644 --- a/ghc/lib/hbc/Random_t.hi +++ b/ghc/lib/hbc/Random_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Random where normalRandomDoubles :: Int -> Int -> [Double] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} diff --git a/ghc/lib/hbc/SimpleLex.hi b/ghc/lib/hbc/SimpleLex.hi index 61e32bf7ca5632650f6b7e15d4aa0a1b8ea80ed6..4763cf9228d2d68a8add246a145c286c9208d778 100644 --- a/ghc/lib/hbc/SimpleLex.hi +++ b/ghc/lib/hbc/SimpleLex.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface SimpleLex where simpleLex :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} diff --git a/ghc/lib/hbc/SimpleLex_mc.hi b/ghc/lib/hbc/SimpleLex_mc.hi index 61e32bf7ca5632650f6b7e15d4aa0a1b8ea80ed6..4763cf9228d2d68a8add246a145c286c9208d778 100644 --- a/ghc/lib/hbc/SimpleLex_mc.hi +++ b/ghc/lib/hbc/SimpleLex_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface SimpleLex where simpleLex :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} diff --git a/ghc/lib/hbc/SimpleLex_mp.hi b/ghc/lib/hbc/SimpleLex_mp.hi index 61e32bf7ca5632650f6b7e15d4aa0a1b8ea80ed6..4763cf9228d2d68a8add246a145c286c9208d778 100644 --- a/ghc/lib/hbc/SimpleLex_mp.hi +++ b/ghc/lib/hbc/SimpleLex_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface SimpleLex where simpleLex :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} diff --git a/ghc/lib/hbc/SimpleLex_p.hi b/ghc/lib/hbc/SimpleLex_p.hi index 61e32bf7ca5632650f6b7e15d4aa0a1b8ea80ed6..4763cf9228d2d68a8add246a145c286c9208d778 100644 --- a/ghc/lib/hbc/SimpleLex_p.hi +++ b/ghc/lib/hbc/SimpleLex_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface SimpleLex where simpleLex :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} diff --git a/ghc/lib/hbc/SimpleLex_t.hi b/ghc/lib/hbc/SimpleLex_t.hi index 61e32bf7ca5632650f6b7e15d4aa0a1b8ea80ed6..4763cf9228d2d68a8add246a145c286c9208d778 100644 --- a/ghc/lib/hbc/SimpleLex_t.hi +++ b/ghc/lib/hbc/SimpleLex_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface SimpleLex where simpleLex :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} diff --git a/ghc/lib/hbc/Time.hi b/ghc/lib/hbc/Time.hi index 9203e3b14b012e862422f82d11b472c5b29064ce..eda33b65c85abc56793c0e0fca40ecca8c53a417 100644 --- a/ghc/lib/hbc/Time.hi +++ b/ghc/lib/hbc/Time.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Time where data Time = Time Int Int Int Int Int Int Double Int dblToTime :: Double -> Time @@ -9,21 +9,21 @@ timeToString :: Time -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(P)LLLLLLL)" _N_ _N_ #-} instance Eq Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Time -> Time -> Bool), (Time -> Time -> Bool)] [_CONSTM_ Eq (==) (Time), _CONSTM_ Eq (/=) (Time)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Ord Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Time}}, (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Time), (Time -> Time -> Time), (Time -> Time -> _CMP_TAG)] [_DFUN_ Eq (Time), _CONSTM_ Ord (<) (Time), _CONSTM_ Ord (<=) (Time), _CONSTM_ Ord (>=) (Time), _CONSTM_ Ord (>) (Time), _CONSTM_ Ord max (Time), _CONSTM_ Ord min (Time), _CONSTM_ Ord _tagCmp (Time)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Text Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Time, [Char])]), (Int -> Time -> [Char] -> [Char]), ([Char] -> [([Time], [Char])]), ([Time] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Time), _CONSTM_ Text showsPrec (Time), _CONSTM_ Text readList (Time), _CONSTM_ Text showList (Time)] _N_ - readsPrec = _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Time_mc.hi b/ghc/lib/hbc/Time_mc.hi index 9203e3b14b012e862422f82d11b472c5b29064ce..eda33b65c85abc56793c0e0fca40ecca8c53a417 100644 --- a/ghc/lib/hbc/Time_mc.hi +++ b/ghc/lib/hbc/Time_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Time where data Time = Time Int Int Int Int Int Int Double Int dblToTime :: Double -> Time @@ -9,21 +9,21 @@ timeToString :: Time -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(P)LLLLLLL)" _N_ _N_ #-} instance Eq Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Time -> Time -> Bool), (Time -> Time -> Bool)] [_CONSTM_ Eq (==) (Time), _CONSTM_ Eq (/=) (Time)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Ord Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Time}}, (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Time), (Time -> Time -> Time), (Time -> Time -> _CMP_TAG)] [_DFUN_ Eq (Time), _CONSTM_ Ord (<) (Time), _CONSTM_ Ord (<=) (Time), _CONSTM_ Ord (>=) (Time), _CONSTM_ Ord (>) (Time), _CONSTM_ Ord max (Time), _CONSTM_ Ord min (Time), _CONSTM_ Ord _tagCmp (Time)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Text Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Time, [Char])]), (Int -> Time -> [Char] -> [Char]), ([Char] -> [([Time], [Char])]), ([Time] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Time), _CONSTM_ Text showsPrec (Time), _CONSTM_ Text readList (Time), _CONSTM_ Text showList (Time)] _N_ - readsPrec = _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Time_mp.hi b/ghc/lib/hbc/Time_mp.hi index 9203e3b14b012e862422f82d11b472c5b29064ce..eda33b65c85abc56793c0e0fca40ecca8c53a417 100644 --- a/ghc/lib/hbc/Time_mp.hi +++ b/ghc/lib/hbc/Time_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Time where data Time = Time Int Int Int Int Int Int Double Int dblToTime :: Double -> Time @@ -9,21 +9,21 @@ timeToString :: Time -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(P)LLLLLLL)" _N_ _N_ #-} instance Eq Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Time -> Time -> Bool), (Time -> Time -> Bool)] [_CONSTM_ Eq (==) (Time), _CONSTM_ Eq (/=) (Time)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Ord Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Time}}, (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Time), (Time -> Time -> Time), (Time -> Time -> _CMP_TAG)] [_DFUN_ Eq (Time), _CONSTM_ Ord (<) (Time), _CONSTM_ Ord (<=) (Time), _CONSTM_ Ord (>=) (Time), _CONSTM_ Ord (>) (Time), _CONSTM_ Ord max (Time), _CONSTM_ Ord min (Time), _CONSTM_ Ord _tagCmp (Time)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Text Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Time, [Char])]), (Int -> Time -> [Char] -> [Char]), ([Char] -> [([Time], [Char])]), ([Time] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Time), _CONSTM_ Text showsPrec (Time), _CONSTM_ Text readList (Time), _CONSTM_ Text showList (Time)] _N_ - readsPrec = _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Time_p.hi b/ghc/lib/hbc/Time_p.hi index 9203e3b14b012e862422f82d11b472c5b29064ce..eda33b65c85abc56793c0e0fca40ecca8c53a417 100644 --- a/ghc/lib/hbc/Time_p.hi +++ b/ghc/lib/hbc/Time_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Time where data Time = Time Int Int Int Int Int Int Double Int dblToTime :: Double -> Time @@ -9,21 +9,21 @@ timeToString :: Time -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(P)LLLLLLL)" _N_ _N_ #-} instance Eq Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Time -> Time -> Bool), (Time -> Time -> Bool)] [_CONSTM_ Eq (==) (Time), _CONSTM_ Eq (/=) (Time)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Ord Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Time}}, (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Time), (Time -> Time -> Time), (Time -> Time -> _CMP_TAG)] [_DFUN_ Eq (Time), _CONSTM_ Ord (<) (Time), _CONSTM_ Ord (<=) (Time), _CONSTM_ Ord (>=) (Time), _CONSTM_ Ord (>) (Time), _CONSTM_ Ord max (Time), _CONSTM_ Ord min (Time), _CONSTM_ Ord _tagCmp (Time)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Text Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Time, [Char])]), (Int -> Time -> [Char] -> [Char]), ([Char] -> [([Time], [Char])]), ([Time] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Time), _CONSTM_ Text showsPrec (Time), _CONSTM_ Text readList (Time), _CONSTM_ Text showList (Time)] _N_ - readsPrec = _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Time_t.hi b/ghc/lib/hbc/Time_t.hi index 9203e3b14b012e862422f82d11b472c5b29064ce..eda33b65c85abc56793c0e0fca40ecca8c53a417 100644 --- a/ghc/lib/hbc/Time_t.hi +++ b/ghc/lib/hbc/Time_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Time where data Time = Time Int Int Int Int Int Int Double Int dblToTime :: Double -> Time @@ -9,21 +9,21 @@ timeToString :: Time -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(P)LLLLLLL)" _N_ _N_ #-} instance Eq Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Time -> Time -> Bool), (Time -> Time -> Bool)] [_CONSTM_ Eq (==) (Time), _CONSTM_ Eq (/=) (Time)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Ord Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Time}}, (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Bool), (Time -> Time -> Time), (Time -> Time -> Time), (Time -> Time -> _CMP_TAG)] [_DFUN_ Eq (Time), _CONSTM_ Ord (<) (Time), _CONSTM_ Ord (<=) (Time), _CONSTM_ Ord (>=) (Time), _CONSTM_ Ord (>) (Time), _CONSTM_ Ord max (Time), _CONSTM_ Ord min (Time), _CONSTM_ Ord _tagCmp (Time)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - max = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - min = _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + max = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + min = { _A_ 2 _U_ 22 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)LLLLLLL)U(U(P)LLLLLLL)" _N_ _N_ } #-} instance Text Time {-# GHC_PRAGMA _M_ Time {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Time, [Char])]), (Int -> Time -> [Char] -> [Char]), ([Char] -> [([Time], [Char])]), ([Time] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Time), _CONSTM_ Text showsPrec (Time), _CONSTM_ Text readList (Time), _CONSTM_ Text showList (Time)] _N_ - readsPrec = _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - showsPrec = _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 112 _N_ _S_ "LU(LLLLLLLL)" _N_ _N_ }, + readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, + showList = { _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/hbc/Trace.hi b/ghc/lib/hbc/Trace.hi index 742622829fc9ac0feb39ff23ff0256bfe81999a3..3745833bfd96dedc91c3c30169c81ca767f67dd6 100644 --- a/ghc/lib/hbc/Trace.hi +++ b/ghc/lib/hbc/Trace.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Trace where trace :: [Char] -> a -> a {-# GHC_PRAGMA _A_ 0 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _trace _N_ #-} diff --git a/ghc/lib/hbc/Trace_mc.hi b/ghc/lib/hbc/Trace_mc.hi index 742622829fc9ac0feb39ff23ff0256bfe81999a3..3745833bfd96dedc91c3c30169c81ca767f67dd6 100644 --- a/ghc/lib/hbc/Trace_mc.hi +++ b/ghc/lib/hbc/Trace_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Trace where trace :: [Char] -> a -> a {-# GHC_PRAGMA _A_ 0 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _trace _N_ #-} diff --git a/ghc/lib/hbc/Trace_mp.hi b/ghc/lib/hbc/Trace_mp.hi index 742622829fc9ac0feb39ff23ff0256bfe81999a3..3745833bfd96dedc91c3c30169c81ca767f67dd6 100644 --- a/ghc/lib/hbc/Trace_mp.hi +++ b/ghc/lib/hbc/Trace_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Trace where trace :: [Char] -> a -> a {-# GHC_PRAGMA _A_ 0 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _trace _N_ #-} diff --git a/ghc/lib/hbc/Trace_p.hi b/ghc/lib/hbc/Trace_p.hi index 742622829fc9ac0feb39ff23ff0256bfe81999a3..3745833bfd96dedc91c3c30169c81ca767f67dd6 100644 --- a/ghc/lib/hbc/Trace_p.hi +++ b/ghc/lib/hbc/Trace_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Trace where trace :: [Char] -> a -> a {-# GHC_PRAGMA _A_ 0 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _trace _N_ #-} diff --git a/ghc/lib/hbc/Trace_t.hi b/ghc/lib/hbc/Trace_t.hi index 742622829fc9ac0feb39ff23ff0256bfe81999a3..3745833bfd96dedc91c3c30169c81ca767f67dd6 100644 --- a/ghc/lib/hbc/Trace_t.hi +++ b/ghc/lib/hbc/Trace_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Trace where trace :: [Char] -> a -> a {-# GHC_PRAGMA _A_ 0 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _trace _N_ #-} diff --git a/ghc/lib/hbc/Word.hi b/ghc/lib/hbc/Word.hi index c994512c122dd53d5302cbb0257a87dfb5dd6952..d308daee8ae31a9bb57db1ab814a4293fda6a2a9 100644 --- a/ghc/lib/hbc/Word.hi +++ b/ghc/lib/hbc/Word.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Word where infixl 7 `bitAnd` infixl 8 `bitLsh` @@ -8,31 +8,31 @@ infixl 6 `bitXor` class Bits a where bitAnd :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(SAAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u2; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitAnd\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitOr :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(ASAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitOr\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitXor :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AASAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u4; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitXor\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitCompl :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAASAAAAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u5; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitCompl\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bitRsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAASAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u6; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitRsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitLsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAAASAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u7; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitLsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitSwap :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAASAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u8; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitSwap\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bit0 :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AAAAAAASA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u9; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Bits u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DWord.Bits.bit0\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} bitSize :: a -> Int {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAAAAS)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> ua; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> Int) } [ _NOREP_S_ "%DWord.Bits.bitSize\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} data Byte {-# GHC_PRAGMA Byte Word# #-} data Short {-# GHC_PRAGMA Short Word# #-} data Word {-# GHC_PRAGMA Word Word# #-} @@ -50,122 +50,122 @@ wordToShorts :: Word -> [Short] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} instance Eq Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Byte -> Byte -> Bool), (Byte -> Byte -> Bool)] [_CONSTM_ Eq (==) (Byte), _CONSTM_ Eq (/=) (Byte)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Short -> Short -> Bool), (Short -> Short -> Bool)] [_CONSTM_ Eq (==) (Short), _CONSTM_ Eq (/=) (Short)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Word -> Word -> Bool), (Word -> Word -> Bool)] [_CONSTM_ Eq (==) (Word), _CONSTM_ Eq (/=) (Word)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Byte}}, {{Text Byte}}, (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Integer -> Byte), (Int -> Byte)] [_DFUN_ Eq (Byte), _DFUN_ Text (Byte), _CONSTM_ Num (+) (Byte), _CONSTM_ Num (-) (Byte), _CONSTM_ Num (*) (Byte), _CONSTM_ Num negate (Byte), _CONSTM_ Num abs (Byte), _CONSTM_ Num signum (Byte), _CONSTM_ Num fromInteger (Byte), _CONSTM_ Num fromInt (Byte)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Short}}, {{Text Short}}, (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Short), (Short -> Short), (Integer -> Short), (Int -> Short)] [_DFUN_ Eq (Short), _DFUN_ Text (Short), _CONSTM_ Num (+) (Short), _CONSTM_ Num (-) (Short), _CONSTM_ Num (*) (Short), _CONSTM_ Num negate (Short), _CONSTM_ Num abs (Short), _CONSTM_ Num signum (Short), _CONSTM_ Num fromInteger (Short), _CONSTM_ Num fromInt (Short)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Word}}, {{Text Word}}, (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Word), (Word -> Word), (Integer -> Word), (Int -> Word)] [_DFUN_ Eq (Word), _DFUN_ Text (Word), _CONSTM_ Num (+) (Word), _CONSTM_ Num (-) (Word), _CONSTM_ Num (*) (Word), _CONSTM_ Num negate (Word), _CONSTM_ Num abs (Word), _CONSTM_ Num signum (Word), _CONSTM_ Num fromInteger (Word), _CONSTM_ Num fromInt (Word)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ } #-} instance Ord Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Byte}}, (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> _CMP_TAG)] [_DFUN_ Eq (Byte), _CONSTM_ Ord (<) (Byte), _CONSTM_ Ord (<=) (Byte), _CONSTM_ Ord (>=) (Byte), _CONSTM_ Ord (>) (Byte), _CONSTM_ Ord max (Byte), _CONSTM_ Ord min (Byte), _CONSTM_ Ord _tagCmp (Byte)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Short}}, (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> _CMP_TAG)] [_DFUN_ Eq (Short), _CONSTM_ Ord (<) (Short), _CONSTM_ Ord (<=) (Short), _CONSTM_ Ord (>=) (Short), _CONSTM_ Ord (>) (Short), _CONSTM_ Ord max (Short), _CONSTM_ Ord min (Short), _CONSTM_ Ord _tagCmp (Short)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Word}}, (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> _CMP_TAG)] [_DFUN_ Eq (Word), _CONSTM_ Ord (<) (Word), _CONSTM_ Ord (<=) (Word), _CONSTM_ Ord (>=) (Word), _CONSTM_ Ord (>) (Word), _CONSTM_ Ord max (Word), _CONSTM_ Ord min (Word), _CONSTM_ Ord _tagCmp (Word)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Byte, [Char])]), (Int -> Byte -> [Char] -> [Char]), ([Char] -> [([Byte], [Char])]), ([Byte] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Byte), _CONSTM_ Text showsPrec (Byte), _CONSTM_ Text readList (Byte), _CONSTM_ Text showList (Byte)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Byte, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Short, [Char])]), (Int -> Short -> [Char] -> [Char]), ([Char] -> [([Short], [Char])]), ([Short] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Short), _CONSTM_ Text showsPrec (Short), _CONSTM_ Text readList (Short), _CONSTM_ Text showList (Short)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Short, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Word, [Char])]), (Int -> Word -> [Char] -> [Char]), ([Char] -> [([Word], [Char])]), ([Word] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Word), _CONSTM_ Text showsPrec (Word), _CONSTM_ Text readList (Word), _CONSTM_ Text showList (Word)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Word, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Bits Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Int -> Byte), (Byte -> Int -> Byte), (Byte -> Byte), Byte, (Byte -> Int)] [_CONSTM_ Bits bitAnd (Byte), _CONSTM_ Bits bitOr (Byte), _CONSTM_ Bits bitXor (Byte), _CONSTM_ Bits bitCompl (Byte), _CONSTM_ Bits bitRsh (Byte), _CONSTM_ Bits bitLsh (Byte), _CONSTM_ Bits bitSwap (Byte), _CONSTM_ Bits bit0 (Byte), _CONSTM_ Bits bitSize (Byte)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _APP_ _TYAPP_ error { Byte } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Byte [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ } #-} instance Bits Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Int -> Short), (Short -> Int -> Short), (Short -> Short), Short, (Short -> Int)] [_CONSTM_ Bits bitAnd (Short), _CONSTM_ Bits bitOr (Short), _CONSTM_ Bits bitXor (Short), _CONSTM_ Bits bitCompl (Short), _CONSTM_ Bits bitRsh (Short), _CONSTM_ Bits bitLsh (Short), _CONSTM_ Bits bitSwap (Short), _CONSTM_ Bits bit0 (Short), _CONSTM_ Bits bitSize (Short)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _APP_ _TYAPP_ error { Short } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Short [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ } #-} instance Bits Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Int -> Word), (Word -> Int -> Word), (Word -> Word), Word, (Word -> Int)] [_CONSTM_ Bits bitAnd (Word), _CONSTM_ Bits bitOr (Word), _CONSTM_ Bits bitXor (Word), _CONSTM_ Bits bitCompl (Word), _CONSTM_ Bits bitRsh (Word), _CONSTM_ Bits bitLsh (Word), _CONSTM_ Bits bitSwap (Word), _CONSTM_ Bits bit0 (Word), _CONSTM_ Bits bitSize (Word)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _APP_ _TYAPP_ error { Word } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Word [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ } #-} diff --git a/ghc/lib/hbc/Word_mc.hi b/ghc/lib/hbc/Word_mc.hi index c994512c122dd53d5302cbb0257a87dfb5dd6952..d308daee8ae31a9bb57db1ab814a4293fda6a2a9 100644 --- a/ghc/lib/hbc/Word_mc.hi +++ b/ghc/lib/hbc/Word_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Word where infixl 7 `bitAnd` infixl 8 `bitLsh` @@ -8,31 +8,31 @@ infixl 6 `bitXor` class Bits a where bitAnd :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(SAAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u2; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitAnd\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitOr :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(ASAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitOr\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitXor :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AASAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u4; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitXor\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitCompl :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAASAAAAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u5; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitCompl\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bitRsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAASAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u6; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitRsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitLsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAAASAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u7; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitLsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitSwap :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAASAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u8; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitSwap\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bit0 :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AAAAAAASA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u9; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Bits u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DWord.Bits.bit0\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} bitSize :: a -> Int {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAAAAS)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> ua; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> Int) } [ _NOREP_S_ "%DWord.Bits.bitSize\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} data Byte {-# GHC_PRAGMA Byte Word# #-} data Short {-# GHC_PRAGMA Short Word# #-} data Word {-# GHC_PRAGMA Word Word# #-} @@ -50,122 +50,122 @@ wordToShorts :: Word -> [Short] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} instance Eq Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Byte -> Byte -> Bool), (Byte -> Byte -> Bool)] [_CONSTM_ Eq (==) (Byte), _CONSTM_ Eq (/=) (Byte)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Short -> Short -> Bool), (Short -> Short -> Bool)] [_CONSTM_ Eq (==) (Short), _CONSTM_ Eq (/=) (Short)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Word -> Word -> Bool), (Word -> Word -> Bool)] [_CONSTM_ Eq (==) (Word), _CONSTM_ Eq (/=) (Word)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Byte}}, {{Text Byte}}, (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Integer -> Byte), (Int -> Byte)] [_DFUN_ Eq (Byte), _DFUN_ Text (Byte), _CONSTM_ Num (+) (Byte), _CONSTM_ Num (-) (Byte), _CONSTM_ Num (*) (Byte), _CONSTM_ Num negate (Byte), _CONSTM_ Num abs (Byte), _CONSTM_ Num signum (Byte), _CONSTM_ Num fromInteger (Byte), _CONSTM_ Num fromInt (Byte)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Short}}, {{Text Short}}, (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Short), (Short -> Short), (Integer -> Short), (Int -> Short)] [_DFUN_ Eq (Short), _DFUN_ Text (Short), _CONSTM_ Num (+) (Short), _CONSTM_ Num (-) (Short), _CONSTM_ Num (*) (Short), _CONSTM_ Num negate (Short), _CONSTM_ Num abs (Short), _CONSTM_ Num signum (Short), _CONSTM_ Num fromInteger (Short), _CONSTM_ Num fromInt (Short)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Word}}, {{Text Word}}, (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Word), (Word -> Word), (Integer -> Word), (Int -> Word)] [_DFUN_ Eq (Word), _DFUN_ Text (Word), _CONSTM_ Num (+) (Word), _CONSTM_ Num (-) (Word), _CONSTM_ Num (*) (Word), _CONSTM_ Num negate (Word), _CONSTM_ Num abs (Word), _CONSTM_ Num signum (Word), _CONSTM_ Num fromInteger (Word), _CONSTM_ Num fromInt (Word)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ } #-} instance Ord Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Byte}}, (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> _CMP_TAG)] [_DFUN_ Eq (Byte), _CONSTM_ Ord (<) (Byte), _CONSTM_ Ord (<=) (Byte), _CONSTM_ Ord (>=) (Byte), _CONSTM_ Ord (>) (Byte), _CONSTM_ Ord max (Byte), _CONSTM_ Ord min (Byte), _CONSTM_ Ord _tagCmp (Byte)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Short}}, (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> _CMP_TAG)] [_DFUN_ Eq (Short), _CONSTM_ Ord (<) (Short), _CONSTM_ Ord (<=) (Short), _CONSTM_ Ord (>=) (Short), _CONSTM_ Ord (>) (Short), _CONSTM_ Ord max (Short), _CONSTM_ Ord min (Short), _CONSTM_ Ord _tagCmp (Short)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Word}}, (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> _CMP_TAG)] [_DFUN_ Eq (Word), _CONSTM_ Ord (<) (Word), _CONSTM_ Ord (<=) (Word), _CONSTM_ Ord (>=) (Word), _CONSTM_ Ord (>) (Word), _CONSTM_ Ord max (Word), _CONSTM_ Ord min (Word), _CONSTM_ Ord _tagCmp (Word)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Byte, [Char])]), (Int -> Byte -> [Char] -> [Char]), ([Char] -> [([Byte], [Char])]), ([Byte] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Byte), _CONSTM_ Text showsPrec (Byte), _CONSTM_ Text readList (Byte), _CONSTM_ Text showList (Byte)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Byte, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Short, [Char])]), (Int -> Short -> [Char] -> [Char]), ([Char] -> [([Short], [Char])]), ([Short] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Short), _CONSTM_ Text showsPrec (Short), _CONSTM_ Text readList (Short), _CONSTM_ Text showList (Short)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Short, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Word, [Char])]), (Int -> Word -> [Char] -> [Char]), ([Char] -> [([Word], [Char])]), ([Word] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Word), _CONSTM_ Text showsPrec (Word), _CONSTM_ Text readList (Word), _CONSTM_ Text showList (Word)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Word, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Bits Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Int -> Byte), (Byte -> Int -> Byte), (Byte -> Byte), Byte, (Byte -> Int)] [_CONSTM_ Bits bitAnd (Byte), _CONSTM_ Bits bitOr (Byte), _CONSTM_ Bits bitXor (Byte), _CONSTM_ Bits bitCompl (Byte), _CONSTM_ Bits bitRsh (Byte), _CONSTM_ Bits bitLsh (Byte), _CONSTM_ Bits bitSwap (Byte), _CONSTM_ Bits bit0 (Byte), _CONSTM_ Bits bitSize (Byte)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _APP_ _TYAPP_ error { Byte } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Byte [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ } #-} instance Bits Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Int -> Short), (Short -> Int -> Short), (Short -> Short), Short, (Short -> Int)] [_CONSTM_ Bits bitAnd (Short), _CONSTM_ Bits bitOr (Short), _CONSTM_ Bits bitXor (Short), _CONSTM_ Bits bitCompl (Short), _CONSTM_ Bits bitRsh (Short), _CONSTM_ Bits bitLsh (Short), _CONSTM_ Bits bitSwap (Short), _CONSTM_ Bits bit0 (Short), _CONSTM_ Bits bitSize (Short)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _APP_ _TYAPP_ error { Short } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Short [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ } #-} instance Bits Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Int -> Word), (Word -> Int -> Word), (Word -> Word), Word, (Word -> Int)] [_CONSTM_ Bits bitAnd (Word), _CONSTM_ Bits bitOr (Word), _CONSTM_ Bits bitXor (Word), _CONSTM_ Bits bitCompl (Word), _CONSTM_ Bits bitRsh (Word), _CONSTM_ Bits bitLsh (Word), _CONSTM_ Bits bitSwap (Word), _CONSTM_ Bits bit0 (Word), _CONSTM_ Bits bitSize (Word)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _APP_ _TYAPP_ error { Word } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Word [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ } #-} diff --git a/ghc/lib/hbc/Word_mp.hi b/ghc/lib/hbc/Word_mp.hi index c994512c122dd53d5302cbb0257a87dfb5dd6952..d308daee8ae31a9bb57db1ab814a4293fda6a2a9 100644 --- a/ghc/lib/hbc/Word_mp.hi +++ b/ghc/lib/hbc/Word_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Word where infixl 7 `bitAnd` infixl 8 `bitLsh` @@ -8,31 +8,31 @@ infixl 6 `bitXor` class Bits a where bitAnd :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(SAAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u2; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitAnd\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitOr :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(ASAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitOr\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitXor :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AASAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u4; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitXor\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitCompl :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAASAAAAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u5; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitCompl\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bitRsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAASAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u6; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitRsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitLsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAAASAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u7; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitLsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitSwap :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAASAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u8; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitSwap\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bit0 :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AAAAAAASA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u9; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Bits u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DWord.Bits.bit0\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} bitSize :: a -> Int {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAAAAS)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> ua; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> Int) } [ _NOREP_S_ "%DWord.Bits.bitSize\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} data Byte {-# GHC_PRAGMA Byte Word# #-} data Short {-# GHC_PRAGMA Short Word# #-} data Word {-# GHC_PRAGMA Word Word# #-} @@ -50,122 +50,122 @@ wordToShorts :: Word -> [Short] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} instance Eq Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Byte -> Byte -> Bool), (Byte -> Byte -> Bool)] [_CONSTM_ Eq (==) (Byte), _CONSTM_ Eq (/=) (Byte)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Short -> Short -> Bool), (Short -> Short -> Bool)] [_CONSTM_ Eq (==) (Short), _CONSTM_ Eq (/=) (Short)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Word -> Word -> Bool), (Word -> Word -> Bool)] [_CONSTM_ Eq (==) (Word), _CONSTM_ Eq (/=) (Word)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Byte}}, {{Text Byte}}, (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Integer -> Byte), (Int -> Byte)] [_DFUN_ Eq (Byte), _DFUN_ Text (Byte), _CONSTM_ Num (+) (Byte), _CONSTM_ Num (-) (Byte), _CONSTM_ Num (*) (Byte), _CONSTM_ Num negate (Byte), _CONSTM_ Num abs (Byte), _CONSTM_ Num signum (Byte), _CONSTM_ Num fromInteger (Byte), _CONSTM_ Num fromInt (Byte)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Short}}, {{Text Short}}, (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Short), (Short -> Short), (Integer -> Short), (Int -> Short)] [_DFUN_ Eq (Short), _DFUN_ Text (Short), _CONSTM_ Num (+) (Short), _CONSTM_ Num (-) (Short), _CONSTM_ Num (*) (Short), _CONSTM_ Num negate (Short), _CONSTM_ Num abs (Short), _CONSTM_ Num signum (Short), _CONSTM_ Num fromInteger (Short), _CONSTM_ Num fromInt (Short)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Word}}, {{Text Word}}, (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Word), (Word -> Word), (Integer -> Word), (Int -> Word)] [_DFUN_ Eq (Word), _DFUN_ Text (Word), _CONSTM_ Num (+) (Word), _CONSTM_ Num (-) (Word), _CONSTM_ Num (*) (Word), _CONSTM_ Num negate (Word), _CONSTM_ Num abs (Word), _CONSTM_ Num signum (Word), _CONSTM_ Num fromInteger (Word), _CONSTM_ Num fromInt (Word)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ } #-} instance Ord Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Byte}}, (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> _CMP_TAG)] [_DFUN_ Eq (Byte), _CONSTM_ Ord (<) (Byte), _CONSTM_ Ord (<=) (Byte), _CONSTM_ Ord (>=) (Byte), _CONSTM_ Ord (>) (Byte), _CONSTM_ Ord max (Byte), _CONSTM_ Ord min (Byte), _CONSTM_ Ord _tagCmp (Byte)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Short}}, (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> _CMP_TAG)] [_DFUN_ Eq (Short), _CONSTM_ Ord (<) (Short), _CONSTM_ Ord (<=) (Short), _CONSTM_ Ord (>=) (Short), _CONSTM_ Ord (>) (Short), _CONSTM_ Ord max (Short), _CONSTM_ Ord min (Short), _CONSTM_ Ord _tagCmp (Short)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Word}}, (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> _CMP_TAG)] [_DFUN_ Eq (Word), _CONSTM_ Ord (<) (Word), _CONSTM_ Ord (<=) (Word), _CONSTM_ Ord (>=) (Word), _CONSTM_ Ord (>) (Word), _CONSTM_ Ord max (Word), _CONSTM_ Ord min (Word), _CONSTM_ Ord _tagCmp (Word)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Byte, [Char])]), (Int -> Byte -> [Char] -> [Char]), ([Char] -> [([Byte], [Char])]), ([Byte] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Byte), _CONSTM_ Text showsPrec (Byte), _CONSTM_ Text readList (Byte), _CONSTM_ Text showList (Byte)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Byte, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Short, [Char])]), (Int -> Short -> [Char] -> [Char]), ([Char] -> [([Short], [Char])]), ([Short] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Short), _CONSTM_ Text showsPrec (Short), _CONSTM_ Text readList (Short), _CONSTM_ Text showList (Short)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Short, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Word, [Char])]), (Int -> Word -> [Char] -> [Char]), ([Char] -> [([Word], [Char])]), ([Word] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Word), _CONSTM_ Text showsPrec (Word), _CONSTM_ Text readList (Word), _CONSTM_ Text showList (Word)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Word, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Bits Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Int -> Byte), (Byte -> Int -> Byte), (Byte -> Byte), Byte, (Byte -> Int)] [_CONSTM_ Bits bitAnd (Byte), _CONSTM_ Bits bitOr (Byte), _CONSTM_ Bits bitXor (Byte), _CONSTM_ Bits bitCompl (Byte), _CONSTM_ Bits bitRsh (Byte), _CONSTM_ Bits bitLsh (Byte), _CONSTM_ Bits bitSwap (Byte), _CONSTM_ Bits bit0 (Byte), _CONSTM_ Bits bitSize (Byte)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _APP_ _TYAPP_ error { Byte } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Byte [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ } #-} instance Bits Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Int -> Short), (Short -> Int -> Short), (Short -> Short), Short, (Short -> Int)] [_CONSTM_ Bits bitAnd (Short), _CONSTM_ Bits bitOr (Short), _CONSTM_ Bits bitXor (Short), _CONSTM_ Bits bitCompl (Short), _CONSTM_ Bits bitRsh (Short), _CONSTM_ Bits bitLsh (Short), _CONSTM_ Bits bitSwap (Short), _CONSTM_ Bits bit0 (Short), _CONSTM_ Bits bitSize (Short)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _APP_ _TYAPP_ error { Short } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Short [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ } #-} instance Bits Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Int -> Word), (Word -> Int -> Word), (Word -> Word), Word, (Word -> Int)] [_CONSTM_ Bits bitAnd (Word), _CONSTM_ Bits bitOr (Word), _CONSTM_ Bits bitXor (Word), _CONSTM_ Bits bitCompl (Word), _CONSTM_ Bits bitRsh (Word), _CONSTM_ Bits bitLsh (Word), _CONSTM_ Bits bitSwap (Word), _CONSTM_ Bits bit0 (Word), _CONSTM_ Bits bitSize (Word)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _APP_ _TYAPP_ error { Word } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Word [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ } #-} diff --git a/ghc/lib/hbc/Word_p.hi b/ghc/lib/hbc/Word_p.hi index c994512c122dd53d5302cbb0257a87dfb5dd6952..d308daee8ae31a9bb57db1ab814a4293fda6a2a9 100644 --- a/ghc/lib/hbc/Word_p.hi +++ b/ghc/lib/hbc/Word_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Word where infixl 7 `bitAnd` infixl 8 `bitLsh` @@ -8,31 +8,31 @@ infixl 6 `bitXor` class Bits a where bitAnd :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(SAAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u2; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitAnd\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitOr :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(ASAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitOr\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitXor :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AASAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u4; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitXor\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitCompl :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAASAAAAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u5; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitCompl\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bitRsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAASAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u6; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitRsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitLsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAAASAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u7; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitLsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitSwap :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAASAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u8; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitSwap\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bit0 :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AAAAAAASA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u9; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Bits u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DWord.Bits.bit0\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} bitSize :: a -> Int {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAAAAS)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> ua; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> Int) } [ _NOREP_S_ "%DWord.Bits.bitSize\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} data Byte {-# GHC_PRAGMA Byte Word# #-} data Short {-# GHC_PRAGMA Short Word# #-} data Word {-# GHC_PRAGMA Word Word# #-} @@ -50,122 +50,122 @@ wordToShorts :: Word -> [Short] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} instance Eq Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Byte -> Byte -> Bool), (Byte -> Byte -> Bool)] [_CONSTM_ Eq (==) (Byte), _CONSTM_ Eq (/=) (Byte)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Short -> Short -> Bool), (Short -> Short -> Bool)] [_CONSTM_ Eq (==) (Short), _CONSTM_ Eq (/=) (Short)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Word -> Word -> Bool), (Word -> Word -> Bool)] [_CONSTM_ Eq (==) (Word), _CONSTM_ Eq (/=) (Word)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Byte}}, {{Text Byte}}, (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Integer -> Byte), (Int -> Byte)] [_DFUN_ Eq (Byte), _DFUN_ Text (Byte), _CONSTM_ Num (+) (Byte), _CONSTM_ Num (-) (Byte), _CONSTM_ Num (*) (Byte), _CONSTM_ Num negate (Byte), _CONSTM_ Num abs (Byte), _CONSTM_ Num signum (Byte), _CONSTM_ Num fromInteger (Byte), _CONSTM_ Num fromInt (Byte)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Short}}, {{Text Short}}, (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Short), (Short -> Short), (Integer -> Short), (Int -> Short)] [_DFUN_ Eq (Short), _DFUN_ Text (Short), _CONSTM_ Num (+) (Short), _CONSTM_ Num (-) (Short), _CONSTM_ Num (*) (Short), _CONSTM_ Num negate (Short), _CONSTM_ Num abs (Short), _CONSTM_ Num signum (Short), _CONSTM_ Num fromInteger (Short), _CONSTM_ Num fromInt (Short)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Word}}, {{Text Word}}, (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Word), (Word -> Word), (Integer -> Word), (Int -> Word)] [_DFUN_ Eq (Word), _DFUN_ Text (Word), _CONSTM_ Num (+) (Word), _CONSTM_ Num (-) (Word), _CONSTM_ Num (*) (Word), _CONSTM_ Num negate (Word), _CONSTM_ Num abs (Word), _CONSTM_ Num signum (Word), _CONSTM_ Num fromInteger (Word), _CONSTM_ Num fromInt (Word)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ } #-} instance Ord Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Byte}}, (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> _CMP_TAG)] [_DFUN_ Eq (Byte), _CONSTM_ Ord (<) (Byte), _CONSTM_ Ord (<=) (Byte), _CONSTM_ Ord (>=) (Byte), _CONSTM_ Ord (>) (Byte), _CONSTM_ Ord max (Byte), _CONSTM_ Ord min (Byte), _CONSTM_ Ord _tagCmp (Byte)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Short}}, (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> _CMP_TAG)] [_DFUN_ Eq (Short), _CONSTM_ Ord (<) (Short), _CONSTM_ Ord (<=) (Short), _CONSTM_ Ord (>=) (Short), _CONSTM_ Ord (>) (Short), _CONSTM_ Ord max (Short), _CONSTM_ Ord min (Short), _CONSTM_ Ord _tagCmp (Short)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Word}}, (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> _CMP_TAG)] [_DFUN_ Eq (Word), _CONSTM_ Ord (<) (Word), _CONSTM_ Ord (<=) (Word), _CONSTM_ Ord (>=) (Word), _CONSTM_ Ord (>) (Word), _CONSTM_ Ord max (Word), _CONSTM_ Ord min (Word), _CONSTM_ Ord _tagCmp (Word)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Byte, [Char])]), (Int -> Byte -> [Char] -> [Char]), ([Char] -> [([Byte], [Char])]), ([Byte] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Byte), _CONSTM_ Text showsPrec (Byte), _CONSTM_ Text readList (Byte), _CONSTM_ Text showList (Byte)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Byte, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Short, [Char])]), (Int -> Short -> [Char] -> [Char]), ([Char] -> [([Short], [Char])]), ([Short] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Short), _CONSTM_ Text showsPrec (Short), _CONSTM_ Text readList (Short), _CONSTM_ Text showList (Short)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Short, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Word, [Char])]), (Int -> Word -> [Char] -> [Char]), ([Char] -> [([Word], [Char])]), ([Word] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Word), _CONSTM_ Text showsPrec (Word), _CONSTM_ Text readList (Word), _CONSTM_ Text showList (Word)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Word, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Bits Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Int -> Byte), (Byte -> Int -> Byte), (Byte -> Byte), Byte, (Byte -> Int)] [_CONSTM_ Bits bitAnd (Byte), _CONSTM_ Bits bitOr (Byte), _CONSTM_ Bits bitXor (Byte), _CONSTM_ Bits bitCompl (Byte), _CONSTM_ Bits bitRsh (Byte), _CONSTM_ Bits bitLsh (Byte), _CONSTM_ Bits bitSwap (Byte), _CONSTM_ Bits bit0 (Byte), _CONSTM_ Bits bitSize (Byte)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _APP_ _TYAPP_ error { Byte } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Byte [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ } #-} instance Bits Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Int -> Short), (Short -> Int -> Short), (Short -> Short), Short, (Short -> Int)] [_CONSTM_ Bits bitAnd (Short), _CONSTM_ Bits bitOr (Short), _CONSTM_ Bits bitXor (Short), _CONSTM_ Bits bitCompl (Short), _CONSTM_ Bits bitRsh (Short), _CONSTM_ Bits bitLsh (Short), _CONSTM_ Bits bitSwap (Short), _CONSTM_ Bits bit0 (Short), _CONSTM_ Bits bitSize (Short)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _APP_ _TYAPP_ error { Short } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Short [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ } #-} instance Bits Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Int -> Word), (Word -> Int -> Word), (Word -> Word), Word, (Word -> Int)] [_CONSTM_ Bits bitAnd (Word), _CONSTM_ Bits bitOr (Word), _CONSTM_ Bits bitXor (Word), _CONSTM_ Bits bitCompl (Word), _CONSTM_ Bits bitRsh (Word), _CONSTM_ Bits bitLsh (Word), _CONSTM_ Bits bitSwap (Word), _CONSTM_ Bits bit0 (Word), _CONSTM_ Bits bitSize (Word)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _APP_ _TYAPP_ error { Word } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Word [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ } #-} diff --git a/ghc/lib/hbc/Word_t.hi b/ghc/lib/hbc/Word_t.hi index c994512c122dd53d5302cbb0257a87dfb5dd6952..d308daee8ae31a9bb57db1ab814a4293fda6a2a9 100644 --- a/ghc/lib/hbc/Word_t.hi +++ b/ghc/lib/hbc/Word_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Word where infixl 7 `bitAnd` infixl 8 `bitLsh` @@ -8,31 +8,31 @@ infixl 6 `bitXor` class Bits a where bitAnd :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(SAAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u2; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitAnd\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitOr :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(ASAAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u3; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitOr\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitXor :: a -> a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AASAAAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u4; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitXor\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitCompl :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAASAAAAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u5; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitCompl\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bitRsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAASAAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u6; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitRsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitLsh :: a -> Int -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 122 _N_ _S_ "U(AAAAASAAA)" {_A_ 1 _U_ 122 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u7; _NO_DEFLT_ } _N_ - {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 3 XXX 4 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) (u3 :: Int) -> _APP_ _TYAPP_ patError# { (u0 -> Int -> u0) } [ _NOREP_S_ "%DWord.Bits.bitLsh\"", u2, u3 ] _N_ #-} + {-defm-} _A_ 3 _U_ 022 _N_ _S_ _!_ _N_ _N_ #-} bitSwap :: a -> a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAASAA)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u8; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> u0) } [ _NOREP_S_ "%DWord.Bits.bitSwap\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} bit0 :: a {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 1 _N_ _S_ "U(AAAAAAASA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> u9; _NO_DEFLT_ } _N_ - {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 1 X 2 _/\_ u0 -> \ (u1 :: {{Bits u0}}) -> _APP_ _TYAPP_ patError# { u0 } [ _NOREP_S_ "%DWord.Bits.bit0\"" ] _N_ #-} + {-defm-} _A_ 1 _U_ 0 _N_ _S_ _!_ _N_ _N_ #-} bitSize :: a -> Int {-# GHC_PRAGMA {-meth-} _A_ 1 _U_ 12 _N_ _S_ "U(AAAAAAAAS)" {_A_ 1 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0 -> Int) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: (u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0 -> u0, u0 -> u0, u0 -> Int -> u0, u0 -> Int -> u0, u0 -> u0, u0, u0 -> Int)) -> case u1 of { _ALG_ _TUP_9 (u2 :: u0 -> u0 -> u0) (u3 :: u0 -> u0 -> u0) (u4 :: u0 -> u0 -> u0) (u5 :: u0 -> u0) (u6 :: u0 -> Int -> u0) (u7 :: u0 -> Int -> u0) (u8 :: u0 -> u0) (u9 :: u0) (ua :: u0 -> Int) -> ua; _NO_DEFLT_ } _N_ - {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _F_ _IF_ARGS_ 1 2 XX 3 _/\_ u0 -> \ (u1 :: {{Bits u0}}) (u2 :: u0) -> _APP_ _TYAPP_ patError# { (u0 -> Int) } [ _NOREP_S_ "%DWord.Bits.bitSize\"", u2 ] _N_ #-} + {-defm-} _A_ 2 _U_ 02 _N_ _S_ _!_ _N_ _N_ #-} data Byte {-# GHC_PRAGMA Byte Word# #-} data Short {-# GHC_PRAGMA Short Word# #-} data Word {-# GHC_PRAGMA Word Word# #-} @@ -50,122 +50,122 @@ wordToShorts :: Word -> [Short] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} instance Eq Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Byte -> Byte -> Bool), (Byte -> Byte -> Bool)] [_CONSTM_ Eq (==) (Byte), _CONSTM_ Eq (/=) (Byte)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Short -> Short -> Bool), (Short -> Short -> Bool)] [_CONSTM_ Eq (==) (Short), _CONSTM_ Eq (/=) (Short)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Eq Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(Word -> Word -> Bool), (Word -> Word -> Bool)] [_CONSTM_ Eq (==) (Word), _CONSTM_ Eq (/=) (Word)] _N_ - (==) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - (/=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ #-} + (==) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 1 \ (u0 :: Word#) (u1 :: Word#) -> _#_ eqWord# [] [u0, u1] _N_} _F_ _IF_ARGS_ 0 2 CC 3 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _#_ eqWord# [] [u2, u3]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + (/=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ eqWord# [] [u0, u1] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ eqWord# [] [u2, u3] of { _ALG_ True -> _!_ False [] []; False -> _!_ True [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Byte}}, {{Text Byte}}, (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Byte -> Byte), (Integer -> Byte), (Int -> Byte)] [_DFUN_ Eq (Byte), _DFUN_ Text (Byte), _CONSTM_ Num (+) (Byte), _CONSTM_ Num (-) (Byte), _CONSTM_ Num (*) (Byte), _CONSTM_ Num negate (Byte), _CONSTM_ Num abs (Byte), _CONSTM_ Num signum (Byte), _CONSTM_ Num fromInteger (Byte), _CONSTM_ Num fromInt (Byte)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Byte) -> _APP_ _TYAPP_ patError# { (Byte -> Byte) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Byte [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Short}}, {{Text Short}}, (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Short), (Short -> Short), (Integer -> Short), (Int -> Short)] [_DFUN_ Eq (Short), _DFUN_ Text (Short), _CONSTM_ Num (+) (Short), _CONSTM_ Num (-) (Short), _CONSTM_ Num (*) (Short), _CONSTM_ Num negate (Short), _CONSTM_ Num abs (Short), _CONSTM_ Num signum (Short), _CONSTM_ Num fromInteger (Short), _CONSTM_ Num fromInt (Short)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Short) -> _APP_ _TYAPP_ patError# { (Short -> Short) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 6 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } } } _N_} _F_ _ALWAYS_ \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u6 :: Word#) -> case _#_ and# [] [u5, u6] of { _PRIM_ (u7 :: Word#) -> _!_ _ORIG_ Word Short [] [u7] } } } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Num Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Word}}, {{Text Word}}, (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Word), (Word -> Word), (Integer -> Word), (Int -> Word)] [_DFUN_ Eq (Word), _DFUN_ Text (Word), _CONSTM_ Num (+) (Word), _CONSTM_ Num (-) (Word), _CONSTM_ Num (*) (Word), _CONSTM_ Num negate (Word), _CONSTM_ Num abs (Word), _CONSTM_ Num signum (Word), _CONSTM_ Num fromInteger (Word), _CONSTM_ Num fromInt (Word)] _N_ - (+) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (-) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (*) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - negate = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - abs = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.abs\"", u0 ] _N_, - signum = _A_ 1 _U_ 2 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word) -> _APP_ _TYAPP_ patError# { (Word -> Word) } [ _NOREP_S_ "%DPreludeCore.Num.signum\"", u0 ] _N_, - fromInteger = _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_, - fromInt = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ #-} + (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (-) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (*) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + negate = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + abs = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + signum = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + fromInteger = { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 4 \ (u0 :: Int#) (u1 :: Int#) (u2 :: ByteArray#) -> case _#_ integer2Int# [] [u0, u1, u2] of { _PRIM_ (u3 :: Int#) -> case _#_ int2Word# [] [u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] } } _N_} _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: Integer) -> case u0 of { _ALG_ J# (u1 :: Int#) (u2 :: Int#) (u3 :: ByteArray#) -> case _#_ integer2Int# [] [u1, u2, u3] of { _PRIM_ (u4 :: Int#) -> case _#_ int2Word# [] [u4] of { _PRIM_ (u5 :: Word#) -> _!_ _ORIG_ Word Word [] [u5] } }; _NO_DEFLT_ } _N_ }, + fromInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Int#) -> case _#_ int2Word# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Int) -> case u0 of { _ALG_ I# (u1 :: Int#) -> case _#_ int2Word# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ } #-} instance Ord Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Byte}}, (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Bool), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> _CMP_TAG)] [_DFUN_ Eq (Byte), _CONSTM_ Ord (<) (Byte), _CONSTM_ Ord (<=) (Byte), _CONSTM_ Ord (>=) (Byte), _CONSTM_ Ord (>) (Byte), _CONSTM_ Ord max (Byte), _CONSTM_ Ord min (Byte), _CONSTM_ Ord _tagCmp (Byte)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Short}}, (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Bool), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> _CMP_TAG)] [_DFUN_ Eq (Short), _CONSTM_ Ord (<) (Short), _CONSTM_ Ord (<=) (Short), _CONSTM_ Ord (>=) (Short), _CONSTM_ Ord (>) (Short), _CONSTM_ Ord max (Short), _CONSTM_ Ord min (Short), _CONSTM_ Ord _tagCmp (Short)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ord Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 9 _!_ _TUP_8 [{{Eq Word}}, (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Bool), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> _CMP_TAG)] [_DFUN_ Eq (Word), _CONSTM_ Ord (<) (Word), _CONSTM_ Ord (<=) (Word), _CONSTM_ Ord (>=) (Word), _CONSTM_ Ord (>) (Word), _CONSTM_ Ord max (Word), _CONSTM_ Ord min (Word), _CONSTM_ Ord _tagCmp (Word)] _N_ - (<) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (<=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>=) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - (>) = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - max = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - min = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - _tagCmp = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} + (<) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (<=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>=) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + (>) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + max = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + min = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + _tagCmp = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Text Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Byte, [Char])]), (Int -> Byte -> [Char] -> [Char]), ([Char] -> [([Byte], [Char])]), ([Byte] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Byte), _CONSTM_ Text showsPrec (Byte), _CONSTM_ Text readList (Byte), _CONSTM_ Text showList (Byte)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Byte, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Short, [Char])]), (Int -> Short -> [Char] -> [Char]), ([Char] -> [([Short], [Char])]), ([Short] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Short), _CONSTM_ Text showsPrec (Short), _CONSTM_ Text readList (Short), _CONSTM_ Text showList (Short)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Short, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Text Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [(Word, [Char])]), (Int -> Word -> [Char] -> [Char]), ([Char] -> [([Word], [Char])]), ([Word] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (Word), _CONSTM_ Text showsPrec (Word), _CONSTM_ Text readList (Word), _CONSTM_ Text showList (Word)] _N_ - readsPrec = _A_ 2 _U_ 22 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 XX 4 \ (u0 :: Int) (u1 :: [Char]) -> _APP_ _TYAPP_ patError# { (Int -> [Char] -> [(Word, [Char])]) } [ _NOREP_S_ "%DPreludeCore.Text.readsPrec\"", u0, u1 ] _N_, - showsPrec = _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_, - readList = _A_ 0 _U_ 2 _N_ _N_ _N_ _N_, - showList = _A_ 0 _U_ 12 _N_ _N_ _N_ _N_ #-} + readsPrec = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ }, + showsPrec = { _A_ 2 _U_ 012 _N_ _S_ "AU(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, + readList = { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, + showList = { _A_ 2 _U_ 22 _N_ _S_ _!_ _N_ _N_ } #-} instance Bits Byte {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte -> Byte), (Byte -> Byte), (Byte -> Int -> Byte), (Byte -> Int -> Byte), (Byte -> Byte), Byte, (Byte -> Int)] [_CONSTM_ Bits bitAnd (Byte), _CONSTM_ Bits bitOr (Byte), _CONSTM_ Bits bitXor (Byte), _CONSTM_ Bits bitCompl (Byte), _CONSTM_ Bits bitRsh (Byte), _CONSTM_ Bits bitLsh (Byte), _CONSTM_ Bits bitSwap (Byte), _CONSTM_ Bits bit0 (Byte), _CONSTM_ Bits bitSize (Byte)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> _APP_ _TYAPP_ error { Byte } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Byte [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Byte (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Byte [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Byte [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Byte) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Byte (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [255#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Byte [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [8#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Byte) -> case u0 of { _ALG_ _ORIG_ Word Byte (u1 :: Word#) -> _!_ I# [] [8#]; _NO_DEFLT_ } _N_ } #-} instance Bits Short {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short -> Short), (Short -> Short), (Short -> Int -> Short), (Short -> Int -> Short), (Short -> Short), Short, (Short -> Int)] [_CONSTM_ Bits bitAnd (Short), _CONSTM_ Bits bitOr (Short), _CONSTM_ Bits bitXor (Short), _CONSTM_ Bits bitCompl (Short), _CONSTM_ Bits bitRsh (Short), _CONSTM_ Bits bitLsh (Short), _CONSTM_ Bits bitSwap (Short), _CONSTM_ Bits bit0 (Short), _CONSTM_ Bits bitSize (Short)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> _APP_ _TYAPP_ error { Short } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Short [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Short (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Short [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 5 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Short [] [u4] } } } _N_} _F_ _IF_ARGS_ 0 2 CC 7 \ (u0 :: Short) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Short (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> case _#_ int2Word# [] [65535#] of { _PRIM_ (u5 :: Word#) -> case _#_ and# [] [u4, u5] of { _PRIM_ (u6 :: Word#) -> _!_ _ORIG_ Word Short [] [u6] } } }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [16#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Short) -> case u0 of { _ALG_ _ORIG_ Word Short (u1 :: Word#) -> _!_ I# [] [16#]; _NO_DEFLT_ } _N_ } #-} instance Bits Word {-# GHC_PRAGMA _M_ Word {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 10 _!_ _TUP_9 [(Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word -> Word), (Word -> Word), (Word -> Int -> Word), (Word -> Int -> Word), (Word -> Word), Word, (Word -> Int)] [_CONSTM_ Bits bitAnd (Word), _CONSTM_ Bits bitOr (Word), _CONSTM_ Bits bitXor (Word), _CONSTM_ Bits bitCompl (Word), _CONSTM_ Bits bitRsh (Word), _CONSTM_ Bits bitLsh (Word), _CONSTM_ Bits bitSwap (Word), _CONSTM_ Bits bit0 (Word), _CONSTM_ Bits bitSize (Word)] _N_ - bitAnd = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitOr = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitXor = _A_ 2 _U_ 11 _N_ _S_ _!_ _F_ _IF_ARGS_ 0 2 CC 4 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> _APP_ _TYAPP_ error { Word } [ _NOREP_S_ "later..." ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitCompl = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_, - bitRsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitLsh = _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_, - bitSwap = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_, - bit0 = _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 case _#_ int2Word# [] [1#] of { _PRIM_ (u0 :: Word#) -> _!_ _ORIG_ Word Word [] [u0] } _N_, - bitSize = _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ #-} + bitAnd = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ and# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ and# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitOr = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Word#) -> case _#_ or# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ _ORIG_ Word Word (u3 :: Word#) -> case _#_ or# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitXor = { _A_ 2 _U_ 11 _N_ _S_ _!_ _N_ _N_ }, + bitCompl = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: Word#) -> case _#_ not# [] [u0] of { _PRIM_ (u1 :: Word#) -> _!_ _ORIG_ Word Word [] [u1] } _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> case _#_ not# [] [u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] }; _NO_DEFLT_ } _N_ }, + bitRsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftRL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftRL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitLsh = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Word#) (u1 :: Int#) -> case _#_ shiftL# [] [u0, u1] of { _PRIM_ (u2 :: Word#) -> _!_ _ORIG_ Word Word [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Word) (u1 :: Int) -> case u0 of { _ALG_ _ORIG_ Word Word (u2 :: Word#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ shiftL# [] [u2, u3] of { _PRIM_ (u4 :: Word#) -> _!_ _ORIG_ Word Word [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + bitSwap = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, + bit0 = { _A_ 0 _N_ _N_ _N_ _N_ _N_ }, + bitSize = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Word#) -> _!_ I# [] [32#] _N_} _F_ _IF_ARGS_ 0 1 C 3 \ (u0 :: Word) -> case u0 of { _ALG_ _ORIG_ Word Word (u1 :: Word#) -> _!_ I# [] [32#]; _NO_DEFLT_ } _N_ } #-} diff --git a/ghc/lib/prelude/Builtin.hi b/ghc/lib/prelude/Builtin.hi index b802737f1e21700f358db746626ff3a5a947680c..ba441b9d3dec831d321c4352224fa90d29f721d7 100644 --- a/ghc/lib/prelude/Builtin.hi +++ b/ghc/lib/prelude/Builtin.hi @@ -11,5 +11,13 @@ error :: [Char] -> a parError# :: a {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} patError# :: [Char] -> a - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ _!_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} +unpackAppendPS# :: Addr# -> [Char] -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PL" _N_ _N_ #-} +unpackFoldrPS# :: Addr# -> (Char -> a -> a) -> a -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "PLL" _N_ _N_ #-} +unpackPS# :: Addr# -> [Char] + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} +unpackPS2# :: Addr# -> Int# -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} diff --git a/ghc/lib/prelude/Builtin.hs b/ghc/lib/prelude/Builtin.hs index a8eaa04675a29b36f1f131cc91d83a432925f2b8..629aef8386841dbc91e8dca3360e72573b4844d9 100644 --- a/ghc/lib/prelude/Builtin.hs +++ b/ghc/lib/prelude/Builtin.hs @@ -4,7 +4,10 @@ module PreludeBuiltin ( absent#, error, patError#, - parError# + parError#, + unpackPS#, unpackPS2#, + unpackAppendPS#, + unpackFoldrPS# ) where import Cls @@ -18,7 +21,7 @@ import PreludeDialogueIO ( appendChan# ) #ifndef __PARALLEL_HASKELL__ import PreludeGlaMisc ( deRefStablePtr ) #endif -import PS ( _PackedString, _unpackPS ) +import PS ( _PackedString, _unpackPS, _packCBytes ) import Stdio ( _FILE ) import Text import TyComplex @@ -117,3 +120,41 @@ _trace string expr returnPrimIO expr ) where sTDERR = (``stderr'' :: _FILE) + +-------------------------------------------------------------------------- + +unpackPS# :: Addr# -> [Char] -- calls injected by compiler +unpackPS2# :: Addr# -> Int# -> [Char] -- calls injected by compiler +unpackAppendPS# :: Addr# -> [Char] -> [Char] -- ditto? +unpackFoldrPS# :: Addr# -> (Char -> a -> a) -> a -> a -- ditto? + +unpackPS# addr -- calls injected by compiler + = unpack 0# + where + unpack nh + | ch `eqChar#` '\0'# = [] + | True = C# ch : unpack (nh +# 1#) + where + ch = indexCharOffAddr# addr nh + +unpackAppendPS# addr rest + = unpack 0# + where + unpack nh + | ch `eqChar#` '\0'# = rest + | True = C# ch : unpack (nh +# 1#) + where + ch = indexCharOffAddr# addr nh + +unpackFoldrPS# addr f z + = unpack 0# + where + unpack nh + | ch `eqChar#` '\0'# = z + | True = C# ch `f` unpack (nh +# 1#) + where + ch = indexCharOffAddr# addr nh + +unpackPS2# addr len -- calls injected by compiler + -- this one is for literal strings with NULs in them; rare. + = _unpackPS (_packCBytes (I# len) (A# addr)) diff --git a/ghc/lib/prelude/Builtin_mc.hi b/ghc/lib/prelude/Builtin_mc.hi index b802737f1e21700f358db746626ff3a5a947680c..ba441b9d3dec831d321c4352224fa90d29f721d7 100644 --- a/ghc/lib/prelude/Builtin_mc.hi +++ b/ghc/lib/prelude/Builtin_mc.hi @@ -11,5 +11,13 @@ error :: [Char] -> a parError# :: a {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} patError# :: [Char] -> a - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ _!_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} +unpackAppendPS# :: Addr# -> [Char] -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PL" _N_ _N_ #-} +unpackFoldrPS# :: Addr# -> (Char -> a -> a) -> a -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "PLL" _N_ _N_ #-} +unpackPS# :: Addr# -> [Char] + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} +unpackPS2# :: Addr# -> Int# -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} diff --git a/ghc/lib/prelude/Builtin_mp.hi b/ghc/lib/prelude/Builtin_mp.hi index b802737f1e21700f358db746626ff3a5a947680c..ba441b9d3dec831d321c4352224fa90d29f721d7 100644 --- a/ghc/lib/prelude/Builtin_mp.hi +++ b/ghc/lib/prelude/Builtin_mp.hi @@ -11,5 +11,13 @@ error :: [Char] -> a parError# :: a {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} patError# :: [Char] -> a - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ _!_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} +unpackAppendPS# :: Addr# -> [Char] -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PL" _N_ _N_ #-} +unpackFoldrPS# :: Addr# -> (Char -> a -> a) -> a -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "PLL" _N_ _N_ #-} +unpackPS# :: Addr# -> [Char] + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} +unpackPS2# :: Addr# -> Int# -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} diff --git a/ghc/lib/prelude/Builtin_p.hi b/ghc/lib/prelude/Builtin_p.hi index b802737f1e21700f358db746626ff3a5a947680c..ba441b9d3dec831d321c4352224fa90d29f721d7 100644 --- a/ghc/lib/prelude/Builtin_p.hi +++ b/ghc/lib/prelude/Builtin_p.hi @@ -11,5 +11,13 @@ error :: [Char] -> a parError# :: a {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} patError# :: [Char] -> a - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ _!_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} +unpackAppendPS# :: Addr# -> [Char] -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PL" _N_ _N_ #-} +unpackFoldrPS# :: Addr# -> (Char -> a -> a) -> a -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "PLL" _N_ _N_ #-} +unpackPS# :: Addr# -> [Char] + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} +unpackPS2# :: Addr# -> Int# -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} diff --git a/ghc/lib/prelude/Builtin_t.hi b/ghc/lib/prelude/Builtin_t.hi index b802737f1e21700f358db746626ff3a5a947680c..ba441b9d3dec831d321c4352224fa90d29f721d7 100644 --- a/ghc/lib/prelude/Builtin_t.hi +++ b/ghc/lib/prelude/Builtin_t.hi @@ -11,5 +11,13 @@ error :: [Char] -> a parError# :: a {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} patError# :: [Char] -> a - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ _!_ _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ #-} +unpackAppendPS# :: Addr# -> [Char] -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PL" _N_ _N_ #-} +unpackFoldrPS# :: Addr# -> (Char -> a -> a) -> a -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "PLL" _N_ _N_ #-} +unpackPS# :: Addr# -> [Char] + {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} +unpackPS2# :: Addr# -> Int# -> [Char] + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} diff --git a/ghc/lib/prelude/Cls.hs b/ghc/lib/prelude/Cls.hs index 43c5b461f3e839f8064533f675934ef3198799a8..2274d8cef3104bd95e6739fbf425d0fcea173236 100644 --- a/ghc/lib/prelude/Cls.hs +++ b/ghc/lib/prelude/Cls.hs @@ -10,7 +10,7 @@ import UTypes import Core import IChar -import IInt ( Int ) +import IInt ( _rangeComplaint_Ix_Int, Int ) import IInteger ( __integer1, Integer ) import List ( takeWhile, (++), foldr ) import Prel ( (&&), (.), otherwise ) diff --git a/ghc/lib/prelude/FoldrBuild.hs b/ghc/lib/prelude/FoldrBuild.hs index 5d7175a45bc8a41eb557e25cc411e20a8ecc5a3c..ce36edde9c4a683441e769ffef6060a68a640523 100644 --- a/ghc/lib/prelude/FoldrBuild.hs +++ b/ghc/lib/prelude/FoldrBuild.hs @@ -18,7 +18,6 @@ foldl :: (a -> b -> a) -> a -> [b] -> a foldl f z [] = z foldl f z (x:xs) = foldl f (f z x) xs - -- HACK: Magic unfoldings not implemented for unboxed lists -- Need to define a _build to avoid undefined symbol diff --git a/ghc/lib/prelude/IArray.hi b/ghc/lib/prelude/IArray.hi index 1742ef849460ad24a07f4ed09c5cb86e5aa6b18d..c46696801ae1187d9ec12b6d7bb7abb7b626c7d3 100644 --- a/ghc/lib/prelude/IArray.hi +++ b/ghc/lib/prelude/IArray.hi @@ -1,33 +1,40 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeArray where -import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2) +import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2, _State(..)) import PreludeCore(Eq(..), Ix(..), Ord(..), Text(..)) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) data Array a b {-# GHC_PRAGMA _Array (a, a) (Array# b) #-} data Assoc a b {-# GHC_PRAGMA (:=) a b #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance (Ix a, Eq b) => Eq (Array a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} instance (Eq a, Eq b) => Eq (Assoc a b) diff --git a/ghc/lib/prelude/IArray.hs b/ghc/lib/prelude/IArray.hs index 85f874942d89cc8e1968a2417c758c2e8d30f040..2f68c05cb9d40b48c3eecc255f269a79a68d6580 100644 --- a/ghc/lib/prelude/IArray.hs +++ b/ghc/lib/prelude/IArray.hs @@ -14,7 +14,10 @@ module PreludeArray ( elems, indices, ixmap, - listArray + listArray, + _arrEleBottom, + _newArray, + _freezeArray ) where import Cls @@ -125,6 +128,23 @@ ixmap :: (Ix a, Ix b) => (a,a) -> (a -> b) -> Array b c -> Array a c bounds (_Array b _) = b +#ifdef USE_FOLDR_BUILD +{-# INLINE array #-} +#endif +array ixs@(ix_start, ix_end) ivs = + _runST ( \ s -> + case _newArray ixs _arrEleBottom s of { (arr@(_MutableArray _ arr#),s) -> + let + fill_one_in (S# s#) (i := v) + = case index ixs i of { I# n# -> + case writeArray# arr# n# v s# of { s2# -> S# s2# }} + in + case foldl fill_one_in s ivs of { s@(S# _) -> + _freezeArray arr s }}) + +_arrEleBottom = error "(!){PreludeArray}: undefined array element" + +{- OLD: array ixs@(ix_start, ix_end) ivs = _runST ( newArray ixs arrEleBottom `thenStrictlyST` \ arr# -> @@ -133,6 +153,7 @@ array ixs@(ix_start, ix_end) ivs ) where arrEleBottom = error "(!){PreludeArray}: undefined array element" +-} (_Array bounds arr#) ! i = let n# = case (index bounds i) of { I# x -> x } -- index fails if out of range @@ -150,6 +171,12 @@ fill_it_in arr lst s listArray b vs = array b (zipWith (:=) (range b) vs) +#ifdef USE_FOLDR_BUILD +{-# INLINE indices #-} +{-# INLINE elems #-} +{-# INLINE assocs #-} +#endif + indices a = range (bounds a) elems a = [a!i | i <- indices a] @@ -167,11 +194,12 @@ accumArray f z b = accum f (array b [i := z | i <- range b]) #else /* ! USE_REPORT_PRELUDE */ +-- TODO: add (//), accum, accumArray, listArray + old_array // ivs = _runST ( -- copy the old array: - newArray (bounds old_array) bottom `thenStrictlyST` \ arr# -> - fill_it_in arr# (assocs old_array) `seqStrictlyST` + thawArray old_array `thenStrictlyST` \ arr# -> -- now write the new elements into the new array: fill_it_in arr# ivs `seqStrictlyST` freezeArray arr# diff --git a/ghc/lib/prelude/IArray_mc.hi b/ghc/lib/prelude/IArray_mc.hi index 1742ef849460ad24a07f4ed09c5cb86e5aa6b18d..c46696801ae1187d9ec12b6d7bb7abb7b626c7d3 100644 --- a/ghc/lib/prelude/IArray_mc.hi +++ b/ghc/lib/prelude/IArray_mc.hi @@ -1,33 +1,40 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeArray where -import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2) +import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2, _State(..)) import PreludeCore(Eq(..), Ix(..), Ord(..), Text(..)) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) data Array a b {-# GHC_PRAGMA _Array (a, a) (Array# b) #-} data Assoc a b {-# GHC_PRAGMA (:=) a b #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance (Ix a, Eq b) => Eq (Array a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} instance (Eq a, Eq b) => Eq (Assoc a b) diff --git a/ghc/lib/prelude/IArray_mp.hi b/ghc/lib/prelude/IArray_mp.hi index 1742ef849460ad24a07f4ed09c5cb86e5aa6b18d..c46696801ae1187d9ec12b6d7bb7abb7b626c7d3 100644 --- a/ghc/lib/prelude/IArray_mp.hi +++ b/ghc/lib/prelude/IArray_mp.hi @@ -1,33 +1,40 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeArray where -import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2) +import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2, _State(..)) import PreludeCore(Eq(..), Ix(..), Ord(..), Text(..)) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) data Array a b {-# GHC_PRAGMA _Array (a, a) (Array# b) #-} data Assoc a b {-# GHC_PRAGMA (:=) a b #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance (Ix a, Eq b) => Eq (Array a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} instance (Eq a, Eq b) => Eq (Assoc a b) diff --git a/ghc/lib/prelude/IArray_p.hi b/ghc/lib/prelude/IArray_p.hi index 1742ef849460ad24a07f4ed09c5cb86e5aa6b18d..c46696801ae1187d9ec12b6d7bb7abb7b626c7d3 100644 --- a/ghc/lib/prelude/IArray_p.hi +++ b/ghc/lib/prelude/IArray_p.hi @@ -1,33 +1,40 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeArray where -import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2) +import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2, _State(..)) import PreludeCore(Eq(..), Ix(..), Ord(..), Text(..)) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) data Array a b {-# GHC_PRAGMA _Array (a, a) (Array# b) #-} data Assoc a b {-# GHC_PRAGMA (:=) a b #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance (Ix a, Eq b) => Eq (Array a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} instance (Eq a, Eq b) => Eq (Assoc a b) diff --git a/ghc/lib/prelude/IArray_t.hi b/ghc/lib/prelude/IArray_t.hi index 1742ef849460ad24a07f4ed09c5cb86e5aa6b18d..c46696801ae1187d9ec12b6d7bb7abb7b626c7d3 100644 --- a/ghc/lib/prelude/IArray_t.hi +++ b/ghc/lib/prelude/IArray_t.hi @@ -1,33 +1,40 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeArray where -import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2) +import PreludeBuiltin(Double(..), Int(..), List(..), Tuple2, _State(..)) import PreludeCore(Eq(..), Ix(..), Ord(..), Text(..)) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) data Array a b {-# GHC_PRAGMA _Array (a, a) (Array# b) #-} data Assoc a b {-# GHC_PRAGMA (:=) a b #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance (Ix a, Eq b) => Eq (Array a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 2 _U_ 21 _N_ _N_ _N_ _N_ #-} instance (Eq a, Eq b) => Eq (Assoc a b) diff --git a/ghc/lib/prelude/IInt.hi b/ghc/lib/prelude/IInt.hi index 1964be7ac98f8c16ff1b06900844e1358c78bab9..4aa9ef060348f42f87a742a795a90c8f7db1aba5 100644 --- a/ghc/lib/prelude/IInt.hi +++ b/ghc/lib/prelude/IInt.hi @@ -2,7 +2,7 @@ interface PreludeCore where import PreludeBuiltin(Int(..), Tuple0, _Addr(..), _Word(..)) import PreludeGlaMisc(_MallocPtr(..), _StablePtr(..)) -rangeComplaint_Ix_Int# :: Int# -> Int# -> Int# -> a +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} instance Enum Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Int}}, (Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> Int -> [Int])] [_DFUN_ Ord (Int), _CONSTM_ Enum enumFrom (Int), _CONSTM_ Enum enumFromThen (Int), _CONSTM_ Enum enumFromTo (Int), _CONSTM_ Enum enumFromThenTo (Int)] _N_ @@ -36,9 +36,9 @@ instance Integral Int toInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Int#) -> _!_ I# [] [u0] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Int) -> u0 _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Int}}, {{Text Int}}, (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int), (Int -> Int), (Int -> Int), (Integer -> Int), (Int -> Int)] [_DFUN_ Eq (Int), _DFUN_ Text (Int), _CONSTM_ Num (+) (Int), _CONSTM_ Num (-) (Int), _CONSTM_ Num (*) (Int), _CONSTM_ Num negate (Int), _CONSTM_ Num abs (Int), _CONSTM_ Num signum (Int), _CONSTM_ Num fromInteger (Int), _CONSTM_ Num fromInt (Int)] _N_ (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Int#) (u1 :: Int#) -> case _#_ plusInt# [] [u0, u1] of { _PRIM_ (u2 :: Int#) -> _!_ I# [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Int) (u1 :: Int) -> case u0 of { _ALG_ I# (u2 :: Int#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ plusInt# [] [u2, u3] of { _PRIM_ (u4 :: Int#) -> _!_ I# [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, diff --git a/ghc/lib/prelude/IInt.hs b/ghc/lib/prelude/IInt.hs index bb64d6895c6a1ba5d01f0872c579a25f77d208c1..0c684e0c56cb337f95212dd4f8434bfab4e59531 100644 --- a/ghc/lib/prelude/IInt.hs +++ b/ghc/lib/prelude/IInt.hs @@ -1,4 +1,4 @@ -module PreludeCore ( Int(..), rangeComplaint_Ix_Int#{-see comment later-} ) where +module PreludeCore ( Int(..), _rangeComplaint_Ix_Int{-see comment later-} ) where import Cls import Core @@ -96,16 +96,19 @@ instance Integral Int where toInteger (I# n#) = int2Integer# n# -- give back a full-blown Integer toInt x = x -rangeComplaint_Ix_Int# i m n -- export it so it will *not* be floated inwards - = error ("Ix.Int.index2{PreludeCore}: Index " +_rangeComplaint_Ix_Int i m n -- export it so it will *not* be floated inwards + = error ("Ix.Int.index{PreludeCore}: Index " ++ show (I# i) ++ " outside the range " ++ show (I# m,I# n) ++ ".\n") instance Ix Int where + {-# INLINE range #-} range (m,n) = [m..n] + {-# INLINE index #-} index b@(I# m, I# n) (I# i) | inRange b (I# i) = I# (i -# m) - | otherwise = rangeComplaint_Ix_Int# i m n + | otherwise = _rangeComplaint_Ix_Int i m n + {-# INLINE inRange #-} inRange (I# m, I# n) (I# i) = m <=# i && i <=# n instance Enum Int where @@ -205,10 +208,11 @@ instance Integral Int# where toInt n# = I# n# instance Ix Int# where + {-# INLINE range #-} range (m,n) = [m..n] index b@(m, n) i | inRange b i = I# (i -# m) - | otherwise = rangeComplaint_Ix_Int# i m n + | otherwise = _rangeComplaint_Ix_Int i m n inRange (m, n) i = m <=# i && i <=# n instance Enum Int# where @@ -216,12 +220,12 @@ instance Enum Int# where enumFrom x = x : enumFrom (x `plusInt#` 1) enumFromTo n m = takeWhile (<= m) (enumFrom n) #else - {-# INLINE enumFrom #-} {-# INLINE enumFromTo #-} - enumFrom x = _build (\ c _ -> - let g x = x `c` g (x `plusInt#` 1) in g x) + {-# INLINE enumFrom #-} enumFromTo x y = _build (\ c n -> - let g x = if x <= y then x `c` g (x `plusInt#` 1) else n in g x) + let g x = if x <= y then x `c` g (x +# 1) else n in g x) + enumFrom x = _build (\ c _ -> + let g x = x `c` g (x +# 1) in g x) #endif enumFromThen m n = en' m (n `minusInt#` m) where en' m n = m : en' (m `plusInt#` n) n diff --git a/ghc/lib/prelude/IInt_mc.hi b/ghc/lib/prelude/IInt_mc.hi index 1964be7ac98f8c16ff1b06900844e1358c78bab9..4aa9ef060348f42f87a742a795a90c8f7db1aba5 100644 --- a/ghc/lib/prelude/IInt_mc.hi +++ b/ghc/lib/prelude/IInt_mc.hi @@ -2,7 +2,7 @@ interface PreludeCore where import PreludeBuiltin(Int(..), Tuple0, _Addr(..), _Word(..)) import PreludeGlaMisc(_MallocPtr(..), _StablePtr(..)) -rangeComplaint_Ix_Int# :: Int# -> Int# -> Int# -> a +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} instance Enum Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Int}}, (Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> Int -> [Int])] [_DFUN_ Ord (Int), _CONSTM_ Enum enumFrom (Int), _CONSTM_ Enum enumFromThen (Int), _CONSTM_ Enum enumFromTo (Int), _CONSTM_ Enum enumFromThenTo (Int)] _N_ @@ -36,9 +36,9 @@ instance Integral Int toInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Int#) -> _!_ I# [] [u0] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Int) -> u0 _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Int}}, {{Text Int}}, (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int), (Int -> Int), (Int -> Int), (Integer -> Int), (Int -> Int)] [_DFUN_ Eq (Int), _DFUN_ Text (Int), _CONSTM_ Num (+) (Int), _CONSTM_ Num (-) (Int), _CONSTM_ Num (*) (Int), _CONSTM_ Num negate (Int), _CONSTM_ Num abs (Int), _CONSTM_ Num signum (Int), _CONSTM_ Num fromInteger (Int), _CONSTM_ Num fromInt (Int)] _N_ (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Int#) (u1 :: Int#) -> case _#_ plusInt# [] [u0, u1] of { _PRIM_ (u2 :: Int#) -> _!_ I# [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Int) (u1 :: Int) -> case u0 of { _ALG_ I# (u2 :: Int#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ plusInt# [] [u2, u3] of { _PRIM_ (u4 :: Int#) -> _!_ I# [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, diff --git a/ghc/lib/prelude/IInt_mp.hi b/ghc/lib/prelude/IInt_mp.hi index 1964be7ac98f8c16ff1b06900844e1358c78bab9..4aa9ef060348f42f87a742a795a90c8f7db1aba5 100644 --- a/ghc/lib/prelude/IInt_mp.hi +++ b/ghc/lib/prelude/IInt_mp.hi @@ -2,7 +2,7 @@ interface PreludeCore where import PreludeBuiltin(Int(..), Tuple0, _Addr(..), _Word(..)) import PreludeGlaMisc(_MallocPtr(..), _StablePtr(..)) -rangeComplaint_Ix_Int# :: Int# -> Int# -> Int# -> a +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} instance Enum Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Int}}, (Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> Int -> [Int])] [_DFUN_ Ord (Int), _CONSTM_ Enum enumFrom (Int), _CONSTM_ Enum enumFromThen (Int), _CONSTM_ Enum enumFromTo (Int), _CONSTM_ Enum enumFromThenTo (Int)] _N_ @@ -36,9 +36,9 @@ instance Integral Int toInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Int#) -> _!_ I# [] [u0] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Int) -> u0 _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Int}}, {{Text Int}}, (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int), (Int -> Int), (Int -> Int), (Integer -> Int), (Int -> Int)] [_DFUN_ Eq (Int), _DFUN_ Text (Int), _CONSTM_ Num (+) (Int), _CONSTM_ Num (-) (Int), _CONSTM_ Num (*) (Int), _CONSTM_ Num negate (Int), _CONSTM_ Num abs (Int), _CONSTM_ Num signum (Int), _CONSTM_ Num fromInteger (Int), _CONSTM_ Num fromInt (Int)] _N_ (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Int#) (u1 :: Int#) -> case _#_ plusInt# [] [u0, u1] of { _PRIM_ (u2 :: Int#) -> _!_ I# [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Int) (u1 :: Int) -> case u0 of { _ALG_ I# (u2 :: Int#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ plusInt# [] [u2, u3] of { _PRIM_ (u4 :: Int#) -> _!_ I# [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, diff --git a/ghc/lib/prelude/IInt_p.hi b/ghc/lib/prelude/IInt_p.hi index 1964be7ac98f8c16ff1b06900844e1358c78bab9..4aa9ef060348f42f87a742a795a90c8f7db1aba5 100644 --- a/ghc/lib/prelude/IInt_p.hi +++ b/ghc/lib/prelude/IInt_p.hi @@ -2,7 +2,7 @@ interface PreludeCore where import PreludeBuiltin(Int(..), Tuple0, _Addr(..), _Word(..)) import PreludeGlaMisc(_MallocPtr(..), _StablePtr(..)) -rangeComplaint_Ix_Int# :: Int# -> Int# -> Int# -> a +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} instance Enum Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Int}}, (Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> Int -> [Int])] [_DFUN_ Ord (Int), _CONSTM_ Enum enumFrom (Int), _CONSTM_ Enum enumFromThen (Int), _CONSTM_ Enum enumFromTo (Int), _CONSTM_ Enum enumFromThenTo (Int)] _N_ @@ -36,9 +36,9 @@ instance Integral Int toInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Int#) -> _!_ I# [] [u0] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Int) -> u0 _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Int}}, {{Text Int}}, (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int), (Int -> Int), (Int -> Int), (Integer -> Int), (Int -> Int)] [_DFUN_ Eq (Int), _DFUN_ Text (Int), _CONSTM_ Num (+) (Int), _CONSTM_ Num (-) (Int), _CONSTM_ Num (*) (Int), _CONSTM_ Num negate (Int), _CONSTM_ Num abs (Int), _CONSTM_ Num signum (Int), _CONSTM_ Num fromInteger (Int), _CONSTM_ Num fromInt (Int)] _N_ (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Int#) (u1 :: Int#) -> case _#_ plusInt# [] [u0, u1] of { _PRIM_ (u2 :: Int#) -> _!_ I# [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Int) (u1 :: Int) -> case u0 of { _ALG_ I# (u2 :: Int#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ plusInt# [] [u2, u3] of { _PRIM_ (u4 :: Int#) -> _!_ I# [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, diff --git a/ghc/lib/prelude/IInt_t.hi b/ghc/lib/prelude/IInt_t.hi index 1964be7ac98f8c16ff1b06900844e1358c78bab9..4aa9ef060348f42f87a742a795a90c8f7db1aba5 100644 --- a/ghc/lib/prelude/IInt_t.hi +++ b/ghc/lib/prelude/IInt_t.hi @@ -2,7 +2,7 @@ interface PreludeCore where import PreludeBuiltin(Int(..), Tuple0, _Addr(..), _Word(..)) import PreludeGlaMisc(_MallocPtr(..), _StablePtr(..)) -rangeComplaint_Ix_Int# :: Int# -> Int# -> Int# -> a +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} instance Enum Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 6 _!_ _TUP_5 [{{Ord Int}}, (Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> [Int]), (Int -> Int -> Int -> [Int])] [_DFUN_ Ord (Int), _CONSTM_ Enum enumFrom (Int), _CONSTM_ Enum enumFromThen (Int), _CONSTM_ Enum enumFromTo (Int), _CONSTM_ Enum enumFromThenTo (Int)] _N_ @@ -36,9 +36,9 @@ instance Integral Int toInt = { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 2 \ (u0 :: Int#) -> _!_ I# [] [u0] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: Int) -> u0 _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Num Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 11 _!_ _TUP_10 [{{Eq Int}}, {{Text Int}}, (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int -> Int), (Int -> Int), (Int -> Int), (Int -> Int), (Integer -> Int), (Int -> Int)] [_DFUN_ Eq (Int), _DFUN_ Text (Int), _CONSTM_ Num (+) (Int), _CONSTM_ Num (-) (Int), _CONSTM_ Num (*) (Int), _CONSTM_ Num negate (Int), _CONSTM_ Num abs (Int), _CONSTM_ Num signum (Int), _CONSTM_ Num fromInteger (Int), _CONSTM_ Num fromInt (Int)] _N_ (+) = { _A_ 2 _U_ 11 _N_ _S_ "U(P)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Int#) (u1 :: Int#) -> case _#_ plusInt# [] [u0, u1] of { _PRIM_ (u2 :: Int#) -> _!_ I# [] [u2] } _N_} _F_ _IF_ARGS_ 0 2 CC 5 \ (u0 :: Int) (u1 :: Int) -> case u0 of { _ALG_ I# (u2 :: Int#) -> case u1 of { _ALG_ I# (u3 :: Int#) -> case _#_ plusInt# [] [u2, u3] of { _PRIM_ (u4 :: Int#) -> _!_ I# [] [u4] }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, diff --git a/ghc/lib/prelude/ITup0.hi b/ghc/lib/prelude/ITup0.hi index cdfaff0729db41913a084c86f4a91640d24cb400..85463b477ffd4c8eab0a71558a53a622dc19ced9 100644 --- a/ghc/lib/prelude/ITup0.hi +++ b/ghc/lib/prelude/ITup0.hi @@ -28,7 +28,7 @@ instance Ord () instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/prelude/ITup0_mc.hi b/ghc/lib/prelude/ITup0_mc.hi index cdfaff0729db41913a084c86f4a91640d24cb400..85463b477ffd4c8eab0a71558a53a622dc19ced9 100644 --- a/ghc/lib/prelude/ITup0_mc.hi +++ b/ghc/lib/prelude/ITup0_mc.hi @@ -28,7 +28,7 @@ instance Ord () instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/prelude/ITup0_mp.hi b/ghc/lib/prelude/ITup0_mp.hi index cdfaff0729db41913a084c86f4a91640d24cb400..85463b477ffd4c8eab0a71558a53a622dc19ced9 100644 --- a/ghc/lib/prelude/ITup0_mp.hi +++ b/ghc/lib/prelude/ITup0_mp.hi @@ -28,7 +28,7 @@ instance Ord () instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/prelude/ITup0_p.hi b/ghc/lib/prelude/ITup0_p.hi index cdfaff0729db41913a084c86f4a91640d24cb400..85463b477ffd4c8eab0a71558a53a622dc19ced9 100644 --- a/ghc/lib/prelude/ITup0_p.hi +++ b/ghc/lib/prelude/ITup0_p.hi @@ -28,7 +28,7 @@ instance Ord () instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/prelude/ITup0_t.hi b/ghc/lib/prelude/ITup0_t.hi index cdfaff0729db41913a084c86f4a91640d24cb400..85463b477ffd4c8eab0a71558a53a622dc19ced9 100644 --- a/ghc/lib/prelude/ITup0_t.hi +++ b/ghc/lib/prelude/ITup0_t.hi @@ -28,7 +28,7 @@ instance Ord () instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} diff --git a/ghc/lib/prelude/ITup2.hi b/ghc/lib/prelude/ITup2.hi index 199c904f21f4376dfd19b1722a092265dc1342bc..0213fd36a52f9f6cd5c6f37b454c4203d1d28e08 100644 --- a/ghc/lib/prelude/ITup2.hi +++ b/ghc/lib/prelude/ITup2.hi @@ -24,9 +24,9 @@ instance (Ix a, Ix b) => Ix (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ord a, Ord b) => Ord (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 112 _N_ _N_ _N_ _N_ #-} instance Ord (Int, Int) diff --git a/ghc/lib/prelude/ITup2.hs b/ghc/lib/prelude/ITup2.hs index 07a3f91c4781e5f2aa2891efef89484348b66495..47f69a76c6289b76bf1ca6c9d7da9b569d132fa4 100644 --- a/ghc/lib/prelude/ITup2.hs +++ b/ghc/lib/prelude/ITup2.hs @@ -33,12 +33,15 @@ instance (Ord a, Ord b) => Ord (a, b) where _EQ -> _tagCmp b1 b2 instance (Ix a, Ix b) => Ix (a, b) where + {-# INLINE range #-} range ((l1,l2),(u1,u2)) = [ (i1,i2) | i1 <- range (l1,u1), i2 <- range (l2,u2) ] + {-# INLINE index #-} index ((l1,l2),(u1,u2)) (i1,i2) - = index (l1,u1) i1 * (index (l2,u2) u2 + 1){-rangeSize (l2,u2)-} + index (l2,u2) i2 + = index (l1,u1) i1 * (index (l2,u2) u2 + (I# 1#)){-rangeSize (l2,u2)-} + index (l2,u2) i2 + {-# INLINE inRange #-} inRange ((l1,l2),(u1,u2)) (i1,i2) = inRange (l1,u1) i1 && inRange (l2,u2) i2 diff --git a/ghc/lib/prelude/ITup2_mc.hi b/ghc/lib/prelude/ITup2_mc.hi index 199c904f21f4376dfd19b1722a092265dc1342bc..0213fd36a52f9f6cd5c6f37b454c4203d1d28e08 100644 --- a/ghc/lib/prelude/ITup2_mc.hi +++ b/ghc/lib/prelude/ITup2_mc.hi @@ -24,9 +24,9 @@ instance (Ix a, Ix b) => Ix (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ord a, Ord b) => Ord (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 112 _N_ _N_ _N_ _N_ #-} instance Ord (Int, Int) diff --git a/ghc/lib/prelude/ITup2_mp.hi b/ghc/lib/prelude/ITup2_mp.hi index 199c904f21f4376dfd19b1722a092265dc1342bc..0213fd36a52f9f6cd5c6f37b454c4203d1d28e08 100644 --- a/ghc/lib/prelude/ITup2_mp.hi +++ b/ghc/lib/prelude/ITup2_mp.hi @@ -24,9 +24,9 @@ instance (Ix a, Ix b) => Ix (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ord a, Ord b) => Ord (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 112 _N_ _N_ _N_ _N_ #-} instance Ord (Int, Int) diff --git a/ghc/lib/prelude/ITup2_p.hi b/ghc/lib/prelude/ITup2_p.hi index 199c904f21f4376dfd19b1722a092265dc1342bc..0213fd36a52f9f6cd5c6f37b454c4203d1d28e08 100644 --- a/ghc/lib/prelude/ITup2_p.hi +++ b/ghc/lib/prelude/ITup2_p.hi @@ -24,9 +24,9 @@ instance (Ix a, Ix b) => Ix (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ord a, Ord b) => Ord (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 112 _N_ _N_ _N_ _N_ #-} instance Ord (Int, Int) diff --git a/ghc/lib/prelude/ITup2_t.hi b/ghc/lib/prelude/ITup2_t.hi index 199c904f21f4376dfd19b1722a092265dc1342bc..0213fd36a52f9f6cd5c6f37b454c4203d1d28e08 100644 --- a/ghc/lib/prelude/ITup2_t.hi +++ b/ghc/lib/prelude/ITup2_t.hi @@ -24,9 +24,9 @@ instance (Ix a, Ix b) => Ix (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ord a, Ord b) => Ord (a, b) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 3 _U_ 112 _N_ _N_ _N_ _N_ #-} instance Ord (Int, Int) diff --git a/ghc/lib/prelude/List.hi b/ghc/lib/prelude/List.hi index cbf183537837019761646fd6783610fea713bce9..cd81ce6f394a9d82f12c82cc007e71209bc8f16f 100644 --- a/ghc/lib/prelude/List.hi +++ b/ghc/lib/prelude/List.hi @@ -5,7 +5,7 @@ import PreludeCore(Bool(..), Eq(..), Integral(..), Num(..), Ord(..)) (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -25,7 +25,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -39,23 +39,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -89,17 +89,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -111,7 +111,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] diff --git a/ghc/lib/prelude/List.hs b/ghc/lib/prelude/List.hs index f487e332b13f7ea424c7b27018e3d6e2b7f008fa..d0dc9bf8330852b69635976b98a40854688deef6 100644 --- a/ghc/lib/prelude/List.hs +++ b/ghc/lib/prelude/List.hs @@ -63,9 +63,19 @@ tail [] = error "tail{PreludeList}: tail []\n" {-# GENERATE_SPECS init a #-} init :: [a] -> [a] +#ifndef USE_FOLDR_BUILD init [] = error "init{PreludeList}: init []\n" init [x] = [] init (x:xs) = x : init xs +#else +init xs = _build (\ c n -> + let + _init [] = error "init{PreludeList}: init []\n" + _init [x] = n + _init (x:xs) = x `c` _init xs + in + _init xs) +#endif -- null determines if a list is empty. {-# GENERATE_SPECS null a #-} @@ -89,8 +99,8 @@ xs ++ ys = foldr (:) ys xs [] ++ ys = ys (x:xs) ++ ys = x : (xs ++ ys) # else ---#ANDY?#{-# INLINE (++) #-} -xs ++ ys = foldr (:) ys xs +{-# INLINE (++) #-} +xs ++ ys = _augment (\ c n -> foldr c n xs) ys # endif /* USE_FOLDR_BUILD */ #endif /* ! USE_REPORT_PRELUDE */ @@ -118,8 +128,7 @@ length :: [a] -> Int #ifdef USE_REPORT_PRELUDE length = genericLength #else -#if 1 ---#ANDY?## ifndef USE_FOLDR_BUILD +# ifndef USE_FOLDR_BUILD -- stolen from HBC, then unboxified length l = len l 0# where @@ -127,7 +136,7 @@ length l = len l 0# len [] a# = I# a# len (_:xs) a# = len xs (a# +# 1#) # else ---#ANDY?#{-# INLINE length #-} +{-# INLINE length #-} length l = foldl (\ n _ -> n+I# 1#) (I# 0#) l # endif /* USE_FOLDR_BUILD */ #endif /* ! USE_REPORT_PRELUDE */ @@ -164,7 +173,8 @@ map f [] = [] map f (x:xs) = f x : map f xs #else {-# INLINE map #-} -map f xs = _build (\ c n -> foldr (c.f) n xs) +map f xs = _build (\ c n -> + foldr (\ a b -> f a `c` b) n xs) #endif /* USE_FOLDR_BUILD */ -- filter, applied to a predicate and a list, returns the list of those @@ -258,9 +268,9 @@ iterate f x = x : iterate f (f x) {-# INLINE iterate #-} iterate f x = _build (\ c n -> let - _iterate f x = x `c` _iterate f (f x) + _iterate x = x `c` _iterate (f x) in - _iterate f x) + _iterate x) #endif /* USE_FOLDR_BUILD */ @@ -390,6 +400,7 @@ _take_unsafe_Integral n (x:xs) = x : _take_unsafe_Integral (n-1) xs __max :: Num a => a __max = fromInt maxInt +#ifndef USE_FOLDR_BUILD take n | n < __i0 = error "take{PreludeList}: negative index" | n <= __max @@ -404,6 +415,24 @@ take n | n < __i0 where (m,r) = n `quotRem` __max i2i# (I# i#) = i# +#else +{-# INLINE take #-} +take n xs = takeInt (toInt n) xs + +{-# INLINE takeInt #-} +takeInt :: Int -> [b] -> [b] +takeInt n xs = _build (\ c0 n0 -> + let + takeInt# 0# _ = n0 + takeInt# _ [] = n0 + takeInt# m# (x:xs) = x `c0` takeInt# (m# `minusInt#` 1#) xs + in + case n of + I# n# -> if n# <# 0# + then error "take{PreludeList}: negative index" + else takeInt# n# xs) + +#endif /* USE_FOLDR_BUILD */ -- Test -- main = print (head (take (123456789123456789::Integer) [1..])) @@ -440,7 +469,7 @@ splitAtInt (I# n#) xs where (xs', xs'') = splitAtInt# (m# `minusInt#` 1#) xs -#endif {- ! USE_REPORT_PRELUDE -} +#endif /* USE_REPORT_PRELUDE */ -- takeWhile, applied to a predicate p and a list xs, returns the longest -- prefix (possibly empty) of xs of elements that satisfy p. dropWhile p xs @@ -506,10 +535,22 @@ lines s = let (l, s') = break (== '\n') s (_:s'') -> lines s'' words :: String -> [String] +#ifndef USE_FOLDR_BUILD words s = case dropWhile isSpace s of "" -> [] s' -> w : words s'' where (w, s'') = break isSpace s' +#else +{-# INLINE words #-} +words s = _build (\ c n -> + let + words' s = case dropWhile isSpace s of + "" -> n + s' -> w `c` words' s'' + where (w, s'') = break isSpace s' + in + words' s) +#endif /* USE_FOLDR_BUILD */ unlines :: [String] -> String #ifdef USE_REPORT_PRELUDE @@ -520,11 +561,11 @@ unlines = concat . map (++ "\n") -- here's a more efficient version unlines [] = [] unlines (l:ls) = l ++ '\n' : unlines ls + # else {-# INLINE unlines #-} -unlines xs = foldr (\ l r -> l ++ '\n' : r) [] xs --- OLD --- unlines = concat . map (++ "\n") +unlines xs = _build (\ c n -> foldr (\ l r -> foldr c ('\n' `c` r) l) n xs) + # endif /* USE_FOLDR_BUILD */ #endif /* ! USE_REPORT_PRELUDE */ @@ -547,11 +588,21 @@ nub :: (Eq a) => [a] -> [a] nub [] = [] nub (x:xs) = x : nub (filter (/= x) xs) #else +# ifndef USE_FOLDR_BUILD -- stolen from HBC nub l = nub' l [] where nub' [] _ = [] nub' (x:xs) l = if x `elem` l then nub' xs l else x : nub' xs (x:l) +# else +{-# INLINE nub #-} +nub l = _build (\ c n -> + let + nub' [] _ = n + nub' (x:xs) l = if x `elem` l then nub' xs l else x `c` nub' xs (x:l) + in + nub' l []) +# endif /* USE_FOLDR_BUILD */ #endif /* ! USE_REPORT_PRELUDE */ -- reverse xs returns the elements of xs in reverse order. xs must be finite. @@ -567,7 +618,7 @@ reverse l = rev l [] rev (x:xs) a = rev xs (x:a) # else {-# INLINE reverse #-} -reverse xs = _build (\ c n -> foldl (flip c) n xs) +reverse xs = _build (\ c n -> foldl (\ a b -> c b a) n xs) # endif /* USE_FOLDR_BUILD */ #endif /* ! USE_REPORT_PRELUDE */ @@ -638,12 +689,19 @@ notElem x [] = True notElem x (y:ys)= x /= y && notElem x ys # else -{-# INLINE elem #-} -{-# INLINE notElem #-} --- We are prepared to lose the partial application to equality, --- ie (x ==), and replace it with (\ y -> x == y) -elem x ys = any (\ y -> x == y) ys -notElem x ys = all (\ y -> x /= y) ys +elem _ [] = False +elem x (y:ys) = x==y || elem x ys + +notElem x [] = True +notElem x (y:ys)= x /= y && notElem x ys + +-- Put back later .... +--{-# INLINE elem #-} +--{-# INLINE notElem #-} +----- We are prepared to lose the partial application to equality, +---- ie (x ==), and replace it with (\ y -> x == y) +--elem x ys = any (\ y -> x == y) ys +--notElem x ys = all (\ y -> x /= y) ys # endif /* USE_FOLDR_BUILD */ #endif /* ! USE_REPORT_PRELUDE */ @@ -816,6 +874,10 @@ zipWith7 _ _ _ _ _ _ _ _ = [] -- unzip transforms a list of pairs into a pair of lists. As with zip, -- a family of such functions up to septuplets is provided. +#ifdef USE_FOLDR_BUILD +{-# INLINE unzip #-} +#endif + {-# GENERATE_SPECS unzip a b #-} unzip :: [(a,b)] -> ([a],[b]) unzip xs = foldr (\(a,b) ~(as,bs) -> (a:as,b:bs)) ([],[]) xs diff --git a/ghc/lib/prelude/List_mc.hi b/ghc/lib/prelude/List_mc.hi index cbf183537837019761646fd6783610fea713bce9..cd81ce6f394a9d82f12c82cc007e71209bc8f16f 100644 --- a/ghc/lib/prelude/List_mc.hi +++ b/ghc/lib/prelude/List_mc.hi @@ -5,7 +5,7 @@ import PreludeCore(Bool(..), Eq(..), Integral(..), Num(..), Ord(..)) (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -25,7 +25,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -39,23 +39,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -89,17 +89,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -111,7 +111,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] diff --git a/ghc/lib/prelude/List_mp.hi b/ghc/lib/prelude/List_mp.hi index cbf183537837019761646fd6783610fea713bce9..cd81ce6f394a9d82f12c82cc007e71209bc8f16f 100644 --- a/ghc/lib/prelude/List_mp.hi +++ b/ghc/lib/prelude/List_mp.hi @@ -5,7 +5,7 @@ import PreludeCore(Bool(..), Eq(..), Integral(..), Num(..), Ord(..)) (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -25,7 +25,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -39,23 +39,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -89,17 +89,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -111,7 +111,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] diff --git a/ghc/lib/prelude/List_p.hi b/ghc/lib/prelude/List_p.hi index cbf183537837019761646fd6783610fea713bce9..cd81ce6f394a9d82f12c82cc007e71209bc8f16f 100644 --- a/ghc/lib/prelude/List_p.hi +++ b/ghc/lib/prelude/List_p.hi @@ -5,7 +5,7 @@ import PreludeCore(Bool(..), Eq(..), Integral(..), Num(..), Ord(..)) (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -25,7 +25,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -39,23 +39,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -89,17 +89,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -111,7 +111,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] diff --git a/ghc/lib/prelude/List_t.hi b/ghc/lib/prelude/List_t.hi index cbf183537837019761646fd6783610fea713bce9..cd81ce6f394a9d82f12c82cc007e71209bc8f16f 100644 --- a/ghc/lib/prelude/List_t.hi +++ b/ghc/lib/prelude/List_t.hi @@ -5,7 +5,7 @@ import PreludeCore(Bool(..), Eq(..), Integral(..), Num(..), Ord(..)) (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -25,7 +25,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -39,23 +39,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -89,17 +89,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" {-IWantToBeINLINEd _ALWAYS_ -} _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -111,7 +111,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] diff --git a/ghc/lib/prelude/PS.hi b/ghc/lib/prelude/PS.hi index 506f2cfd6163226896307a61ca0d3c07cce26b3b..386dc9de6a247f3384322c2a0abb1523a5b263f8 100644 --- a/ghc/lib/prelude/PS.hi +++ b/ghc/lib/prelude/PS.hi @@ -82,10 +82,6 @@ _unsafeByteArrayToPS :: _ByteArray a -> Int -> _PackedString {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(AP)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} _wordsPS :: _PackedString -> [_PackedString] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} -unpackPS# :: Addr# -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} -unpackPS2# :: Addr# -> Int# -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} instance Eq _PackedString {-# GHC_PRAGMA _M_ PreludePS {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(_PackedString -> _PackedString -> Bool), (_PackedString -> _PackedString -> Bool)] [_CONSTM_ Eq (==) (_PackedString), _CONSTM_ Eq (/=) (_PackedString)] _N_ (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, diff --git a/ghc/lib/prelude/PS.lhs b/ghc/lib/prelude/PS.lhs index 449069d6d560d21b62a4cd74ac081b97cb8d2297..3bef7cab7a86bb7313ed9de9d684fd30132e6286 100644 --- a/ghc/lib/prelude/PS.lhs +++ b/ghc/lib/prelude/PS.lhs @@ -26,7 +26,6 @@ module PreludePS{-yes, a Prelude module!-} ( _psToByteArray, _unpackPS, - unpackPS#, unpackPS2#, -- toCString, _putPS, _getPS, @@ -72,7 +71,8 @@ import IList import IInt import Prel ( otherwise, (&&), (||), chr, ($), not, (.), isSpace, flip ) import List ( length, (++), map, filter, foldl, foldr, - lines, words, reverse, null, foldr1 + lines, words, reverse, null, foldr1, + dropWhile, break ) import TyArray ( Array(..) ) import TyComplex @@ -112,8 +112,6 @@ _psToByteArray :: _PackedString -> _ByteArray Int --OLD: packToCString :: [Char] -> _ByteArray Int -- hmmm... weird name _unpackPS :: _PackedString -> [Char] -unpackPS# :: Addr# -> [Char] -- calls injected by compiler -unpackPS2# :: Addr# -> Int# -> [Char] -- calls injected by compiler --???toCString :: _PackedString -> ByteArray# _putPS :: _FILE -> _PackedString -> PrimIO () -- ToDo: more sensible type \end{code} @@ -272,14 +270,12 @@ _psToByteArray (_CPS addr len#) %************************************************************************ \begin{code} +{- OLD: but good? WDP 96/01 unpackPS# addr -- calls injected by compiler = _unpackPS (_CPS addr len) where len = case (strlen# addr) of { I# x -> x } - -unpackPS2# addr len -- calls injected by compiler - -- this one is for literal strings with NULs in them; rare. - = _unpackPS (_packCBytes (I# len) (A# addr)) +-} -- OK, but this code gets *hammered*: -- _unpackPS ps diff --git a/ghc/lib/prelude/PS_mc.hi b/ghc/lib/prelude/PS_mc.hi index 506f2cfd6163226896307a61ca0d3c07cce26b3b..386dc9de6a247f3384322c2a0abb1523a5b263f8 100644 --- a/ghc/lib/prelude/PS_mc.hi +++ b/ghc/lib/prelude/PS_mc.hi @@ -82,10 +82,6 @@ _unsafeByteArrayToPS :: _ByteArray a -> Int -> _PackedString {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(AP)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} _wordsPS :: _PackedString -> [_PackedString] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} -unpackPS# :: Addr# -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} -unpackPS2# :: Addr# -> Int# -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} instance Eq _PackedString {-# GHC_PRAGMA _M_ PreludePS {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(_PackedString -> _PackedString -> Bool), (_PackedString -> _PackedString -> Bool)] [_CONSTM_ Eq (==) (_PackedString), _CONSTM_ Eq (/=) (_PackedString)] _N_ (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, diff --git a/ghc/lib/prelude/PS_mp.hi b/ghc/lib/prelude/PS_mp.hi index 506f2cfd6163226896307a61ca0d3c07cce26b3b..386dc9de6a247f3384322c2a0abb1523a5b263f8 100644 --- a/ghc/lib/prelude/PS_mp.hi +++ b/ghc/lib/prelude/PS_mp.hi @@ -82,10 +82,6 @@ _unsafeByteArrayToPS :: _ByteArray a -> Int -> _PackedString {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(AP)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} _wordsPS :: _PackedString -> [_PackedString] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} -unpackPS# :: Addr# -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} -unpackPS2# :: Addr# -> Int# -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} instance Eq _PackedString {-# GHC_PRAGMA _M_ PreludePS {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(_PackedString -> _PackedString -> Bool), (_PackedString -> _PackedString -> Bool)] [_CONSTM_ Eq (==) (_PackedString), _CONSTM_ Eq (/=) (_PackedString)] _N_ (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, diff --git a/ghc/lib/prelude/PS_p.hi b/ghc/lib/prelude/PS_p.hi index 506f2cfd6163226896307a61ca0d3c07cce26b3b..386dc9de6a247f3384322c2a0abb1523a5b263f8 100644 --- a/ghc/lib/prelude/PS_p.hi +++ b/ghc/lib/prelude/PS_p.hi @@ -82,10 +82,6 @@ _unsafeByteArrayToPS :: _ByteArray a -> Int -> _PackedString {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(AP)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} _wordsPS :: _PackedString -> [_PackedString] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} -unpackPS# :: Addr# -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} -unpackPS2# :: Addr# -> Int# -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} instance Eq _PackedString {-# GHC_PRAGMA _M_ PreludePS {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(_PackedString -> _PackedString -> Bool), (_PackedString -> _PackedString -> Bool)] [_CONSTM_ Eq (==) (_PackedString), _CONSTM_ Eq (/=) (_PackedString)] _N_ (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, diff --git a/ghc/lib/prelude/PS_t.hi b/ghc/lib/prelude/PS_t.hi index 506f2cfd6163226896307a61ca0d3c07cce26b3b..386dc9de6a247f3384322c2a0abb1523a5b263f8 100644 --- a/ghc/lib/prelude/PS_t.hi +++ b/ghc/lib/prelude/PS_t.hi @@ -82,10 +82,6 @@ _unsafeByteArrayToPS :: _ByteArray a -> Int -> _PackedString {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(AP)U(P)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ #-} _wordsPS :: _PackedString -> [_PackedString] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} -unpackPS# :: Addr# -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "P" _N_ _N_ #-} -unpackPS2# :: Addr# -> Int# -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _S_ "PP" _N_ _N_ #-} instance Eq _PackedString {-# GHC_PRAGMA _M_ PreludePS {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 3 _!_ _TUP_2 [(_PackedString -> _PackedString -> Bool), (_PackedString -> _PackedString -> Bool)] [_CONSTM_ Eq (==) (_PackedString), _CONSTM_ Eq (/=) (_PackedString)] _N_ (==) = { _A_ 2 _U_ 22 _N_ _S_ "SS" _N_ _N_ }, diff --git a/ghc/lib/prelude/Parallel.hi b/ghc/lib/prelude/Parallel.hi index 27e35d56e841dd72f8c00cc27c6235f593a56078..4ae1077615fa071022fc571e020ca7601d60e702 100644 --- a/ghc/lib/prelude/Parallel.hi +++ b/ghc/lib/prelude/Parallel.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parallel where infixr 0 `par` infixr 1 `seq` diff --git a/ghc/lib/prelude/Parallel_mc.hi b/ghc/lib/prelude/Parallel_mc.hi index bef532dd744cbb99fd4b174998139d9755db2704..4ff6c05c5ab7133122d76b5da5c35e9ef6074944 100644 --- a/ghc/lib/prelude/Parallel_mc.hi +++ b/ghc/lib/prelude/Parallel_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parallel where infixr 0 `par` infixr 1 `seq` diff --git a/ghc/lib/prelude/Parallel_mp.hi b/ghc/lib/prelude/Parallel_mp.hi index bef532dd744cbb99fd4b174998139d9755db2704..4ff6c05c5ab7133122d76b5da5c35e9ef6074944 100644 --- a/ghc/lib/prelude/Parallel_mp.hi +++ b/ghc/lib/prelude/Parallel_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parallel where infixr 0 `par` infixr 1 `seq` diff --git a/ghc/lib/prelude/Parallel_p.hi b/ghc/lib/prelude/Parallel_p.hi index 27e35d56e841dd72f8c00cc27c6235f593a56078..4ae1077615fa071022fc571e020ca7601d60e702 100644 --- a/ghc/lib/prelude/Parallel_p.hi +++ b/ghc/lib/prelude/Parallel_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parallel where infixr 0 `par` infixr 1 `seq` diff --git a/ghc/lib/prelude/Parallel_t.hi b/ghc/lib/prelude/Parallel_t.hi index 27e35d56e841dd72f8c00cc27c6235f593a56078..4ae1077615fa071022fc571e020ca7601d60e702 100644 --- a/ghc/lib/prelude/Parallel_t.hi +++ b/ghc/lib/prelude/Parallel_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Parallel where infixr 0 `par` infixr 1 `seq` diff --git a/ghc/lib/prelude/Prel13.hi b/ghc/lib/prelude/Prel13.hi index 7c3c3c21d22f240d43f54575e6d061332f4d46b7..c7a93cc6cb200dba0d15f96abc1a9c0291fef3b9 100644 --- a/ghc/lib/prelude/Prel13.hi +++ b/ghc/lib/prelude/Prel13.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(interact13) renaming (interact13 to interact) import PreludeIOError(IOError13) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) @@ -111,29 +112,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -150,18 +153,24 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} interact :: ([Char] -> [Char]) -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -181,7 +190,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -195,23 +204,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -245,17 +254,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -267,7 +276,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -477,9 +486,9 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendFile :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 221 _N_ _S_ "LLU(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ #-} hPutChar :: _MVar _Handle -> Char -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) diff --git a/ghc/lib/prelude/Prel13.hs b/ghc/lib/prelude/Prel13.hs index 1a91e7b455f8b6d9905e4b6986c34a259070d5f7..3ff387f7247fdb43d7ac072fbbd50d93574d524f 100644 --- a/ghc/lib/prelude/Prel13.hs +++ b/ghc/lib/prelude/Prel13.hs @@ -114,8 +114,10 @@ module Prelude ( primIOToIO, ioToPrimIO, -- extra, and very dodgy -- and for foldr/build - _build + _build, _augment, + _newArray, _freezeArray, _arrEleBottom, + _rangeComplaint_Ix_Int ) where -- few *Ty(s) imports diff --git a/ghc/lib/prelude/Prel13_mc.hi b/ghc/lib/prelude/Prel13_mc.hi index 7c3c3c21d22f240d43f54575e6d061332f4d46b7..c7a93cc6cb200dba0d15f96abc1a9c0291fef3b9 100644 --- a/ghc/lib/prelude/Prel13_mc.hi +++ b/ghc/lib/prelude/Prel13_mc.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(interact13) renaming (interact13 to interact) import PreludeIOError(IOError13) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) @@ -111,29 +112,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -150,18 +153,24 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} interact :: ([Char] -> [Char]) -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -181,7 +190,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -195,23 +204,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -245,17 +254,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -267,7 +276,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -477,9 +486,9 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendFile :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 221 _N_ _S_ "LLU(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ #-} hPutChar :: _MVar _Handle -> Char -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) diff --git a/ghc/lib/prelude/Prel13_mp.hi b/ghc/lib/prelude/Prel13_mp.hi index 7c3c3c21d22f240d43f54575e6d061332f4d46b7..c7a93cc6cb200dba0d15f96abc1a9c0291fef3b9 100644 --- a/ghc/lib/prelude/Prel13_mp.hi +++ b/ghc/lib/prelude/Prel13_mp.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(interact13) renaming (interact13 to interact) import PreludeIOError(IOError13) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) @@ -111,29 +112,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -150,18 +153,24 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} interact :: ([Char] -> [Char]) -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -181,7 +190,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -195,23 +204,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -245,17 +254,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -267,7 +276,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -477,9 +486,9 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendFile :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 221 _N_ _S_ "LLU(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ #-} hPutChar :: _MVar _Handle -> Char -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) diff --git a/ghc/lib/prelude/Prel13_p.hi b/ghc/lib/prelude/Prel13_p.hi index 41b2965d9a6e612aeabe99cb2ecbd03cbb83c0dd..b19a9e3d988d467998baa192edfd0055be02079f 100644 --- a/ghc/lib/prelude/Prel13_p.hi +++ b/ghc/lib/prelude/Prel13_p.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(interact13) renaming (interact13 to interact) import PreludeIOError(IOError13) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) @@ -111,29 +112,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -150,18 +153,24 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} interact :: ([Char] -> [Char]) -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -181,7 +190,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -195,23 +204,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -245,17 +254,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -267,7 +276,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -461,7 +470,7 @@ readSigned :: Real a => ([Char] -> [(a, [Char])]) -> [Char] -> [(a, [Char])] reads :: Text a => [Char] -> [(a, [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(SAAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Bool] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Bool) _N_ }, [ [Char] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Char) _N_ }, [ [Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Double) _N_ }, [ [Float] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Int) _N_ }, [ [Integer] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Char]) _N_ }, [ [[Int]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Int]) _N_ }, [ [Complex Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ () ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} show :: Text a => a -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: ()) -> case u0 of { _ALG_ _TUP_0 -> _NOREP_S_ "()"; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} showChar :: Char -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Char) (u1 :: [Char]) -> _!_ (:) [Char] [u0, u1] _N_ #-} showFloat :: RealFloat a => a -> [Char] -> [Char] @@ -477,9 +486,9 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendFile :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 221 _N_ _S_ "LLU(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ #-} hPutChar :: _MVar _Handle -> Char -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) diff --git a/ghc/lib/prelude/Prel13_t.hi b/ghc/lib/prelude/Prel13_t.hi index 7c3c3c21d22f240d43f54575e6d061332f4d46b7..73bff315c441a27638671abf8c2c8a1c2e2c164b 100644 --- a/ghc/lib/prelude/Prel13_t.hi +++ b/ghc/lib/prelude/Prel13_t.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(interact13) renaming (interact13 to interact) import PreludeIOError(IOError13) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) @@ -111,29 +112,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -150,18 +153,24 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} interact :: ([Char] -> [Char]) -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ #-} (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -181,7 +190,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -195,23 +204,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -245,17 +254,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -267,7 +276,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -461,7 +470,7 @@ readSigned :: Real a => ([Char] -> [(a, [Char])]) -> [Char] -> [(a, [Char])] reads :: Text a => [Char] -> [(a, [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(SAAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Bool] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Bool) _N_ }, [ [Char] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Char) _N_ }, [ [Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Double) _N_ }, [ [Float] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Int) _N_ }, [ [Integer] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Char]) _N_ }, [ [[Int]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Int]) _N_ }, [ [Complex Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ () ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} show :: Text a => a -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: ()) -> case u0 of { _ALG_ _TUP_0 -> _NOREP_S_ "()"; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} showChar :: Char -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Char) (u1 :: [Char]) -> _!_ (:) [Char] [u0, u1] _N_ #-} showFloat :: RealFloat a => a -> [Char] -> [Char] @@ -477,9 +486,9 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} appendFile :: [Char] -> [Char] -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) {-# GHC_PRAGMA _A_ 3 _U_ 221 _N_ _S_ "LLU(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ #-} hPutChar :: _MVar _Handle -> Char -> _State _RealWorld -> (Either IOError13 (), _State _RealWorld) diff --git a/ghc/lib/prelude/PrelCore13.hi b/ghc/lib/prelude/PrelCore13.hi index a14d0894db3ecd05a5c0049746a61d8281b87ffd..cf1ceddb8480fdc65eab2fd813f58edc1f77dc08 100644 --- a/ghc/lib/prelude/PrelCore13.hi +++ b/ghc/lib/prelude/PrelCore13.hi @@ -611,9 +611,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -628,9 +628,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -1012,7 +1012,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/PrelCore13_mc.hi b/ghc/lib/prelude/PrelCore13_mc.hi index a14d0894db3ecd05a5c0049746a61d8281b87ffd..cf1ceddb8480fdc65eab2fd813f58edc1f77dc08 100644 --- a/ghc/lib/prelude/PrelCore13_mc.hi +++ b/ghc/lib/prelude/PrelCore13_mc.hi @@ -611,9 +611,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -628,9 +628,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -1012,7 +1012,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/PrelCore13_mp.hi b/ghc/lib/prelude/PrelCore13_mp.hi index a14d0894db3ecd05a5c0049746a61d8281b87ffd..cf1ceddb8480fdc65eab2fd813f58edc1f77dc08 100644 --- a/ghc/lib/prelude/PrelCore13_mp.hi +++ b/ghc/lib/prelude/PrelCore13_mp.hi @@ -611,9 +611,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -628,9 +628,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -1012,7 +1012,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/PrelCore13_p.hi b/ghc/lib/prelude/PrelCore13_p.hi index a14d0894db3ecd05a5c0049746a61d8281b87ffd..cf1ceddb8480fdc65eab2fd813f58edc1f77dc08 100644 --- a/ghc/lib/prelude/PrelCore13_p.hi +++ b/ghc/lib/prelude/PrelCore13_p.hi @@ -611,9 +611,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -628,9 +628,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -1012,7 +1012,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/PrelCore13_t.hi b/ghc/lib/prelude/PrelCore13_t.hi index a14d0894db3ecd05a5c0049746a61d8281b87ffd..cf1ceddb8480fdc65eab2fd813f58edc1f77dc08 100644 --- a/ghc/lib/prelude/PrelCore13_t.hi +++ b/ghc/lib/prelude/PrelCore13_t.hi @@ -611,9 +611,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -628,9 +628,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -1012,7 +1012,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/Prelude.hi b/ghc/lib/prelude/Prelude.hi index 3eadd6eb96e82359953524e42dc71e377e2fc833..ee051f93771f3d45a2bbb6a4e761e7293772fd66 100644 --- a/ghc/lib/prelude/Prelude.hi +++ b/ghc/lib/prelude/Prelude.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(IOError, Request, Response, SigAct, abort, appendBinChan, appendBinFile, appendChan, appendFile, binDispatch, deleteFile, done, echo, exit, getArgs, getEnv, getProgName, interact, print, prints, readBinChan, readBinFile, readChan, readFile, setEnv, sigAction, statusChan, statusFile, stdecho, stderr, stdin, stdout, strDispatch, strListDispatch, succDispatch, writeBinFile, writeFile) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) import PreludePS(_PackedString, _appendPS, _breakPS, _byteArrayToPS, _concatPS, _consPS, _dropPS, _dropWhilePS, _filterPS, _foldlPS, _foldrPS, _headPS, _indexPS, _lengthPS, _linesPS, _mapPS, _nilPS, _nullPS, _packCBytes, _packCString, _packString, _psToByteArray, _putPS, _reversePS, _spanPS, _splitAtPS, _substrPS, _tailPS, _takePS, _takeWhilePS, _unpackPS, _wordsPS) @@ -93,29 +94,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -132,12 +135,18 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} abort :: IOError -> [Response] -> [Request] {-# GHC_PRAGMA _A_ 2 _U_ 00 _N_ _S_ "A" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: [Response]) -> _!_ _NIL_ [Request] [] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: IOError) -> _ORIG_ PreludeIO done _N_ #-} appendBinChan :: [Char] -> Bin -> (IOError -> [Response] -> [Request]) -> ([Response] -> [Request]) -> [Response] -> [Request] @@ -207,7 +216,7 @@ writeFile :: [Char] -> [Char] -> (IOError -> [Response] -> [Request]) -> ([Respo (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -227,7 +236,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -241,23 +250,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -291,17 +300,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -313,7 +322,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -449,7 +458,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/PreludeCore.hi b/ghc/lib/prelude/PreludeCore.hi index 7ca6cddf8a794c910123e1c6913ded566aa9165e..8a88adc5dffa2c4c60c9164ae70c19b80f21bf6a 100644 --- a/ghc/lib/prelude/PreludeCore.hi +++ b/ghc/lib/prelude/PreludeCore.hi @@ -602,9 +602,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -619,9 +619,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -999,7 +999,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/PreludeCore_mc.hi b/ghc/lib/prelude/PreludeCore_mc.hi index 7ca6cddf8a794c910123e1c6913ded566aa9165e..8a88adc5dffa2c4c60c9164ae70c19b80f21bf6a 100644 --- a/ghc/lib/prelude/PreludeCore_mc.hi +++ b/ghc/lib/prelude/PreludeCore_mc.hi @@ -602,9 +602,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -619,9 +619,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -999,7 +999,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/PreludeCore_mp.hi b/ghc/lib/prelude/PreludeCore_mp.hi index 7ca6cddf8a794c910123e1c6913ded566aa9165e..8a88adc5dffa2c4c60c9164ae70c19b80f21bf6a 100644 --- a/ghc/lib/prelude/PreludeCore_mp.hi +++ b/ghc/lib/prelude/PreludeCore_mp.hi @@ -602,9 +602,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -619,9 +619,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -999,7 +999,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/PreludeCore_p.hi b/ghc/lib/prelude/PreludeCore_p.hi index 7ca6cddf8a794c910123e1c6913ded566aa9165e..8a88adc5dffa2c4c60c9164ae70c19b80f21bf6a 100644 --- a/ghc/lib/prelude/PreludeCore_p.hi +++ b/ghc/lib/prelude/PreludeCore_p.hi @@ -602,9 +602,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -619,9 +619,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -999,7 +999,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/PreludeCore_t.hi b/ghc/lib/prelude/PreludeCore_t.hi index 7ca6cddf8a794c910123e1c6913ded566aa9165e..8a88adc5dffa2c4c60c9164ae70c19b80f21bf6a 100644 --- a/ghc/lib/prelude/PreludeCore_t.hi +++ b/ghc/lib/prelude/PreludeCore_t.hi @@ -602,9 +602,9 @@ instance (Ix a, Ix b, Ix c, Ix d, Ix e) => Ix (a, b, c, d, e) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 6 _U_ 222222 _N_ _N_ _N_ _N_ #-} instance Ix (Int, Int) {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord (Int, Int)}}, (((Int, Int), (Int, Int)) -> [(Int, Int)]), (((Int, Int), (Int, Int)) -> (Int, Int) -> Int), (((Int, Int), (Int, Int)) -> (Int, Int) -> Bool)] [_DFUN_ Ord ((Int, Int)), _CONSTM_ Ix range ((Int, Int)), _CONSTM_ Ix index ((Int, Int)), _CONSTM_ Ix inRange ((Int, Int))] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(SS)" {_A_ 2 _U_ 11 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)U(P))" {_A_ 4 _U_ 1122 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(SS)U(U(P)L)" {_A_ 4 _U_ 1121 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) -> case u0 of { _ALG_ _TUP_2 (u1 :: (Int, Int)) (u2 :: (Int, Int)) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u2 of { _ALG_ _TUP_2 (u5 :: Int) (u6 :: Int) -> let {(ux :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u7 -> \ (u8 :: (Int, Int) -> u7 -> u7) (u9 :: u7) -> let {(uo :: Int -> u7 -> u7) = \ (ua :: Int) (ub :: u7) -> let {(uf :: Int -> u7 -> u7) = \ (uc :: Int) (ud :: u7) -> let {(ue :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ua, uc]} in _APP_ u8 [ ue, ud ]} in let {(un :: [Int]) = case u4 of { _ALG_ I# (ug :: Int#) -> _LETREC_ {(uh :: Int# -> [Int]) = \ (ui :: Int#) -> case u6 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ui, uj] of { _ALG_ True -> let {(ul :: [Int]) = case _#_ plusInt# [] [ui, 1#] of { _PRIM_ (uk :: Int#) -> _APP_ uh [ uk ] }} in let {(um :: Int) = _!_ I# [] [ui]} in _!_ (:) [Int] [um, ul]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uh [ ug ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uf, ub, un ]} in let {(uw :: [Int]) = case u3 of { _ALG_ I# (up :: Int#) -> _LETREC_ {(uq :: Int# -> [Int]) = \ (ur :: Int#) -> case u5 of { _ALG_ I# (us :: Int#) -> case _#_ leInt# [] [ur, us] of { _ALG_ True -> let {(uu :: [Int]) = case _#_ plusInt# [] [ur, 1#] of { _PRIM_ (ut :: Int#) -> _APP_ uq [ ut ] }} in let {(uv :: Int) = _!_ I# [] [ur]} in _!_ (:) [Int] [uv, uu]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ uq [ up ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u7 } [ uo, u9, uw ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ ux ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case _#_ minusInt# [] [uc, ua] of { _PRIM_ (ud :: Int#) -> case u5 of { _ALG_ I# (ue :: Int#) -> case u7 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ue, uf] of { _ALG_ True -> case _#_ leInt# [] [uf, uf] of { _ALG_ True -> case _#_ minusInt# [] [uf, ue] of { _PRIM_ (ug :: Int#) -> case _#_ plusInt# [] [ug, 1#] of { _PRIM_ (uh :: Int#) -> case _#_ timesInt# [] [ud, uh] of { _PRIM_ (ui :: Int#) -> case u9 of { _ALG_ I# (uj :: Int#) -> case _#_ leInt# [] [ue, uj] of { _ALG_ True -> case _#_ leInt# [] [uj, uf] of { _ALG_ True -> case _#_ minusInt# [] [uj, ue] of { _PRIM_ (uk :: Int#) -> case _#_ plusInt# [] [ui, uk] of { _PRIM_ (ul :: Int#) -> _!_ I# [] [ul] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uj, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uf, ue, uf ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ uc, ua, ub ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: ((Int, Int), (Int, Int))) (u1 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u1 of { _ALG_ _TUP_2 (u8 :: Int) (u9 :: Int) -> case u4 of { _ALG_ I# (ua :: Int#) -> case u6 of { _ALG_ I# (ub :: Int#) -> case u8 of { _ALG_ I# (uc :: Int#) -> case _#_ leInt# [] [ua, uc] of { _ALG_ True -> case _#_ leInt# [] [uc, ub] of { _ALG_ True -> case u5 of { _ALG_ I# (ud :: Int#) -> case u7 of { _ALG_ I# (ue :: Int#) -> case u9 of { _ALG_ I# (uf :: Int#) -> case _#_ leInt# [] [ud, uf] of { _ALG_ True -> _#_ leInt# [] [uf, ue]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance (Ix a, Ix b) => Ix (Assoc a b) {-# GHC_PRAGMA _M_ PreludeArray {-dfun-} _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ #-} instance Ix Bool @@ -619,9 +619,9 @@ instance Ix Char inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)L)U(P)" {_A_ 3 _U_ 212 _N_ _N_ _N_ _N_} _N_ _N_ } #-} instance Ix Int {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Int}}, ((Int, Int) -> [Int]), ((Int, Int) -> Int -> Int), ((Int, Int) -> Int -> Bool)] [_DFUN_ Ord (Int), _CONSTM_ Ix range (Int), _CONSTM_ Ix index (Int), _CONSTM_ Ix inRange (Int)] _N_ - range = { _A_ 1 _U_ 1 _N_ _S_ "U(U(P)U(P))" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, - index = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, - inRange = { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))U(P)" {_A_ 3 _U_ 222 _N_ _N_ _F_ _IF_ARGS_ 0 3 XXX 5 \ (u0 :: Int#) (u1 :: Int#) (u2 :: Int#) -> case _#_ leInt# [] [u0, u2] of { _ALG_ True -> _#_ leInt# [] [u2, u1]; False -> _!_ False [] []; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} + range = { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Int) (u2 :: Int) -> _APP_ _CONSTM_ Enum enumFromTo (Int) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, + index = { _A_ 2 _U_ 22 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _APP_ _CONSTM_ Ix inRange (Int) [ u0, u1 ] of { _ALG_ True -> case _#_ minusInt# [] [u6, u4] of { _PRIM_ (u7 :: Int#) -> _!_ I# [] [u7] }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { Int } [ u6, u4, u5 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, + inRange = { _A_ 2 _U_ 11 _N_ _S_ "SS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: Int) -> case u0 of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u1 of { _ALG_ I# (u6 :: Int#) -> case _#_ leInt# [] [u4, u6] of { _ALG_ True -> _#_ leInt# [] [u6, u5]; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} instance Ix Integer {-# GHC_PRAGMA _M_ PreludeCore {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [{{Ord Integer}}, ((Integer, Integer) -> [Integer]), ((Integer, Integer) -> Integer -> Int), ((Integer, Integer) -> Integer -> Bool)] [_DFUN_ Ord (Integer), _CONSTM_ Ix range (Integer), _CONSTM_ Ix index (Integer), _CONSTM_ Ix inRange (Integer)] _N_ range = { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Enum enumFromTo (Integer) _N_} _F_ _IF_ARGS_ 0 1 C 4 \ (u0 :: (Integer, Integer)) -> case u0 of { _ALG_ _TUP_2 (u1 :: Integer) (u2 :: Integer) -> _APP_ _CONSTM_ Enum enumFromTo (Integer) [ u1, u2 ]; _NO_DEFLT_ } _N_ }, @@ -999,7 +999,7 @@ instance Text ((Int, Int), (Int, Int)) instance Text () {-# GHC_PRAGMA _M_ PreludeBuiltin {-dfun-} _A_ 0 _N_ _N_ _N_ _F_ _IF_ARGS_ 0 0 X 5 _!_ _TUP_4 [(Int -> [Char] -> [((), [Char])]), (Int -> () -> [Char] -> [Char]), ([Char] -> [([()], [Char])]), ([()] -> [Char] -> [Char])] [_CONSTM_ Text readsPrec (()), _CONSTM_ Text showsPrec (()), _CONSTM_ Text readList (()), _CONSTM_ Text showList (())] _N_ readsPrec = { _A_ 1 _U_ 02 _N_ _S_ "A" {_A_ 0 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, - showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_} _F_ _IF_ARGS_ 0 3 XCX 4 \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u2 ]; _NO_DEFLT_ } _N_ }, + showsPrec = { _A_ 3 _U_ 012 _N_ _S_ "AEL" {_A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: ()) (u2 :: [Char]) -> case u1 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u2 ]; _NO_DEFLT_ } _N_ }, readList = { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, showList = { _A_ 1 _U_ 12 _N_ _N_ _N_ _N_ } #-} instance (Text a, Text b) => Text (a, b) diff --git a/ghc/lib/prelude/PreludeHi.hs b/ghc/lib/prelude/PreludeHi.hs index 62fa8d0c605612744d03fa9ea217a7ffdaf9cde8..998dbe623349b69d352749ac7bd3af220ace2bcf 100644 --- a/ghc/lib/prelude/PreludeHi.hs +++ b/ghc/lib/prelude/PreludeHi.hs @@ -64,8 +64,10 @@ module Prelude ( strDispatch, strListDispatch, binDispatch, succDispatch, -- and for foldr/build - _build + _build, _augment, + _newArray, _freezeArray, _arrEleBottom, + _rangeComplaint_Ix_Int ) where -- few *Ty(s) imports diff --git a/ghc/lib/prelude/Prelude_mc.hi b/ghc/lib/prelude/Prelude_mc.hi index 3eadd6eb96e82359953524e42dc71e377e2fc833..ee051f93771f3d45a2bbb6a4e761e7293772fd66 100644 --- a/ghc/lib/prelude/Prelude_mc.hi +++ b/ghc/lib/prelude/Prelude_mc.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(IOError, Request, Response, SigAct, abort, appendBinChan, appendBinFile, appendChan, appendFile, binDispatch, deleteFile, done, echo, exit, getArgs, getEnv, getProgName, interact, print, prints, readBinChan, readBinFile, readChan, readFile, setEnv, sigAction, statusChan, statusFile, stdecho, stderr, stdin, stdout, strDispatch, strListDispatch, succDispatch, writeBinFile, writeFile) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) import PreludePS(_PackedString, _appendPS, _breakPS, _byteArrayToPS, _concatPS, _consPS, _dropPS, _dropWhilePS, _filterPS, _foldlPS, _foldrPS, _headPS, _indexPS, _lengthPS, _linesPS, _mapPS, _nilPS, _nullPS, _packCBytes, _packCString, _packString, _psToByteArray, _putPS, _reversePS, _spanPS, _splitAtPS, _substrPS, _tailPS, _takePS, _takeWhilePS, _unpackPS, _wordsPS) @@ -93,29 +94,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -132,12 +135,18 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} abort :: IOError -> [Response] -> [Request] {-# GHC_PRAGMA _A_ 2 _U_ 00 _N_ _S_ "A" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: [Response]) -> _!_ _NIL_ [Request] [] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: IOError) -> _ORIG_ PreludeIO done _N_ #-} appendBinChan :: [Char] -> Bin -> (IOError -> [Response] -> [Request]) -> ([Response] -> [Request]) -> [Response] -> [Request] @@ -207,7 +216,7 @@ writeFile :: [Char] -> [Char] -> (IOError -> [Response] -> [Request]) -> ([Respo (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -227,7 +236,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -241,23 +250,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -291,17 +300,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -313,7 +322,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -449,7 +458,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/Prelude_mp.hi b/ghc/lib/prelude/Prelude_mp.hi index 3eadd6eb96e82359953524e42dc71e377e2fc833..ee051f93771f3d45a2bbb6a4e761e7293772fd66 100644 --- a/ghc/lib/prelude/Prelude_mp.hi +++ b/ghc/lib/prelude/Prelude_mp.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(IOError, Request, Response, SigAct, abort, appendBinChan, appendBinFile, appendChan, appendFile, binDispatch, deleteFile, done, echo, exit, getArgs, getEnv, getProgName, interact, print, prints, readBinChan, readBinFile, readChan, readFile, setEnv, sigAction, statusChan, statusFile, stdecho, stderr, stdin, stdout, strDispatch, strListDispatch, succDispatch, writeBinFile, writeFile) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) import PreludePS(_PackedString, _appendPS, _breakPS, _byteArrayToPS, _concatPS, _consPS, _dropPS, _dropWhilePS, _filterPS, _foldlPS, _foldrPS, _headPS, _indexPS, _lengthPS, _linesPS, _mapPS, _nilPS, _nullPS, _packCBytes, _packCString, _packString, _psToByteArray, _putPS, _reversePS, _spanPS, _splitAtPS, _substrPS, _tailPS, _takePS, _takeWhilePS, _unpackPS, _wordsPS) @@ -93,29 +94,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -132,12 +135,18 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} abort :: IOError -> [Response] -> [Request] {-# GHC_PRAGMA _A_ 2 _U_ 00 _N_ _S_ "A" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: [Response]) -> _!_ _NIL_ [Request] [] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: IOError) -> _ORIG_ PreludeIO done _N_ #-} appendBinChan :: [Char] -> Bin -> (IOError -> [Response] -> [Request]) -> ([Response] -> [Request]) -> [Response] -> [Request] @@ -207,7 +216,7 @@ writeFile :: [Char] -> [Char] -> (IOError -> [Response] -> [Request]) -> ([Respo (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -227,7 +236,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -241,23 +250,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -291,17 +300,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -313,7 +322,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -449,7 +458,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/Prelude_p.hi b/ghc/lib/prelude/Prelude_p.hi index c5f7651ef181522b4a59174acd9b7887ffd4c60d..a882dd5f4f7a1c0d1ae7b35b4b2c9ef5b0e61496 100644 --- a/ghc/lib/prelude/Prelude_p.hi +++ b/ghc/lib/prelude/Prelude_p.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(IOError, Request, Response, SigAct, abort, appendBinChan, appendBinFile, appendChan, appendFile, binDispatch, deleteFile, done, echo, exit, getArgs, getEnv, getProgName, interact, print, prints, readBinChan, readBinFile, readChan, readFile, setEnv, sigAction, statusChan, statusFile, stdecho, stderr, stdin, stdout, strDispatch, strListDispatch, succDispatch, writeBinFile, writeFile) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) import PreludePS(_PackedString, _appendPS, _breakPS, _byteArrayToPS, _concatPS, _consPS, _dropPS, _dropWhilePS, _filterPS, _foldlPS, _foldrPS, _headPS, _indexPS, _lengthPS, _linesPS, _mapPS, _nilPS, _nullPS, _packCBytes, _packCString, _packString, _psToByteArray, _putPS, _reversePS, _spanPS, _splitAtPS, _substrPS, _tailPS, _takePS, _takeWhilePS, _unpackPS, _wordsPS) @@ -93,29 +94,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -132,12 +135,18 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} abort :: IOError -> [Response] -> [Request] {-# GHC_PRAGMA _A_ 2 _U_ 00 _N_ _S_ "A" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: [Response]) -> _!_ _NIL_ [Request] [] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: IOError) -> _ORIG_ PreludeIO done _N_ #-} appendBinChan :: [Char] -> Bin -> (IOError -> [Response] -> [Request]) -> ([Response] -> [Request]) -> [Response] -> [Request] @@ -207,7 +216,7 @@ writeFile :: [Char] -> [Char] -> (IOError -> [Response] -> [Request]) -> ([Respo (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -227,7 +236,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -241,23 +250,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -291,17 +300,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -313,7 +322,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -433,7 +442,7 @@ readSigned :: Real a => ([Char] -> [(a, [Char])]) -> [Char] -> [(a, [Char])] reads :: Text a => [Char] -> [(a, [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(SAAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Bool] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Bool) _N_ }, [ [Char] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Char) _N_ }, [ [Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Double) _N_ }, [ [Float] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Int) _N_ }, [ [Integer] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Char]) _N_ }, [ [[Int]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Int]) _N_ }, [ [Complex Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ () ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} show :: Text a => a -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: ()) -> case u0 of { _ALG_ _TUP_0 -> _NOREP_S_ "()"; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} showChar :: Char -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Char) (u1 :: [Char]) -> _!_ (:) [Char] [u0, u1] _N_ #-} showFloat :: RealFloat a => a -> [Char] -> [Char] @@ -449,7 +458,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/Prelude_t.hi b/ghc/lib/prelude/Prelude_t.hi index 3eadd6eb96e82359953524e42dc71e377e2fc833..d41ef85ff1ab888556755cd49384d0a7df74a3c3 100644 --- a/ghc/lib/prelude/Prelude_t.hi +++ b/ghc/lib/prelude/Prelude_t.hi @@ -1,9 +1,10 @@ {-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface Prelude where -import PreludeArray((!), (//), Array, Assoc, _ByteArray, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) +import PreludeArray((!), (//), Array, Assoc, _ByteArray, _arrEleBottom, accum, accumArray, amap, array, assocs, bounds, elems, indices, ixmap, listArray) import PreludeBuiltin(Bin, Char(..), Int(..), Integer(..), List(..), Tuple0, Tuple2, Tuple3, Tuple4, Tuple5, Tuple6, Tuple7, _Addr(..), _RealWorld(..), _State(..)) import PreludeComplex(Complex, cis, conjugate, imagPart, magnitude, mkPolar, phase, polar, realPart) -import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _readList, _showList, _showRational) +import PreludeCore(Bool(..), Eq(..), Fractional(..), Integral(..), Ix(..), Num(..), Ord(..), Real(..), RealFloat(..), RealFrac(..), Text(..), _rangeComplaint_Ix_Int, _readList, _showList, _showRational) +import PreludeGlaST(_MutableArray, _freezeArray, _newArray) import PreludeIO(IOError, Request, Response, SigAct, abort, appendBinChan, appendBinFile, appendChan, appendFile, binDispatch, deleteFile, done, echo, exit, getArgs, getEnv, getProgName, interact, print, prints, readBinChan, readBinFile, readChan, readFile, setEnv, sigAction, statusChan, statusFile, stdecho, stderr, stdin, stdout, strDispatch, strListDispatch, succDispatch, writeBinFile, writeFile) import PreludeList((!!), (++), (\\), all, and, any, break, concat, cycle, drop, dropWhile, elem, filter, foldl1, foldr1, genericLength, head, init, iterate, last, length, lines, map, maximum, minimum, notElem, nub, null, or, partition, product, products, repeat, reverse, scanl, scanl1, scanr, scanr1, span, splitAt, sum, sums, tail, take, takeWhile, transpose, unlines, unwords, unzip, unzip3, unzip4, unzip5, unzip6, unzip7, words, zip, zip3, zip4, zip5, zip6, zip7, zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7) import PreludePS(_PackedString, _appendPS, _breakPS, _byteArrayToPS, _concatPS, _consPS, _dropPS, _dropWhilePS, _filterPS, _foldlPS, _foldrPS, _headPS, _indexPS, _lengthPS, _linesPS, _mapPS, _nilPS, _nullPS, _packCBytes, _packCString, _packString, _psToByteArray, _putPS, _reversePS, _spanPS, _splitAtPS, _substrPS, _tailPS, _takePS, _takeWhilePS, _unpackPS, _wordsPS) @@ -93,29 +94,31 @@ until :: (a -> Bool) -> (a -> a) -> a -> a (||) :: Bool -> Bool -> Bool {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "EL" _F_ _ALWAYS_ \ (u0 :: Bool) (u1 :: Bool) -> case u0 of { _ALG_ True -> _!_ True [] []; False -> u1; _NO_DEFLT_ } _N_ #-} (!) :: Ix a => Array a b -> a -> b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(AASA)U(LP)L" {_A_ 4 _U_ 1222 _N_ _N_ _F_ _IF_ARGS_ 2 4 XXXX 7 _/\_ u0 u1 -> \ (u2 :: (u0, u0) -> u0 -> Int) (u3 :: (u0, u0)) (u4 :: Array# u1) (u5 :: u0) -> case _APP_ u2 [ u3, u5 ] of { _ALG_ I# (u6 :: Int#) -> case _#_ indexArray# [u1] [u4, u6] of { _ALG_ _Lift (u7 :: u1) -> u7; _NO_DEFLT_ }; _NO_DEFLT_ } _N_} _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: Array u0 u1) (u4 :: u0) -> case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> case u3 of { _ALG_ _Array (u9 :: (u0, u0)) (ua :: Array# u1) -> case _APP_ u7 [ u9, u4 ] of { _ALG_ I# (ub :: Int#) -> case _#_ indexArray# [u1] [ua, ub] of { _ALG_ _Lift (uc :: u1) -> uc; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(U(P)U(P))" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (//) :: Ix a => Array a b -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(U(P)U(P))P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(SS)P)S" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "U(LSLL)LS" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} +_arrEleBottom :: a + {-# GHC_PRAGMA _A_ 0 _N_ _N_ _S_ _!_ _N_ _N_ #-} accum :: Ix b => (c -> a -> c) -> Array b c -> [Assoc b a] -> Array b c - {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 2 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1222 _N_ _S_ "U(ASLA)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 222 _N_ _N_ _N_ _N_ } #-} accumArray :: Ix b => (c -> a -> c) -> c -> (b, b) -> [Assoc b a] -> Array b c {-# GHC_PRAGMA _A_ 5 _U_ 22222 _N_ _S_ "U(ASLA)LLLL" _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 4 _U_ 2222 _N_ _N_ _N_ _N_ } #-} amap :: Ix b => (a -> c) -> Array b a -> Array b c {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(U(P)U(P))P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LU(U(SS)P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} array :: Ix a => (a, a) -> [Assoc a b] -> Array a b - {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)S" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)S" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ "SSS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) (u3 :: (u0, u0)) (u4 :: [Assoc u0 u1]) -> let {(u9 :: (u0, u0) -> u0 -> Int) = case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u0}}) (u6 :: (u0, u0) -> [u0]) (u7 :: (u0, u0) -> u0 -> Int) (u8 :: (u0, u0) -> u0 -> Bool) -> u7; _NO_DEFLT_ }} in case u3 of { _ALG_ _TUP_2 (ua :: u0) (ub :: u0) -> let {(ux :: _forall_ a$z1 =>_State a$z1 -> (Array u0 u1, _State a$z1)) = _/\_ u12 -> \ (ud :: _State u12) -> let {(ue :: u1) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u1 }} in case u2 of { _ALG_ _TUP_4 (uf :: {{Ord u0}}) (ug :: (u0, u0) -> [u0]) (uh :: (u0, u0) -> u0 -> Int) (ui :: (u0, u0) -> u0 -> Bool) -> case ud of { _ALG_ S# (uj :: State# u12) -> case _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _newArray { u12 } { u0 } { u1 } [ ug, uh, u3, ue, uj ] of { _ALG_ _TUP_2 (uk :: _MutableArray u12 u0 u1) (ul :: _State u12) -> case uk of { _ALG_ _MutableArray (um :: (u0, u0)) (un :: MutableArray# u12 u1) -> let {(uv :: _State u12 -> Assoc u0 u1 -> _State u12) = \ (uo :: _State u12) (up :: Assoc u0 u1) -> case uo of { _ALG_ S# (uq :: State# u12) -> case up of { _ALG_ (:=) (ur :: u0) (us :: u1) -> case _APP_ u9 [ u3, ur ] of { _ALG_ I# (ut :: Int#) -> case _#_ writeArray# [u12, u1] [un, ut, us, uq] of { _PRIM_ (uu :: State# u12) -> _!_ S# [u12] [uu] }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u12) } { (Assoc u0 u1) } [ uv, ul, u4 ] of { _ALG_ S# (uw :: State# u12) -> _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _WRKR_ _ORIG_ PreludeGlaST _freezeArray { u12 } { u0 } { u1 } [ ug, uh, um, un, uw ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array u0 u1) } [ ux ]; _NO_DEFLT_ } _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: (Int, Int)) (u2 :: [Assoc Int u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> let {(ut :: _forall_ a$z1 =>_State a$z1 -> (Array Int u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u3 of { _ALG_ I# (u8 :: Int#) -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u6 of { _ALG_ S# (ua :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ u8, u9, u7, ua ] of { _ALG_ _TUP_2 (ub :: _MutableArray u5 Int u0) (uc :: _State u5) -> case ub of { _ALG_ _MutableArray (ud :: (Int, Int)) (ue :: MutableArray# u5 u0) -> let {(un :: _State u5 -> Assoc Int u0 -> _State u5) = \ (uf :: _State u5) (ug :: Assoc Int u0) -> case uf of { _ALG_ S# (uh :: State# u5) -> case ug of { _ALG_ (:=) (ui :: Int) (uj :: u0) -> case ui of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [u8, uk] of { _ALG_ True -> case _#_ leInt# [] [uk, u9] of { _ALG_ True -> case _#_ minusInt# [] [uk, u8] of { _PRIM_ (ul :: Int#) -> case _#_ writeArray# [u5, u0] [ue, ul, uj, uh] of { _PRIM_ (um :: State# u5) -> _!_ S# [u5] [um] } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uk, u8, u9 ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc Int u0) } [ un, uc, u2 ] of { _ALG_ S# (uo :: State# u5) -> case ud of { _ALG_ _TUP_2 (up :: Int) (uq :: Int) -> case up of { _ALG_ I# (ur :: Int#) -> case uq of { _ALG_ I# (us :: Int#) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, (Int), _N_ ] { u5 } { u0 } [ ur, us, ue, uo ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array Int u0) } [ ut ]; _NO_DEFLT_ } _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "SS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: ((Int, Int), (Int, Int))) (u2 :: [Assoc (Int, Int) u0]) -> case u1 of { _ALG_ _TUP_2 (u3 :: (Int, Int)) (u4 :: (Int, Int)) -> let {(uF :: _forall_ a$z1 =>_State a$z1 -> (Array (Int, Int) u0, _State a$z1)) = _/\_ u5 -> \ (u6 :: _State u5) -> let {(u7 :: u0) = _TYAPP_ _ORIG_ PreludeArray _arrEleBottom { u0 }} in case u6 of { _ALG_ S# (u8 :: State# u5) -> case _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _newArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ u3, u4, u7, u8 ] of { _ALG_ _TUP_2 (u9 :: _MutableArray u5 (Int, Int) u0) (ua :: _State u5) -> case u9 of { _ALG_ _MutableArray (ub :: ((Int, Int), (Int, Int))) (uc :: MutableArray# u5 u0) -> let {(uB :: _State u5 -> Assoc (Int, Int) u0 -> _State u5) = \ (ud :: _State u5) (ue :: Assoc (Int, Int) u0) -> case ud of { _ALG_ S# (uf :: State# u5) -> case ue of { _ALG_ (:=) (ug :: (Int, Int)) (uh :: u0) -> case u3 of { _ALG_ _TUP_2 (ui :: Int) (uj :: Int) -> case u4 of { _ALG_ _TUP_2 (uk :: Int) (ul :: Int) -> case ug of { _ALG_ _TUP_2 (um :: Int) (un :: Int) -> case ui of { _ALG_ I# (uo :: Int#) -> case uk of { _ALG_ I# (up :: Int#) -> case um of { _ALG_ I# (uq :: Int#) -> case _#_ leInt# [] [uo, uq] of { _ALG_ True -> case _#_ leInt# [] [uq, up] of { _ALG_ True -> case _#_ minusInt# [] [uq, uo] of { _PRIM_ (ur :: Int#) -> case uj of { _ALG_ I# (us :: Int#) -> case ul of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> case _#_ leInt# [] [ut, ut] of { _ALG_ True -> case _#_ minusInt# [] [ut, us] of { _PRIM_ (uu :: Int#) -> case _#_ plusInt# [] [uu, 1#] of { _PRIM_ (uv :: Int#) -> case _#_ timesInt# [] [ur, uv] of { _PRIM_ (uw :: Int#) -> case un of { _ALG_ I# (ux :: Int#) -> case _#_ leInt# [] [us, ux] of { _ALG_ True -> case _#_ leInt# [] [ux, ut] of { _ALG_ True -> case _#_ minusInt# [] [ux, us] of { _PRIM_ (uy :: Int#) -> case _#_ plusInt# [] [uw, uy] of { _PRIM_ (uz :: Int#) -> case _#_ writeArray# [u5, u0] [uc, uz, uh, uf] of { _PRIM_ (uA :: State# u5) -> _!_ S# [u5] [uA] } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ux, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ } } } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ ut, us, ut ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; False -> _APP_ _TYAPP_ _ORIG_ PreludeCore _rangeComplaint_Ix_Int { (_State u5) } [ uq, uo, up ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in case _APP_ _TYAPP_ _TYAPP_ foldl { (_State u5) } { (Assoc (Int, Int) u0) } [ uB, ua, u2 ] of { _ALG_ S# (uC :: State# u5) -> case ub of { _ALG_ _TUP_2 (uD :: (Int, Int)) (uE :: (Int, Int)) -> _APP_ _TYAPP_ _TYAPP_ _WRKR_ _SPEC_ _ORIG_ PreludeGlaST _freezeArray [ _N_, ((Int, Int)), _N_ ] { u5 } { u0 } [ uD, uE, uc, uC ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _runST { (Array (Int, Int) u0) } [ uF ]; _NO_DEFLT_ } _N_ } #-} assocs :: Ix a => Array a b -> [Assoc a b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(uh :: _forall_ a$z1 =>(Assoc u0 u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: Assoc u0 u1 -> u8 -> u8) (ua :: u8) -> let {(uf :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in let {(ue :: Assoc u0 u1) = _!_ (:=) [u0, u1] [ub, ud]} in _APP_ u9 [ ue, uc ]} in let {(ug :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ uf, ua, ug ]} in _APP_ _TYAPP_ _build { (Assoc u0 u1) } [ uh ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ub :: _forall_ a$z1 =>(Assoc Int u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc Int u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc Int u0) = _!_ (:=) [Int, u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc Int u0) } [ ub ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ub :: _forall_ a$z1 =>(Assoc (Int, Int) u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: Assoc (Int, Int) u0 -> u2 -> u2) (u4 :: u2) -> let {(u9 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in let {(u8 :: Assoc (Int, Int) u0) = _!_ (:=) [(Int, Int), u0] [u5, u7]} in _APP_ u3 [ u8, u6 ]} in let {(ua :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u9, u4, ua ]} in _APP_ _TYAPP_ _build { (Assoc (Int, Int) u0) } [ ub ] _N_ } #-} bounds :: Array b a -> (b, b) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(U(LL)P)" {_A_ 3 _U_ 220 _N_ _N_ _F_ _IF_ARGS_ 2 3 XXX 3 _/\_ u0 u1 -> \ (u2 :: u1) (u3 :: u1) (u4 :: Array# u0) -> _!_ _TUP_2 [u1, u1] [u2, u3] _N_} _F_ _IF_ARGS_ 2 1 C 2 _/\_ u0 u1 -> \ (u2 :: Array u1 u0) -> case u2 of { _ALG_ _Array (u3 :: (u1, u1)) (u4 :: Array# u0) -> u3; _NO_DEFLT_ } _N_ #-} elems :: Ix a => Array a b -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASLA)" {_A_ 3 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u0}}) -> let {(u4 :: _forall_ a$z1 =>Array u0 a$z1 -> [u0]) = _/\_ u3 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray indices { u3 } { u0 } [ u2 ]} in let {(u6 :: _forall_ a$z1 =>Array u0 a$z1 -> u0 -> a$z1) = _/\_ u5 -> _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray (!) { u0 } { u5 } [ u2 ]} in \ (u7 :: Array u0 u1) -> let {(ug :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: u1 -> u8 -> u8) (ua :: u8) -> let {(ue :: u0 -> u8 -> u8) = \ (ub :: u0) (uc :: u8) -> let {(ud :: u1) = _APP_ _TYAPP_ u6 { u1 } [ u7, ub ]} in _APP_ u9 [ ud, uc ]} in let {(uf :: [u0]) = _APP_ _TYAPP_ u4 { u1 } [ u7 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u8 } [ ue, ua, uf ]} in _APP_ _TYAPP_ _build { u1 } [ ug ] _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: Int -> u2 -> u2) = \ (u5 :: Int) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ (Int), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [Int]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, (Int) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 1 _U_ 2 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u2 -> \ (u3 :: u0 -> u2 -> u2) (u4 :: u2) -> let {(u8 :: (Int, Int) -> u2 -> u2) = \ (u5 :: (Int, Int)) (u6 :: u2) -> let {(u7 :: u0) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray (!) [ ((Int, Int)), _N_ ] { u0 } [ u1, u5 ]} in _APP_ u3 [ u7, u6 ]} in let {(u9 :: [(Int, Int)]) = _APP_ _TYAPP_ _SPEC_ _ORIG_ PreludeArray indices [ _N_, ((Int, Int)) ] { u0 } [ u1 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { (Int, Int) } { u2 } [ u8, u4, u9 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ } #-} indices :: Ix b => Array b a -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "U(ASAA)L" {_A_ 2 _U_ 11 _N_ _N_ _F_ _IF_ARGS_ 2 2 XC 5 _/\_ u0 u1 -> \ (u2 :: (u1, u1) -> [u1]) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in _APP_ u2 [ u6 ] _N_} _F_ _IF_ARGS_ 2 2 CC 6 _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u6 :: (u1, u1)) = case u3 of { _ALG_ _Array (u4 :: (u1, u1)) (u5 :: Array# u0) -> u4; _NO_DEFLT_ }} in case u2 of { _ALG_ _TUP_4 (u7 :: {{Ord u1}}) (u8 :: (u1, u1) -> [u1]) (u9 :: (u1, u1) -> u1 -> Int) (ua :: (u1, u1) -> u1 -> Bool) -> _APP_ u8 [ u6 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(U(P)U(P))P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(U(SS)P)" {_A_ 3 _U_ 220 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: {{Ix u1}}) (u3 :: Array u1 u0) -> let {(u4 :: (u1, u1)) = _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { u1 } [ u3 ]} in case u2 of { _ALG_ _TUP_4 (u5 :: {{Ord u1}}) (u6 :: (u1, u1) -> [u1]) (u7 :: (u1, u1) -> u1 -> Int) (u8 :: (u1, u1) -> u1 -> Bool) -> _APP_ u6 [ u4 ]; _NO_DEFLT_ } _SPECIALISE_ [ _N_, Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array Int u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { Int } [ u1 ] of { _ALG_ _TUP_2 (u2 :: Int) (u3 :: Int) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _LETREC_ {(u5 :: Int# -> [Int]) = \ (u6 :: Int#) -> case u3 of { _ALG_ I# (u7 :: Int#) -> case _#_ leInt# [] [u6, u7] of { _ALG_ True -> let {(u9 :: [Int]) = case _#_ plusInt# [] [u6, 1#] of { _PRIM_ (u8 :: Int#) -> _APP_ u5 [ u8 ] }} in let {(ua :: Int) = _!_ I# [] [u6]} in _!_ (:) [Int] [ua, u9]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ u5 [ u4 ]; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ }, [ _N_, (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: Array (Int, Int) u0) -> case _APP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeArray bounds { u0 } { (Int, Int) } [ u1 ] of { _ALG_ _TUP_2 (u2 :: (Int, Int)) (u3 :: (Int, Int)) -> case u2 of { _ALG_ _TUP_2 (u4 :: Int) (u5 :: Int) -> case u3 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> let {(uy :: _forall_ a$z1 =>((Int, Int) -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u8 -> \ (u9 :: (Int, Int) -> u8 -> u8) (ua :: u8) -> let {(up :: Int -> u8 -> u8) = \ (ub :: Int) (uc :: u8) -> let {(ug :: Int -> u8 -> u8) = \ (ud :: Int) (ue :: u8) -> let {(uf :: (Int, Int)) = _!_ _TUP_2 [Int, Int] [ub, ud]} in _APP_ u9 [ uf, ue ]} in let {(uo :: [Int]) = case u5 of { _ALG_ I# (uh :: Int#) -> _LETREC_ {(ui :: Int# -> [Int]) = \ (uj :: Int#) -> case u7 of { _ALG_ I# (uk :: Int#) -> case _#_ leInt# [] [uj, uk] of { _ALG_ True -> let {(um :: [Int]) = case _#_ plusInt# [] [uj, 1#] of { _PRIM_ (ul :: Int#) -> _APP_ ui [ ul ] }} in let {(un :: Int) = _!_ I# [] [uj]} in _!_ (:) [Int] [un, um]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ui [ uh ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ ug, uc, uo ]} in let {(ux :: [Int]) = case u4 of { _ALG_ I# (uq :: Int#) -> _LETREC_ {(ur :: Int# -> [Int]) = \ (us :: Int#) -> case u6 of { _ALG_ I# (ut :: Int#) -> case _#_ leInt# [] [us, ut] of { _ALG_ True -> let {(uv :: [Int]) = case _#_ plusInt# [] [us, 1#] of { _PRIM_ (uu :: Int#) -> _APP_ ur [ uu ] }} in let {(uw :: Int) = _!_ I# [] [us]} in _!_ (:) [Int] [uw, uv]; False -> _!_ _NIL_ [Int] []; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ ur [ uq ]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { Int } { u8 } [ up, ua, ux ]} in _APP_ _TYAPP_ _build { (Int, Int) } [ uy ]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ } _N_ } #-} ixmap :: (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c {-# GHC_PRAGMA _A_ 2 _U_ 12222 _N_ _S_ "U(ASLA)L" {_A_ 6 _U_ 222222 _N_ _N_ _N_ _N_} _N_ _N_ #-} listArray :: Ix a => (a, a) -> [b] -> Array a b - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASLA)" {_A_ 4 _U_ 2221 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 221 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 112 _N_ _S_ "U(ASLA)U(LL)L" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(U(P)U(P))L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int), _N_ ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(SS)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} cis :: RealFloat a => a -> Complex a {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} conjugate :: RealFloat a => Complex a -> Complex a @@ -132,12 +135,18 @@ polar :: RealFloat a => Complex a -> (a, a) {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ } #-} realPart :: Complex a -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "U(SA)" {_A_ 1 _U_ 1 _N_ _N_ _F_ _IF_ARGS_ 1 1 X 1 _/\_ u0 -> \ (u1 :: u0) -> u1 _N_} _F_ _IF_ARGS_ 1 1 C 2 _/\_ u0 -> \ (u1 :: Complex u0) -> case u1 of { _ALG_ (:+) (u2 :: u0) (u3 :: u0) -> u2; _NO_DEFLT_ } _N_ #-} +_rangeComplaint_Ix_Int :: Int# -> Int# -> Int# -> a + {-# GHC_PRAGMA _A_ 3 _U_ 222 _N_ _S_ _!_ _N_ _N_ #-} _readList :: ([Char] -> [(a, [Char])]) -> [Char] -> [([a], [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ #-} _showList :: (a -> [Char] -> [Char]) -> [a] -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 212 _N_ _S_ "LS" _N_ _N_ #-} _showRational :: Int -> Ratio Integer -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LU(U(PPP)L)" {_A_ 5 _U_ 22222 _N_ _N_ _N_ _N_} _N_ _N_ #-} +_freezeArray :: Ix b => _MutableArray a b c -> _State a -> (Array b c, _State a) + {-# GHC_PRAGMA _A_ 3 _U_ 111 _N_ _S_ "U(ASLA)U(U(LL)P)U(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(U(P)U(P))P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(U(SS)P)U(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} +_newArray :: Ix b => (b, b) -> c -> _State a -> (_MutableArray a b c, _State a) + {-# GHC_PRAGMA _A_ 4 _U_ 1221 _N_ _S_ "U(ASLA)U(LL)LU(P)" {_A_ 5 _U_ 11222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ _N_, Int, _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(U(P)U(P))LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ _N_, (Int, Int), _N_ ] 1 { _A_ 3 _U_ 121 _N_ _S_ "U(SS)LU(P)" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} abort :: IOError -> [Response] -> [Request] {-# GHC_PRAGMA _A_ 2 _U_ 00 _N_ _S_ "A" {_A_ 1 _U_ 0 _N_ _N_ _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: [Response]) -> _!_ _NIL_ [Request] [] _N_} _F_ _IF_ARGS_ 0 1 X 1 \ (u0 :: IOError) -> _ORIG_ PreludeIO done _N_ #-} appendBinChan :: [Char] -> Bin -> (IOError -> [Response] -> [Request]) -> ([Response] -> [Request]) -> [Response] -> [Request] @@ -207,7 +216,7 @@ writeFile :: [Char] -> [Char] -> (IOError -> [Response] -> [Request]) -> ([Respo (!!) :: Integral a => [b] -> a -> b {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASAAAAAA)AAA)AAAAAAAAAS)" {_A_ 3 _U_ 11112 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(P)" {_A_ 2 _U_ 12 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SU(PPP)" {_A_ 4 _U_ 1222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} (++) :: [a] -> [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) (u2 :: [u0]) -> let {(u6 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u4, u5, u1 ]} in _APP_ _TYAPP_ _augment { u0 } [ u6, u2 ] _N_ #-} (\\) :: Eq a => [a] -> [a] -> [a] {-# GHC_PRAGMA _A_ 3 _U_ 122 _N_ _S_ "LLS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 22 _N_ _S_ "LS" _N_ _N_ } #-} all :: (a -> Bool) -> [a] -> Bool @@ -227,7 +236,7 @@ drop :: Integral a => a -> [b] -> [b] dropWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ #-} elem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u4; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ eqChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ eqInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ True [] []; (u9 :: Int#) -> _!_ False [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (==) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Char] } [ u3, u1 ] _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Int]) (u1 :: [[Int]]) -> let {(u3 :: [Int] -> Bool) = \ (u2 :: [Int]) -> _APP_ _CONSTM_ Eq (==) ([Int]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList any { [Int] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ eqInt# [] [u5, u8] of { _ALG_ True -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ eqInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; False -> _!_ False [] []; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList any { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Int] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} filter :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u7; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} foldl1 :: (a -> a -> a) -> [a] -> a @@ -241,23 +250,23 @@ head :: [a] -> a init :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} iterate :: (a -> a) -> a -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ub :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: (u0 -> u0) -> u0 -> u3) = \ (u7 :: u0 -> u0) (u8 :: u0) -> let {(ua :: u3) = let {(u9 :: u0) = _APP_ u7 [ u8 ]} in _APP_ u6 [ u7, u9 ]} in _APP_ u4 [ u8, ua ]} in _APP_ u6 [ u1, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ub ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> u0) (u2 :: u0) -> let {(ua :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> _LETREC_ {(u6 :: u0 -> u3) = \ (u7 :: u0) -> let {(u9 :: u3) = let {(u8 :: u0) = _APP_ u1 [ u7 ]} in _APP_ u6 [ u8 ]} in _APP_ u4 [ u7, u9 ]} in _APP_ u6 [ u2 ]} in _APP_ _TYAPP_ _build { u0 } [ ua ] _N_ #-} last :: [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} length :: [a] -> Int - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Int) = _!_ I# [] [0#]} in let {(u7 :: Int -> u0 -> Int) = \ (u3 :: Int) (u4 :: u0) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case _#_ plusInt# [] [u5, 1#] of { _PRIM_ (u6 :: Int#) -> _!_ I# [] [u6] }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldl { Int } { u0 } [ u7, u2, u1 ] _N_ #-} lines :: [Char] -> [[Char]] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _S_ "S" _N_ _N_ #-} map :: (a -> b) -> [a] -> [b] - {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ua :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(u9 :: u0 -> u4 -> u4) = \ (u7 :: u0) -> let {(u8 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ u9, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ua ] _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: u0 -> u1) (u3 :: [u0]) -> let {(ub :: _forall_ a$z1 =>(u1 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u1 -> u4 -> u4) (u6 :: u4) -> let {(ua :: u0 -> u4 -> u4) = \ (u7 :: u0) (u8 :: u4) -> let {(u9 :: u1) = _APP_ u2 [ u7 ]} in _APP_ u5 [ u9, u8 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u4 } [ ua, u6, u3 ]} in _APP_ _TYAPP_ _build { u1 } [ ub ] _N_ #-} maximum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} minimum :: Ord a => [a] -> a {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _N_ _SPECIALISE_ [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} notElem :: Eq a => a -> [a] -> Bool - {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "LLS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) (u2 :: u0) (u3 :: [u0]) -> let {(u6 :: u0 -> u0 -> Bool) = case u1 of { _ALG_ _TUP_2 (u4 :: u0 -> u0 -> Bool) (u5 :: u0 -> u0 -> Bool) -> u5; _NO_DEFLT_ }} in let {(u8 :: u0 -> Bool) = \ (u7 :: u0) -> _APP_ u6 [ u2, u7 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { u0 } [ u8, u3 ] _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Char) (u1 :: [Char]) -> let {(u5 :: Char -> Bool) = \ (u2 :: Char) -> case u0 of { _ALG_ C# (u3 :: Char#) -> case u2 of { _ALG_ C# (u4 :: Char#) -> _#_ neChar# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Char } [ u5, u1 ] _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Int) (u1 :: [Int]) -> let {(u5 :: Int -> Bool) = \ (u2 :: Int) -> case u0 of { _ALG_ I# (u3 :: Int#) -> case u2 of { _ALG_ I# (u4 :: Int#) -> _#_ neInt# [] [u3, u4]; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Int } [ u5, u1 ] _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: Integer) (u1 :: [Integer]) -> let {(ua :: Integer -> Bool) = \ (u2 :: Integer) -> case u0 of { _ALG_ J# (u3 :: Int#) (u4 :: Int#) (u5 :: ByteArray#) -> case u2 of { _ALG_ J# (u6 :: Int#) (u7 :: Int#) (u8 :: ByteArray#) -> case _#_ cmpInteger# [] [u3, u4, u5, u6, u7, u8] of { _PRIM_ 0# -> _!_ False [] []; (u9 :: Int#) -> _!_ True [] [] }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { Integer } [ ua, u1 ] _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: [Char]) (u1 :: [[Char]]) -> let {(u3 :: [Char] -> Bool) = \ (u2 :: [Char]) -> _APP_ _CONSTM_ Eq (/=) ([Char]) [ u0, u2 ]} in _APP_ _TYAPP_ _ORIG_ PreludeList all { [Char] } [ u3, u1 ] _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ \ (u0 :: (Int, Int)) (u1 :: [(Int, Int)]) -> let {(ub :: (Int, Int) -> Bool) = \ (u2 :: (Int, Int)) -> case u0 of { _ALG_ _TUP_2 (u3 :: Int) (u4 :: Int) -> case u3 of { _ALG_ I# (u5 :: Int#) -> case u2 of { _ALG_ _TUP_2 (u6 :: Int) (u7 :: Int) -> case u6 of { _ALG_ I# (u8 :: Int#) -> case _#_ neInt# [] [u5, u8] of { _ALG_ True -> _!_ True [] []; False -> case u4 of { _ALG_ I# (u9 :: Int#) -> case u7 of { _ALG_ I# (ua :: Int#) -> _#_ neInt# [] [u9, ua]; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }; _NO_DEFLT_ }} in _APP_ _TYAPP_ _ORIG_ PreludeList all { (Int, Int) } [ ub, u1 ] _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 121 _N_ _N_ _N_ _SPECIALISE_ [ Char ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ [Char] ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 21 _N_ _S_ "LS" _N_ _N_ } #-} nub :: Eq a => [a] -> [a] - {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "LS" _N_ _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 11 _N_ _N_ _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: {{Eq u0}}) -> let {(u2 :: u0 -> [u0] -> Bool) = _APP_ _TYAPP_ _ORIG_ PreludeList elem { u0 } [ u1 ]} in \ (u3 :: [u0]) -> let {(uf :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u4 -> \ (u5 :: u0 -> u4 -> u4) (u6 :: u4) -> _LETREC_ {(u7 :: [u0] -> [u0] -> u4) = \ (u8 :: [u0]) (u9 :: [u0]) -> case u8 of { _ALG_ _NIL_ -> u6; (:) (ua :: u0) (ub :: [u0]) -> case _APP_ u2 [ ua, u9 ] of { _ALG_ True -> _APP_ u7 [ ub, u9 ]; False -> let {(ud :: u4) = let {(uc :: [u0]) = _!_ (:) [u0] [ua, u9]} in _APP_ u7 [ ub, uc ]} in _APP_ u5 [ ua, ud ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ue :: [u0]) = _!_ _NIL_ [u0] []} in _APP_ u7 [ u3, ue ]} in _APP_ _TYAPP_ _build { u0 } [ uf ] _SPECIALISE_ [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Int]) -> let {(uc :: _forall_ a$z1 =>(Int -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Int -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Int] -> [Int] -> u1) = \ (u5 :: [Int]) (u6 :: [Int]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: Int) (u8 :: [Int]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ (Int) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [Int]) = _!_ (:) [Int] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [Int]) = _!_ _NIL_ [Int] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { Int } [ uc ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(uc :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Char]] -> [[Char]] -> u1) = \ (u5 :: [[Char]]) (u6 :: [[Char]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Char]) (u8 :: [[Char]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Char]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Char]]) = _!_ (:) [[Char]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Char]]) = _!_ _NIL_ [[Char]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Char] } [ uc ] _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Int]]) -> let {(uc :: _forall_ a$z1 =>([Int] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Int] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [[Int]] -> [[Int]] -> u1) = \ (u5 :: [[Int]]) (u6 :: [[Int]]) -> case u5 of { _ALG_ _NIL_ -> u3; (:) (u7 :: [Int]) (u8 :: [[Int]]) -> case _APP_ _SPEC_ _ORIG_ PreludeList elem [ ([Int]) ] [ u7, u6 ] of { _ALG_ True -> _APP_ u4 [ u8, u6 ]; False -> let {(ua :: u1) = let {(u9 :: [[Int]]) = _!_ (:) [[Int]] [u7, u6]} in _APP_ u4 [ u8, u9 ]} in _APP_ u2 [ u7, ua ]; _NO_DEFLT_ }; _NO_DEFLT_ }} in let {(ub :: [[Int]]) = _!_ _NIL_ [[Int]] []} in _APP_ u4 [ u0, ub ]} in _APP_ _TYAPP_ _build { [Int] } [ uc ] _N_ } #-} null :: [a] -> Bool {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: [u0]) -> let {(u2 :: Bool) = _!_ True [] []} in let {(u5 :: u0 -> Bool -> Bool) = \ (u3 :: u0) (u4 :: Bool) -> _!_ False [] []} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { Bool } [ u5, u2, u1 ] _N_ #-} or :: [Bool] -> Bool @@ -291,17 +300,17 @@ sums :: Num a => [a] -> [a] tail :: [a] -> [a] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _IF_ARGS_ 1 1 C 5 _/\_ u0 -> \ (u1 :: [u0]) -> case u1 of { _ALG_ (:) (u2 :: u0) (u3 :: [u0]) -> u3; _NIL_ -> _APP_ _TYAPP_ error { [u0] } [ _NOREP_S_ "tail{PreludeList}: tail []\n" ]; _NO_DEFLT_ } _N_ #-} take :: Integral a => a -> [b] -> [b] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(LU(U(ASSAAAAA)AAA)AAAALAAAAL)" {_A_ 5 _U_ 2121222 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "U(P)L" {_A_ 2 _U_ 21 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 3 _U_ 121 _N_ _S_ "SLL" _N_ _SPECIALISE_ [ Int, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ }, [ Integer, _N_ ] 1 { _A_ 2 _U_ 11 _N_ _S_ "SL" _N_ _N_ } #-} takeWhile :: (a -> Bool) -> [a] -> [a] {-# GHC_PRAGMA _A_ 2 _U_ 21 _N_ _S_ "LS" _F_ _ALWAYS_ _/\_ u0 -> \ (u1 :: u0 -> Bool) (u2 :: [u0]) -> let {(u9 :: _forall_ a$z1 =>(u0 -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u3 -> \ (u4 :: u0 -> u3 -> u3) (u5 :: u3) -> let {(u8 :: u0 -> u3 -> u3) = \ (u6 :: u0) (u7 :: u3) -> case _APP_ u1 [ u6 ] of { _ALG_ True -> _APP_ u4 [ u6, u7 ]; False -> u5; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { u0 } { u3 } [ u8, u5, u2 ]} in _APP_ _TYAPP_ _build { u0 } [ u9 ] _N_ #-} transpose :: [[a]] -> [[a]] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unlines :: [[Char]] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u1 :: [Char]) = _!_ _NIL_ [Char] []} in let {(u6 :: [Char] -> [Char] -> [Char]) = \ (u2 :: [Char]) (u3 :: [Char]) -> let {(u4 :: Char) = _!_ C# [] ['\o12'#]} in let {(u5 :: [Char]) = _!_ (:) [Char] [u4, u3]} in _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ u2, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { [Char] } [ u6, u1, u0 ] _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [[Char]]) -> let {(u9 :: _forall_ a$z1 =>(Char -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: Char -> u1 -> u1) (u3 :: u1) -> let {(u8 :: [Char] -> u1 -> u1) = \ (u4 :: [Char]) (u5 :: u1) -> let {(u7 :: u1) = let {(u6 :: Char) = _!_ C# [] ['\o12'#]} in _APP_ u2 [ u6, u5 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { Char } { u1 } [ u2, u7, u4 ]} in _APP_ _TYAPP_ _TYAPP_ foldr { [Char] } { u1 } [ u8, u3, u0 ]} in _APP_ _TYAPP_ _build { Char } [ u9 ] _N_ #-} unwords :: [[Char]] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip :: [(a, b)] -> ([a], [b]) - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [(u0, u1)]) -> let {(u3 :: [u0]) = _!_ _NIL_ [u0] []} in let {(u4 :: [u1]) = _!_ _NIL_ [u1] []} in let {(u5 :: ([u0], [u1])) = _!_ _TUP_2 [[u0], [u1]] [u3, u4]} in let {(ui :: (u0, u1) -> ([u0], [u1]) -> ([u0], [u1])) = \ (u6 :: (u0, u1)) (u7 :: ([u0], [u1])) -> case u6 of { _ALG_ _TUP_2 (u8 :: u0) (u9 :: u1) -> let {(uc :: [u0]) = case u7 of { _ALG_ _TUP_2 (ua :: [u0]) (ub :: [u1]) -> ua; _NO_DEFLT_ }} in let {(uf :: [u1]) = case u7 of { _ALG_ _TUP_2 (ud :: [u0]) (ue :: [u1]) -> ue; _NO_DEFLT_ }} in let {(ug :: [u0]) = _!_ (:) [u0] [u8, uc]} in let {(uh :: [u1]) = _!_ (:) [u1] [u9, uf]} in _!_ _TUP_2 [[u0], [u1]] [ug, uh]; _NO_DEFLT_ }} in _APP_ _TYAPP_ _TYAPP_ foldr { (u0, u1) } { ([u0], [u1]) } [ ui, u5, u2 ] _N_ #-} unzip3 :: [(a, b, c)] -> ([a], [b], [c]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) @@ -313,7 +322,7 @@ unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g]) {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} words :: [Char] -> [[Char]] - {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ #-} + {-# GHC_PRAGMA _A_ 1 _U_ 1 _N_ _S_ "S" _F_ _ALWAYS_ \ (u0 :: [Char]) -> let {(ug :: _forall_ a$z1 =>([Char] -> a$z1 -> a$z1) -> a$z1 -> a$z1) = _/\_ u1 -> \ (u2 :: [Char] -> u1 -> u1) (u3 :: u1) -> _LETREC_ {(u4 :: [Char] -> u1) = \ (u5 :: [Char]) -> let {(u6 :: [Char]) = _APP_ _TYAPP_ _ORIG_ PreludeList dropWhile { Char } [ _ORIG_ Prelude isSpace, u5 ]} in let {(u7 :: [Char]) = _!_ _NIL_ [Char] []} in case _APP_ _CONSTM_ Eq (==) ([Char]) [ u7, u6 ] of { _ALG_ True -> u3; False -> let {(u8 :: ([Char], [Char])) = _APP_ _TYAPP_ _ORIG_ PreludeList break { Char } [ _ORIG_ Prelude isSpace, u6 ]} in let {(ub :: [Char]) = case u8 of { _ALG_ _TUP_2 (u9 :: [Char]) (ua :: [Char]) -> u9; _NO_DEFLT_ }} in let {(ue :: [Char]) = case u8 of { _ALG_ _TUP_2 (uc :: [Char]) (ud :: [Char]) -> ud; _NO_DEFLT_ }} in let {(uf :: u1) = _APP_ u4 [ ue ]} in _APP_ u2 [ ub, uf ]; _NO_DEFLT_ }} in _APP_ u4 [ u0 ]} in _APP_ _TYAPP_ _build { [Char] } [ ug ] _N_ #-} zip :: [a] -> [b] -> [(a, b)] {-# GHC_PRAGMA _A_ 2 _U_ 11 _N_ _S_ "SL" _F_ _ALWAYS_ _/\_ u0 u1 -> \ (u2 :: [u0]) (u3 :: [u1]) -> let {(u6 :: u0 -> u1 -> (u0, u1)) = \ (u4 :: u0) (u5 :: u1) -> _!_ _TUP_2 [u0, u1] [u4, u5]} in _APP_ _TYAPP_ _TYAPP_ _TYAPP_ _ORIG_ PreludeList zipWith { u0 } { u1 } { (u0, u1) } [ u6, u2, u3 ] _N_ #-} zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] @@ -433,7 +442,7 @@ readSigned :: Real a => ([Char] -> [(a, [Char])]) -> [Char] -> [(a, [Char])] reads :: Text a => [Char] -> [(a, [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(SAAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Bool] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Bool) _N_ }, [ [Char] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Char) _N_ }, [ [Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Double) _N_ }, [ [Float] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Int) _N_ }, [ [Integer] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Char]) _N_ }, [ [[Int]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Int]) _N_ }, [ [Complex Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ () ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} show :: Text a => a -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: ()) -> case u0 of { _ALG_ _TUP_0 -> _NOREP_S_ "()"; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} showChar :: Char -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Char) (u1 :: [Char]) -> _!_ (:) [Char] [u0, u1] _N_ #-} showFloat :: RealFloat a => a -> [Char] -> [Char] @@ -449,7 +458,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/Text.hi b/ghc/lib/prelude/Text.hi index 15f2d2cc9c271e1f519fdea173359e08a13f2820..902b94a15fe8298c57efec66a733fafe1e6f802b 100644 --- a/ghc/lib/prelude/Text.hi +++ b/ghc/lib/prelude/Text.hi @@ -50,7 +50,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/Text.hs b/ghc/lib/prelude/Text.hs index 4a23b905040b1ff050d8cdb92156a55475d7179f..c51ef7e3ed7c04ba8f3ed6dfb415211c88775953 100644 --- a/ghc/lib/prelude/Text.hs +++ b/ghc/lib/prelude/Text.hs @@ -43,6 +43,7 @@ import ITup2 import ITup3 import List import Prel +import PreludeGlaST ( _MutableArray ) import PS ( _PackedString, _unpackPS ) import TyComplex -- for pragmas diff --git a/ghc/lib/prelude/Text_mc.hi b/ghc/lib/prelude/Text_mc.hi index 15f2d2cc9c271e1f519fdea173359e08a13f2820..902b94a15fe8298c57efec66a733fafe1e6f802b 100644 --- a/ghc/lib/prelude/Text_mc.hi +++ b/ghc/lib/prelude/Text_mc.hi @@ -50,7 +50,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/Text_mp.hi b/ghc/lib/prelude/Text_mp.hi index 15f2d2cc9c271e1f519fdea173359e08a13f2820..902b94a15fe8298c57efec66a733fafe1e6f802b 100644 --- a/ghc/lib/prelude/Text_mp.hi +++ b/ghc/lib/prelude/Text_mp.hi @@ -50,7 +50,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/Text_p.hi b/ghc/lib/prelude/Text_p.hi index d6ba564f5ba93559e2dcf3f812985b53d0dd6c45..012d2cae39ca62fb4a489fa5efe65fb527956a0a 100644 --- a/ghc/lib/prelude/Text_p.hi +++ b/ghc/lib/prelude/Text_p.hi @@ -34,7 +34,7 @@ readSigned :: Real a => ([Char] -> [(a, [Char])]) -> [Char] -> [(a, [Char])] reads :: Text a => [Char] -> [(a, [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(SAAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Bool] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Bool) _N_ }, [ [Char] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Char) _N_ }, [ [Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Double) _N_ }, [ [Float] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Int) _N_ }, [ [Integer] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Char]) _N_ }, [ [[Int]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Int]) _N_ }, [ [Complex Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ () ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} show :: Text a => a -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: ()) -> case u0 of { _ALG_ _TUP_0 -> _NOREP_S_ "()"; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} showChar :: Char -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Char) (u1 :: [Char]) -> _!_ (:) [Char] [u0, u1] _N_ #-} showFloat :: RealFloat a => a -> [Char] -> [Char] @@ -50,7 +50,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/Text_t.hi b/ghc/lib/prelude/Text_t.hi index 15f2d2cc9c271e1f519fdea173359e08a13f2820..04fc4b62d9f850e42192fab0f723ea6b10736b2a 100644 --- a/ghc/lib/prelude/Text_t.hi +++ b/ghc/lib/prelude/Text_t.hi @@ -34,7 +34,7 @@ readSigned :: Real a => ([Char] -> [(a, [Char])]) -> [Char] -> [(a, [Char])] reads :: Text a => [Char] -> [(a, [Char])] {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(SAAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Bool] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Bool) _N_ }, [ [Char] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Char) _N_ }, [ [Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Double) _N_ }, [ [Float] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Int) _N_ }, [ [Integer] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Char]) _N_ }, [ [[Int]] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList ([Int]) _N_ }, [ [Complex Double] ] 1 { _A_ 0 _U_ 2 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text readList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 2 _N_ _S_ _!_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ () ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 0 _U_ 2 _N_ _N_ _N_ _N_ } #-} show :: Text a => a -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _N_ _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 12 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 12 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 1 _U_ 2 _N_ _S_ "E" _N_ _N_ }, [ Char ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(P)" {_A_ 1 _U_ 2 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(PPP)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 1 _N_ _S_ "S" _N_ _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 1 _U_ 1 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 1 _U_ 1 _N_ _S_ "E" _F_ _IF_ARGS_ 0 1 C 5 \ (u0 :: ()) -> case u0 of { _ALG_ _TUP_0 -> _NOREP_S_ "()"; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LL)" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 1 _U_ 1 _N_ _S_ "U(LLL)" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} showChar :: Char -> [Char] -> [Char] {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 2 XX 3 \ (u0 :: Char) (u1 :: [Char]) -> _!_ (:) [Char] [u0, u1] _N_ #-} showFloat :: RealFloat a => a -> [Char] -> [Char] @@ -50,7 +50,7 @@ showSigned :: Real a => (a -> [Char] -> [Char]) -> Int -> a -> [Char] -> [Char] showSpace__ :: [Char] -> [Char] {-# GHC_PRAGMA _A_ 1 _U_ 2 _N_ _N_ _N_ _N_ #-} showString :: [Char] -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 2 _U_ 12 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ _ORIG_ PreludeList (++) { Char } _N_ #-} + {-# GHC_PRAGMA _A_ 2 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _TYAPP_ (++) { Char } _N_ #-} shows :: Text a => a -> [Char] -> [Char] - {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ _TYAPP_ _ORIG_ PreludeList (++) { Char } [ _NOREP_S_ "()", u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} + {-# GHC_PRAGMA _A_ 1 _U_ 122 _N_ _S_ "U(ASAA)" {_A_ 1 _U_ 122 _N_ _N_ _N_ _N_} _N_ _SPECIALISE_ [ Bool ] 1 { _A_ 2 _U_ 22 _N_ _N_ _N_ _N_ }, [ Char ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Double ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(P)" {_A_ 1 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Int ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(P)L" {_A_ 2 _U_ 22 _N_ _N_ _N_ _N_} _N_ _N_ }, [ Integer ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(PPP)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ [Bool] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [Bool]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { Bool } [ _WRKR_ _CONSTM_ Text showsPrec (Bool), u0 ] _N_ }, [ [Char] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Char) _N_ }, [ [Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Double) _N_ }, [ [Int] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Int) _N_ }, [ [Integer] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Integer) _N_ }, [ [[Char]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Char]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Char] } [ _CONSTM_ Text showList (Char), u0 ] _N_ }, [ [[Int]] ] 1 { _A_ 1 _U_ 12 _N_ _S_ "S" _F_ _IF_ARGS_ 0 1 X 3 \ (u0 :: [[Int]]) -> _APP_ _TYAPP_ _ORIG_ PreludeCore _showList { [Int] } [ _CONSTM_ Text showList (Int), u0 ] _N_ }, [ [Complex Double] ] 1 { _A_ 1 _U_ 22 _N_ _N_ _F_ _IF_ARGS_ 0 0 X 1 _CONSTM_ Text showList (Complex Double) _N_ }, [ (Ratio Integer) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Array Int Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ (Array (Int, Int) Double) ] 1 { _A_ 1 _U_ 22 _N_ _N_ _N_ _N_ }, [ _PackedString ] 1 { _A_ 2 _U_ 12 _N_ _N_ _N_ _N_ }, [ (Complex Double) ] 1 { _A_ 1 _U_ 12 _N_ _S_ "U(LL)" {_A_ 2 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ () ] 1 { _A_ 2 _U_ 12 _N_ _S_ "EL" _F_ _IF_ARGS_ 0 2 CX 4 \ (u0 :: ()) (u1 :: [Char]) -> case u0 of { _ALG_ _TUP_0 -> _APP_ unpackAppendPS# [ "()"#, u1 ]; _NO_DEFLT_ } _N_ }, [ (Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Integer, Integer) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LL)L" {_A_ 3 _U_ 222 _N_ _N_ _N_ _N_} _N_ _N_ }, [ (Int, Int, Int) ] 1 { _A_ 2 _U_ 12 _N_ _S_ "U(LLL)L" {_A_ 4 _U_ 2222 _N_ _N_ _N_ _N_} _N_ _N_ } #-} diff --git a/ghc/lib/prelude/TyIO.hi b/ghc/lib/prelude/TyIO.hi index c674bbe9d0c1bfca8c9a4bb6b7c881fa8f8bb842..42f2120a92928c0bf0a7c8c11764ed3695be0df3 100644 --- a/ghc/lib/prelude/TyIO.hi +++ b/ghc/lib/prelude/TyIO.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeIO where import PreludeBuiltin(Bin, Char(..), Int(..), List(..)) import PreludeCore(Bool(..)) diff --git a/ghc/lib/prelude/TyIO_mc.hi b/ghc/lib/prelude/TyIO_mc.hi index c674bbe9d0c1bfca8c9a4bb6b7c881fa8f8bb842..42f2120a92928c0bf0a7c8c11764ed3695be0df3 100644 --- a/ghc/lib/prelude/TyIO_mc.hi +++ b/ghc/lib/prelude/TyIO_mc.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeIO where import PreludeBuiltin(Bin, Char(..), Int(..), List(..)) import PreludeCore(Bool(..)) diff --git a/ghc/lib/prelude/TyIO_mp.hi b/ghc/lib/prelude/TyIO_mp.hi index c674bbe9d0c1bfca8c9a4bb6b7c881fa8f8bb842..42f2120a92928c0bf0a7c8c11764ed3695be0df3 100644 --- a/ghc/lib/prelude/TyIO_mp.hi +++ b/ghc/lib/prelude/TyIO_mp.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeIO where import PreludeBuiltin(Bin, Char(..), Int(..), List(..)) import PreludeCore(Bool(..)) diff --git a/ghc/lib/prelude/TyIO_p.hi b/ghc/lib/prelude/TyIO_p.hi index c674bbe9d0c1bfca8c9a4bb6b7c881fa8f8bb842..42f2120a92928c0bf0a7c8c11764ed3695be0df3 100644 --- a/ghc/lib/prelude/TyIO_p.hi +++ b/ghc/lib/prelude/TyIO_p.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeIO where import PreludeBuiltin(Bin, Char(..), Int(..), List(..)) import PreludeCore(Bool(..)) diff --git a/ghc/lib/prelude/TyIO_t.hi b/ghc/lib/prelude/TyIO_t.hi index c674bbe9d0c1bfca8c9a4bb6b7c881fa8f8bb842..42f2120a92928c0bf0a7c8c11764ed3695be0df3 100644 --- a/ghc/lib/prelude/TyIO_t.hi +++ b/ghc/lib/prelude/TyIO_t.hi @@ -1,4 +1,4 @@ -{-# GHC_PRAGMA INTERFACE VERSION 5 #-} +{-# GHC_PRAGMA INTERFACE VERSION 6 #-} interface PreludeIO where import PreludeBuiltin(Bin, Char(..), Int(..), List(..)) import PreludeCore(Bool(..)) diff --git a/ghc/runtime/c-as-asm/HpOverflow.lc b/ghc/runtime/c-as-asm/HpOverflow.lc index a9d559fc64fbe9cfcd5e32d08ee2f2acd118eaf7..b1cf98c1c47445331961755ec4320a542ac38131 100644 --- a/ghc/runtime/c-as-asm/HpOverflow.lc +++ b/ghc/runtime/c-as-asm/HpOverflow.lc @@ -670,7 +670,7 @@ BlackHoleUpdateStack(STG_NO_ARGS) PtrToUpdateFrame = GRAB_SuB(PtrToUpdateFrame); } } -#endif /* CONCURRENT */ +#endif /* !CONCURRENT */ \end{code} diff --git a/ghc/runtime/c-as-asm/StgDebug.lc b/ghc/runtime/c-as-asm/StgDebug.lc index 3e5b2bc2be55b9502130056c9808160c50f3979f..676fadb8988a7a8596bffa48804f56c0fe85700a 100644 --- a/ghc/runtime/c-as-asm/StgDebug.lc +++ b/ghc/runtime/c-as-asm/StgDebug.lc @@ -649,7 +649,7 @@ getClosureShape( P_ node, int *vhs, int *size, int *ptrs, char **type ) #ifdef PAR *vhs = FETCHME_VHS; *size = FETCHME_CLOSURE_SIZE(node); - *ptrs = FETCHME_CLOSURE_PTRS(node); + *ptrs = FETCHME_CLOSURE_NoPTRS(node); *type = "FETCHME"; #else printf("Panic: found FETCHME Infotable in sequential system.\n"); @@ -660,7 +660,7 @@ getClosureShape( P_ node, int *vhs, int *size, int *ptrs, char **type ) #ifdef PAR *vhs = FMBQ_VHS; *size = FMBQ_CLOSURE_SIZE(node); - *ptrs = FMBQ_CLOSURE_PTRS(node); + *ptrs = FMBQ_CLOSURE_NoPTRS(node); *type = "FMBQ"; #else printf("Panic: found FMBQ Infotable in sequential system.\n"); @@ -727,23 +727,27 @@ printAddress( P_ address ) PP_ SuA = STKO_SuA(SAVE_StkO); P_ SpB = STKO_SpB(SAVE_StkO); P_ SuB = STKO_SuB(SAVE_StkO); + PP_ botA = 0; /* junk */ + P_ botB = 0; +# define CAN_SEE_STK_BOTTOMS 0 # else PP_ SpA = SAVE_SpA; PP_ SuA = SAVE_SuA; P_ SpB = SAVE_SpB; P_ SuB = SAVE_SuB; + PP_ botA = stackInfo.botA; + P_ botB = stackInfo.botB; +# define CAN_SEE_STK_BOTTOMS 1 # endif P_ Hp = SAVE_Hp; - PP_ botA = stackInfo.botA; - P_ botB = stackInfo.botB; P_ HpBot = HP_BOT; char *name; /* ToDo: check if it's in text or data segment. */ - /* The @-1@s in stack comparisions are because we sometimes use the + /* The @-1@s in stack comparisons are because we sometimes use the address of just below the stack... */ #if 0 @@ -759,11 +763,17 @@ printAddress( P_ address ) } if (HpBot <= address && address < Hp) { printf("Hp[%d]", address - HpBot); - } else if (SUBTRACT_A_STK((PP_)address, botA) >= -1 && SUBTRACT_A_STK(SpA, (PP_)address) >= 0) { + } else if ( CAN_SEE_STK_BOTTOMS + && SUBTRACT_A_STK((PP_)address, botA) >= -1 + && SUBTRACT_A_STK(SpA, (PP_)address) >= 0) { printf("SpA[%d]", SUBTRACT_A_STK((PP_)address, botA)); - } else if (SUBTRACT_B_STK(address, botB) >= -1 && SUBTRACT_B_STK(SpB, address) >= 0) { + + } else if ( CAN_SEE_STK_BOTTOMS + && SUBTRACT_B_STK(address, botB) >= -1 + && SUBTRACT_B_STK(SpB, address) >= 0) { /* ToDo: check if it's an update frame */ printf("SpB[%d]", SUBTRACT_B_STK(address, botB)); + } else { printWord( (W_) address ); } @@ -1108,6 +1118,8 @@ ToDo: \begin{code} /* How many real stacks are there on SpA and SpB? */ +/* Say what?? (Will and Phil, 96/01) */ +#ifndef CONCURRENT static int numStacks( ) { @@ -1132,6 +1144,7 @@ numStacks( ) } return depth; } +#endif /* !CONCURRENT */ static void printLocalAStack( int depth, int indentation, int weight, PP_ SpA, int size ) @@ -1215,6 +1228,9 @@ static int maxDepth = 5; static int printCases( int depth, int weight, PP_ SpA, PP_ SuA, P_ SpB, P_ SuB ) { +#ifdef CONCURRENT + printf("no printCases for CONCURRENT\n"); +#else int indentation; if (depth < maxDepth && SUBTRACT_B_STK(SuB, stackInfo.botB) >= 0) { @@ -1248,6 +1264,8 @@ printCases( int depth, int weight, PP_ SpA, PP_ SuA, P_ SpB, P_ SuB ) } return indentation; + +#endif /* CONCURRENT */ } /* ToDo: pay more attention to format of vector tables in SMupdate.lh */ @@ -1290,6 +1308,9 @@ printVectorTable( int indentation, PP_ vtbl ) static void printContinuations( int depth, int indentation, int weight, PP_ SpA, PP_ SuA, P_ SpB, P_ SuB ) { +#ifdef CONCURRENT + printf("no printContinuations for CONCURRENT\n"); +#else if (depth < maxDepth && SUBTRACT_B_STK(SuB, stackInfo.botB) >= 0) { PP_ nextSpA, nextSuA; P_ nextSpB, nextSuB; @@ -1335,6 +1356,7 @@ printContinuations( int depth, int indentation, int weight, PP_ SpA, PP_ SuA, P_ } else { printf("...\n"); } +#endif /* CONCURRENT */ } void @@ -1395,9 +1417,10 @@ DEBUG_INFO_TABLE(node) "Tag: %d; Type: %d; Size: %lu; Ptrs: %lu\n\n", INFO_TAG(info_ptr), INFO_TYPE(info_ptr), INFO_SIZE(info_ptr),INFO_NoPTRS(info_ptr)); -#if defined(PAR) +#if defined(GRIP) + /* flushing is GRIP only */ fprintf(stderr,"Enter Flush Entry: 0x%lx;\tExit Flush Entry: 0x%lx\n",INFO_FLUSHENT(info_ptr),INFO_FLUSH(info_ptr)); -#endif /* PAR */ +#endif /* GRIP */ #if defined(PROFILING) fprintf(stderr,"Cost Centre: 0x%lx\n",INFO_CAT(info_ptr)); diff --git a/ghc/runtime/gum/HLComms.lc b/ghc/runtime/gum/HLComms.lc index 450fa0b97f1fa72238bb92ca9ac0c70326f1184f..e9e86bc56a760755902b207bbf2180e0cc05e1b2 100644 --- a/ghc/runtime/gum/HLComms.lc +++ b/ghc/runtime/gum/HLComms.lc @@ -884,11 +884,6 @@ PACKET packet; switch (opcode) { - case PP_IO_INIT: - IAmMainThread = rtsTrue; /* This processor is the IO task */ -/* fprintf(stderr,"I am Main Thread\n"); */ - break; - case PP_FINISH: EXIT(EXIT_SUCCESS); break; @@ -984,18 +979,13 @@ void STG_Exception(packet) PACKET packet; { -/* GLOBAL_TASK_ID sender = Sender_Task(packet); */ + GLOBAL_TASK_ID sender = Sender_Task(packet); OPCODE opcode = Opcode(packet); -/* fprintf(stderr,"STG_Exception: Received %s (%x), sender %x\n",GetOpName(opcode),opcode,sender); */ + fprintf(stderr,"STG_Exception: Received %s (%x), sender %x\n",GetOpName(opcode),opcode,sender); switch (opcode) { - case PP_IO_INIT: - IAmMainThread = rtsTrue; /* This processor is the IO task */ -/* fprintf(stderr,"I am Main Thread\n"); */ - break; - case PP_FINISH: EXIT(EXIT_SUCCESS); break; diff --git a/ghc/runtime/gum/LLComms.lc b/ghc/runtime/gum/LLComms.lc index d88f50d9fd3b12b00fdf7ef70c291b38c3a9abb2..abddf754d5acf3584c8d3a0b6043636156d1efc1 100644 --- a/ghc/runtime/gum/LLComms.lc +++ b/ghc/runtime/gum/LLComms.lc @@ -276,11 +276,12 @@ GLOBAL_TASK_ID who; rtsBool match; do { -/* fprintf(stderr,"WaitForPEOp: op = %x, who = %x\n",op,who); */ + fprintf(stderr,"WaitForPEOp: op = %x, who = %x\n",op,who); while((p = pvm_recv(ANY_TASK,ANY_OPCODE)) < 0) pvm_perror("WaitForPEOp: Waiting for PEOp"); pvm_bufinfo( p, &nbytes, &opcode, &sender_id ); + fprintf(stderr,"WaitForPEOp: received: opcode = %x, sender_id = %x\n",opcode,sender_id); match = (op == ANY_OPCODE || op == opcode) && (who == ANY_TASK || who == sender_id); @@ -346,22 +347,28 @@ unsigned nPEs; GLOBAL_TASK_ID *PEs = (GLOBAL_TASK_ID *) stgMallocBytes(sizeof(GLOBAL_TASK_ID) * nPEs, "PEStartUp (PEs)"); - mytid = _my_gtid; /* Initialise PVM and get task id into global - * variable */ + mytid = _my_gtid; /* Initialise PVM and get task id into global var.*/ -/* fprintf(stderr,"PEStartup, No. PEs = %d \n", nPEs); */ + fprintf(stderr,"PEStartup, Task id = [%x], No. PEs = %d \n", mytid, nPEs); checkComms(pvm_joingroup(PEGROUP), "PEStartup"); -/* fprintf(stderr,"PEStartup, Joined PEGROUP\n"); */ + fprintf(stderr,"PEStartup, Joined PEGROUP\n"); checkComms(pvm_joingroup(PECTLGROUP), "PEStartup"); -/* fprintf(stderr,"PEStartup, Joined PECTLGROUP\n"); */ - checkComms(pvm_barrier(PECTLGROUP, nPEs + 1), "PEStartup"); -/* fprintf(stderr,"PEStartup, Passed PECTLGROUP barrier\n"); */ - + fprintf(stderr,"PEStartup, Joined PECTLGROUP\n"); + checkComms(pvm_barrier(PECTLGROUP, nPEs+1), "PEStartup"); + fprintf(stderr,"PEStartup, Passed PECTLGROUP barrier\n"); + + addr = WaitForPEOp(PP_SYSMAN_TID, ANY_GLOBAL_TASK); + SysManTask = Sender_Task(addr); + if (IAmMainThread) { /* Main Thread Identifies itself to SysMan */ + pvm_initsend(PvmDataDefault); + pvm_send(SysManTask, PP_MAIN_TASK); + } addr = WaitForPEOp(PP_PETIDS, ANY_GLOBAL_TASK); GetArgs(buffer, nPEs); + for (i = 0; i < nPEs; ++i) { PEs[i] = (GLOBAL_TASK_ID) buffer[i]; - /* fprintf(stderr,"PEs[%d] = %x \n", i, PEs[i]); */ + fprintf(stderr,"PEs[%d] = %x \n", i, PEs[i]); } free(buffer); return PEs; diff --git a/ghc/runtime/gum/ParInit.lc b/ghc/runtime/gum/ParInit.lc index c7933a356c2870662758193ebc85ef2ac51f2efe..6f331e870bfeccea8052291e9d80814067fa9878 100644 --- a/ghc/runtime/gum/ParInit.lc +++ b/ghc/runtime/gum/ParInit.lc @@ -156,9 +156,6 @@ SynchroniseSystem(STG_NO_ARGS) for (i = 0; i < nPEs; ++i) registerTask(PEs[i]); - addr = WaitForPEOp(PP_INIT, ANY_GLOBAL_TASK); - SysManTask = Sender_Task(addr); - /* pvm_notify( PvmTaskExit, PP_FAIL, 1, &SysManTask); /* Setup an error handler */ /* Initialise the PE task array? */ diff --git a/ghc/runtime/gum/SysMan.lc b/ghc/runtime/gum/SysMan.lc index 545b8d70b7ef84e674e19ca628a084cdad7892b9..98405d0800c4f53e6d549056bd4667659fa390c1 100644 --- a/ghc/runtime/gum/SysMan.lc +++ b/ghc/runtime/gum/SysMan.lc @@ -8,9 +8,70 @@ %**************************************************************************** The Sysman task controls initiation, termination, global GC -synchronisation and statistics gathering. Based on K. Hammond's SysMan.lc -in Graph for PVM. - +synchronisation and statistics gathering of a parallel Haskell program +running under GUM. Based on K. Hammond's SysMan.lc in Graph for +PVM. SysMan is unusual in that it is not part of the executable +produced by ghc: it is a free-standing program that spawns PVM tasks +(logical PEs) to evaluate the program. + +OK children, buckle down for some serious wierdness, it works like this. + +\begin{itemize} +\item The argument vector (argv) for SysMan has one the following 2 shapes: +@ +------------------------------------------------------------------------------- +| SysMan path | debug flag | pvm-executable path | Num. PEs | Program Args ...| +------------------------------------------------------------------------------- + +------------------------------------------------------------------- +| SysMan path | pvm-executable path | Num. PEs | Program Args ... | +------------------------------------------------------------------- +@ +The "pvm-executable path" is an absolute path of where PVM stashes the +code for each PE. The arguments passed on to each PE-executable +spawned by PVM are: +@ +------------------------------- +| Num. PEs | Program Args ... | +------------------------------- +@ +The arguments passed to the Main-thread PE-executable are +@ +------------------------------------------------------------------- +| main flag | pvm-executable path | Num. PEs | Program Args ... | +------------------------------------------------------------------- +@ +\item SysMan's algorithm is as follows. +\begin{itemize} +\item use PVM to spawn (nPE-1) PVM tasks +\item fork SysMan to create the main-thread PE. This permits the main-thread to +read and write to stdin and stdout. +\item Barrier-synchronise waiting for all of the PE-tasks to start. +\item Broadcast the SysMan task-id, so that the main thread knows it. +\item Wait for the Main-thread PE to send it's task-id. +\item Broadcast an array of the PE task-ids to all of the PE-tasks. +\item Enter a loop awaiting incoming messages, e.g. failure, Garbage-collection, +termination. +\end{itemize} + +The forked Main-thread algorithm, in SysMan, is as follows. +\begin{itemize} +\item disconnects from PVM. +\item sets a flag in argv to indicate that it is the main thread. +\item `exec's a copy of the pvm-executable (i.e. the program being run) +\end{itemize} + +The pvm-executable run by each PE-task, is initialised as follows. +\begin{itemize} +\item Registers with PVM, obtaining a task-id. +\item Joins the barrier synchronisation awaiting the other PEs. +\item Receives and records the task-id of SysMan, for future use. +\item If the PE is the main thread it sends its task-id to SysMan. +\item Receives and records the array of task-ids of the other PEs. +\item Begins execution +\end{itemize} + +\end{itemize} \begin{code} #define NON_POSIX_SOURCE /* so says Solaris */ @@ -18,19 +79,22 @@ in Graph for PVM. #include "LLC.h" \end{code} +The following definitions included so that SysMan can be linked with +Low Level Communications module (LLComms). They are not used in +SysMan. + \begin{code} -static GLOBAL_TASK_ID gtids[MAX_PES], StatsTask = 0; -static long PEbuffer[MAX_PES]; -static int nPEs = 0; +GLOBAL_TASK_ID mytid, SysManTask; +rtsBool IAmMainThread; \end{code} + \begin{code} +static GLOBAL_TASK_ID gtids[MAX_PES], StatsTask = 0; +static long PEbuffer[MAX_PES]; +int nPEs = 0; static GLOBAL_TASK_ID sysman_id, sender_id, mainThread_id; - -GLOBAL_TASK_ID mytid; - static unsigned PEsTerminated = 0; - static rtsBool Finishing = rtsFalse; \end{code} @@ -59,6 +123,7 @@ main(int argc, char **argv) char **pargv; int i, cc; int spawn_flag = PvmTaskDefault; + PACKET addr; char *petask, *pvmExecutable; @@ -71,10 +136,16 @@ main(int argc, char **argv) argv[1] = argv[0]; argv++; argc--; } - mainThread_id = pvm_mytid();/* This must be the first PVM call */ - checkerr(mainThread_id); + sysman_id = pvm_mytid();/* This must be the first PVM call */ + checkerr(sysman_id); - nPEs = atoi(argv[1]); + /* + Get the full path and filename of the pvm executable (stashed in some + PVM directory. + */ + pvmExecutable = argv[1]; + + nPEs = atoi(argv[2]); if ((petask = getenv(PETASK)) == NULL) petask = PETASK; @@ -88,17 +159,15 @@ main(int argc, char **argv) fprintf(stderr, "No more than %d PEs allowed (%d requested)\n", MAX_PES, nPEs); EXIT(EXIT_FAILURE); } - /* - Get the full path and filename of the pvm executable (stashed in some - PVM directory. - */ - pvmExecutable = argv[2]; - /* Create the PE Tasks */ + /* + Now create the PE Tasks. We spawn (nPEs-1) pvm threads: the Main Thread + (which starts execution and performs IO) is created by forking SysMan + */ if (nPEs > 0) { - /* Spawn nPEs-1 pvm threads: the Main Thread (starts execution and performs - IO is created by forking SysMan */ nPEs--; + /* Initialise the PE task arguments from Sysman's arguments */ + pargv = argv + 2; #if 1 fprintf(stderr, "Spawning %d PEs(%s) ...\n", nPEs, petask); fprintf(stderr, " args: "); @@ -106,155 +175,140 @@ main(int argc, char **argv) fprintf(stderr, "%s, ", pargv[i]); fprintf(stderr, "\n"); #endif - /* Initialise the PE task arguments from Sysman's arguments */ - pargv = argv + 2; checkerr(pvm_spawn(petask, pargv, spawn_flag, "", nPEs, gtids)); - PEbuffer[0] = mainThread_id; + /* + * Stash the task-ids of the PEs away in a buffer, once we know + * the Main Thread's task-id, we'll broadcast them all. + */ for (i = 0; i < nPEs; i++) - PEbuffer[i++] = (long) gtids[i]; + PEbuffer[i+1] = (long) gtids[i]; #if 1 fprintf(stderr, "Spawned /* PWT */\n"); #endif - } - /* - SysMan joins PECTLGROUP, so that it can wait (at the - barrier sysnchronisation a few instructions later) for the - other PE-tasks to start. - - Other comments on PVM groupery: - - The manager group (MGRGROUP) is vestigial at the moment. It - may eventually include a statistics manager, garbage - collector manager. - - I suspect that you're [Kei Davis] right: Sysman shouldn't - be in PEGROUP, it's a hangover from GRIP. - - (Phil Trinder, 95/10) - */ - checkerr(pvm_joingroup(PECTLGROUP)); -#if 1 - fprintf(stderr, "Joined PECTLGROUP /* PWT */\n"); -#endif - - /* Wait for all the PEs and IMUs to arrive */ - checkerr(pvm_barrier(PECTLGROUP, nPEs + 1)); -#if 1 - fprintf(stderr, "PECTLGROUP barrier passed /* HWL */\n"); -#endif /* Create the MainThread PE by forking SysMan. This arcane coding is required to allow MainThread to read stdin and write to stdout. PWT 18/1/96 */ + nPEs++; /* Record that the number of PEs is increasing */ if (cc = fork()) { - checkerr(cc); - exec($some path$/petask) /* Parent task become Main Thread PE */ - } else { - /* Child continues as SysMan */ - pvmendtask(); /* Disconnect from PVM to avoid confusion */ - sysman_id = pvm_mytid(); /* Reconnect to PVM to get new task id */ - - /* Broadcast Global Task Ids of all PEs */ - - pvm_initsend(PvmDataDefault); - PutArgs(PEbuffer, nPEs); - pvm_bcast(PEGROUP, PP_PETIDS); - + checkerr(cc); /* Parent continues as SysMan */ #if 1 - fprintf(stderr, "Main Thread Task is [t%x]\n", mainThread_id); + fprintf(stderr, "SysMan Task is [t%x]\n", sysman_id); #endif - - pvm_initsend(PvmDataDefault); - pvm_send(mainThread_id, PP_IO_INIT); - - pvm_initsend(PvmDataDefault); - pvm_bcast(PEGROUP, PP_INIT); + /* + SysMan joins PECTLGROUP, so that it can wait (at the + barrier sysnchronisation a few instructions later) for the + other PE-tasks to start. + + The manager group (MGRGROUP) is vestigial at the moment. It + may eventually include a statistics manager, and a (global) + garbage collector manager. + */ + checkerr(pvm_joingroup(PECTLGROUP)); #if 1 - fprintf(stderr, "Broadcast PP_INIT to all PEs\n"); + fprintf(stderr, "Joined PECTLGROUP /* PWT */\n"); #endif - - /* HWL-DEBUG */ + /* Wait for all the PEs to arrive */ + checkerr(pvm_barrier(PECTLGROUP, nPEs + 1)); #if 1 - fprintf(stderr, "Sysman successfully initialized!\n"); + fprintf(stderr, "PECTLGROUP barrier passed /* HWL */\n"); #endif + /* Broadcast SysMan's ID, so Main Thread PE knows it */ + pvm_initsend(PvmDataDefault); + pvm_bcast(PEGROUP, PP_SYSMAN_TID); - /* Process incoming messages */ - while (1) { - if ((rbufid = pvm_recv(ANY_TASK, ANY_OPCODE)) < 0) - pvm_perror("Sysman: Receiving Message"); - - else { - pvm_bufinfo(rbufid, &nbytes, &opcode, &sender_id); - + /* Wait for Main Thread to identify itself*/ + addr = WaitForPEOp(PP_MAIN_TASK, ANY_GLOBAL_TASK); + pvm_bufinfo(addr, &nbytes, &opcode, &mainThread_id ); + PEbuffer[0] = mainThread_id; +#if 1 + fprintf(stderr,"SysMan received Main Task = %x\n",mainThread_id); +#endif + /* Now that we have them all, broadcast Global Task Ids of all PEs */ + pvm_initsend(PvmDataDefault); + PutArgs(PEbuffer, nPEs); + pvm_bcast(PEGROUP, PP_PETIDS); +#if 1 + fprintf(stderr, "Sysman successfully initialized!\n"); +#endif + /* Process incoming messages */ + while (1) { + if ((rbufid = pvm_recv(ANY_TASK, ANY_OPCODE)) < 0) + pvm_perror("Sysman: Receiving Message"); + else { + pvm_bufinfo(rbufid, &nbytes, &opcode, &sender_id); #if 0 fprintf(stderr, "HWL-DBG(SysMan; main loop): rbufid=%x, nbytes = %d, opcode = %x, sender_id = %x\n", - rbufid, nbytes, opcode, sender_id); + rbufid, nbytes, opcode, sender_id); #endif - switch (opcode) { - case PP_GC_INIT: - /* This Function not yet implemented for GUM */ - fprintf(stderr, "Global GC from %x Not yet implemented for GUM!\n", sender_id); - sync(PECTLGROUP, PP_FULL_SYSTEM); - broadcast(PEGROUP, PP_GC_INIT); - DoGlobalGC(); - broadcast(PEGROUP, PP_INIT); - break; - - case PP_STATS_ON: - case PP_STATS_OFF: + case PP_GC_INIT: /* This Function not yet implemented for GUM */ + fprintf(stderr, "Global GC from %x Not yet implemented for GUM!\n", sender_id); + sync(PECTLGROUP, PP_FULL_SYSTEM); + broadcast(PEGROUP, PP_GC_INIT); + DoGlobalGC(); +/* broadcast(PEGROUP, PP_INIT); */ break; - case PP_FINISH: - fprintf(stderr, "Finish from %x\n", sender_id); - if (!Finishing) { - long buf = (long) StatsTask; - Finishing = rtsTrue; - pvm_initsend(PvmDataDefault); - pvm_pklong(&buf, 1, 1); - pvm_bcast(PEGROUP, PP_FINISH); + case PP_STATS_ON: + case PP_STATS_OFF: + /* This Function not yet implemented for GUM */ + break; + + case PP_FINISH: + fprintf(stderr, "Finish from %x\n", sender_id); + if (!Finishing) { + long buf = (long) StatsTask; + Finishing = rtsTrue; + pvm_initsend(PvmDataDefault); + pvm_pklong(&buf, 1, 1); + pvm_bcast(PEGROUP, PP_FINISH); } else { - ++PEsTerminated; + ++PEsTerminated; } - if (PEsTerminated >= nPEs) { - broadcast(PEGROUP, PP_FINISH); - broadcast(MGRGROUP, PP_FINISH); - pvm_lvgroup(PEGROUP); - pvm_lvgroup(PECTLGROUP); - pvm_lvgroup(MGRGROUP); - pvm_exit(); - EXIT(EXIT_SUCCESS); + broadcast(PEGROUP, PP_FINISH); + broadcast(MGRGROUP, PP_FINISH); + pvm_lvgroup(PECTLGROUP); + pvm_lvgroup(MGRGROUP); + pvm_exit(); + EXIT(EXIT_SUCCESS); } break; case PP_FAIL: fprintf(stderr, "Fail from %x\n", sender_id); if (!Finishing) { - Finishing = rtsTrue; - broadcast(PEGROUP, PP_FAIL); + Finishing = rtsTrue; + broadcast(PEGROUP, PP_FAIL); } break; default: { -/* char *opname = GetOpName(opcode); - fprintf(stderr,"Sysman: Unrecognised opcode %s (%x)\n", - opname,opcode); */ - fprintf(stderr, "Sysman: Unrecognised opcode (%x)\n", - opcode); +/* char *opname = GetOpName(opcode); + fprintf(stderr,"Sysman: Unrecognised opcode %s (%x)\n", + opname,opcode); */ + fprintf(stderr, "Sysman: Unrecognised opcode (%x)\n", + opcode); } break; - } - } - } - } - return(0); -} + } /* switch */ + } /* else */ + } /* while 1 */ + } /* forked Sysman Process */ + else { + pvmendtask(); /* Disconnect from PVM to avoid confusion: */ + /* executable reconnects */ + *argv[0] = '-'; /* Flag that this is the Main Thread PE */ + execv(pvmExecutable,argv); /* Parent task becomes Main Thread PE */ + } + } /* argc > 1 */ +} /* main */ \end{code} @myexit@ for the system manager. diff --git a/ghc/runtime/main/main.lc b/ghc/runtime/main/main.lc index fd70cd623b3fde1c08ddf6a07de8deb1a15ae29f..3e97731fe22de657f3b5739b39e85872cc4fdee4 100644 --- a/ghc/runtime/main/main.lc +++ b/ghc/runtime/main/main.lc @@ -99,12 +99,8 @@ char *rts_argv[MAX_RTS_ARGS]; jmp_buf restart_main; /* For restarting after a signal */ #endif -#if defined(PVM) -unsigned nPEs = 0, nIMUs = 0; -#endif - #if defined(PAR) -int nPEs = 0; +int nPEs = 0; /* Number of PEs */ #endif int /* return type of "main" is defined by the C standard */ @@ -126,15 +122,18 @@ Manager's requirements. \begin{code} #ifdef PAR + if (*argv[0] == '-') { /* Look to see whether we're the Main Thread */ + IAmMainThread = rtsTrue; + argv++; argc--; + fprintf(stderr, "I am Main Thread\n"); + } /* * Grab the number of PEs out of the argument vector, and * eliminate it from further argument processing. */ nPEs = atoi(argv[1]); argv[1] = argv[0]; - argv++; - argc--; - + argv++; argc--; SynchroniseSystem(); #endif diff --git a/ghc/runtime/storage/SMmarking.lc b/ghc/runtime/storage/SMmarking.lc index ae92832b48c081362cbc1c565c2c33466a13ebc8..592cd3573f2cc230de9064b5dda53a11ffad53b0 100644 --- a/ghc/runtime/storage/SMmarking.lc +++ b/ghc/runtime/storage/SMmarking.lc @@ -99,7 +99,9 @@ markHeapRoots(sm, cafs1, cafs2, base, lim, bit_array) miniInterpret((StgFunPtr) _startMarkWorld); } #else - /* Note: no *external* stacks in parallel world */ +# ifndef CONCURRENT + /* Note: no *external* stacks in parallel/concurrent world */ + DEBUG_STRING("Marking A Stack:"); if (SUBTRACT_A_STK(MAIN_SpA, stackInfo.botA) >= 0) { MRoot = (P_) MAIN_SpA; @@ -116,6 +118,7 @@ markHeapRoots(sm, cafs1, cafs2, base, lim, bit_array) MStack = (P_) _PRMarking_MarkNextBStack_closure; miniInterpret((StgFunPtr)_startMarkWorld); } +# endif /* ! CONCURRENT */ #endif /* PAR */ DEBUG_STRING("Marking & Updating CAFs:"); diff --git a/ghc/runtime/storage/SMstacks.lc b/ghc/runtime/storage/SMstacks.lc index f00daa849683a9c3143f31f4e8025e671005ed09..4428b9c20bb52e42a6d094e8b0c2c2411d4a620d 100644 --- a/ghc/runtime/storage/SMstacks.lc +++ b/ghc/runtime/storage/SMstacks.lc @@ -7,7 +7,9 @@ Routine that allocates the A and B stack (sequential only). # define NULL_REG_MAP # include "SMinternal.h" +#ifndef CONCURRENT stackData stackInfo; +#endif P_ stks_space = 0; @@ -45,6 +47,7 @@ initStacks(smInfo *sm) # endif /* Initialise Stack Info and pointers */ +#ifndef CONCURRENT stackInfo.botA = STK_A_FRAME_BASE(stks_space, RTSflags.GcFlags.stksSize); stackInfo.botB = STK_B_FRAME_BASE(stks_space, RTSflags.GcFlags.stksSize); @@ -54,6 +57,7 @@ initStacks(smInfo *sm) if (RTSflags.GcFlags.trace) fprintf(stderr, "STACK init: botA, spa: 0x%lx, 0x%lx\n botB, spb: 0x%lx, 0x%lx\n", (W_) stackInfo.botA, (W_) MAIN_SpA, (W_) stackInfo.botB, (W_) MAIN_SpB); +#endif /* !CONCURRENT */ return rtsTrue; } diff --git a/ghc/utils/hstags/hstags.prl b/ghc/utils/hstags/hstags.prl index 073db474ea706e4a5f5099239799baea0017d68e..519ba134270d29173e9ca8c3fcf128a1ca8a3c11 100644 --- a/ghc/utils/hstags/hstags.prl +++ b/ghc/utils/hstags/hstags.prl @@ -1,6 +1,9 @@ -$tmp = (( $ENV{'TMPDIR'} ) # to make tmp file names - ? ($ENV{'TMPDIR'} . "/$$.eht") - : "$(TMPDIR)/$$.eht" ); +if ( $ENV{'TMPDIR'} ) { # where to make tmp file names + $tmp = $ENV{'TMPDIR'} . "/$$.eht"; +} else { + $tmp ="$(TMPDIR)/$$.eht"; + $ENV{'TMPDIR'} = '$(TMPDIR)'; # set the env var as well +} #------------------------------------------------------------------------ # If you are adjusting paths by hand for a binary GHC distribution, diff --git a/ghc/utils/mkdependHS/mkdependHS.prl b/ghc/utils/mkdependHS/mkdependHS.prl index bfc309f06b744f27208ab1ed5e089a4e4bef21fa..e4a11c8f755e37c91f9fba74f601946faffaf641 100644 --- a/ghc/utils/mkdependHS/mkdependHS.prl +++ b/ghc/utils/mkdependHS/mkdependHS.prl @@ -30,9 +30,12 @@ if ( $OrigCpp =~ /(\S+)\s+(.*)/ ) { $Cpp = $OrigCpp; } -$Tmp_prefix = (( $ENV{'TMPDIR'} ) # to make tmp file names - ? ($ENV{'TMPDIR'} . "/mkdependHS$$") - : "$(TMPDIR)/mkdependHS$$" ); +if ( $ENV{'TMPDIR'} ) { # where to make tmp file names + $Tmp_prefix = $ENV{'TMPDIR'} . "/mkdependHS$$"; +} else { + $Tmp_prefix ="$(TMPDIR)/mkdependHS$$"; + $ENV{'TMPDIR'} = '$(TMPDIR)'; # set the env var as well +} #------------------------------------------------------------------------ # If you are adjusting paths by hand for a binary GHC distribution, diff --git a/ghc/utils/stat2resid/stat2resid.prl b/ghc/utils/stat2resid/stat2resid.prl index 95e9e742a59a9338794d77918516124761f2ca65..048981a8f2947692c18d2df6038bd6171d9fd3fc 100644 --- a/ghc/utils/stat2resid/stat2resid.prl +++ b/ghc/utils/stat2resid/stat2resid.prl @@ -1,5 +1,5 @@ # -# (c) The GRASP Project, Glasgow University, 1992 +# (c) The GRASP/AQUA Project, Glasgow University, 1992-1996 # # *** MSUB does some substitutions here *** # *** grep for $( *** @@ -7,7 +7,13 @@ $debug = 0; $outsuffix = ".resid.ps"; # change as appropriate -$tmpfile = "$(TMPDIR)/$$.resid.data"; + +if ( $ENV{'TMPDIR'} ) { # where to make tmp file names + $tmpfile = $ENV{'TMPDIR'} . "/$$.resid.data"; +} else { + $tmpfile ="$(TMPDIR)/$$.resid.data"; + $ENV{'TMPDIR'} = '$(TMPDIR)'; # set the env var as well +} @INC = ( ( $(INSTALLING) ) ? '$(INSTLIBDIR_GHC)' : '$(TOP_PWD)/$(CURRENT_DIR)' ); diff --git a/glafp-utils/scripts/ltx.prl b/glafp-utils/scripts/ltx.prl index 53e191bdf0beb6e87dd28315945fe78e05cb3991..bf5c767d0858f6dbf1034293065435cdecb4e71f 100644 --- a/glafp-utils/scripts/ltx.prl +++ b/glafp-utils/scripts/ltx.prl @@ -27,11 +27,18 @@ if (-f $ARGV[0]) { die "$Pgm: input file $ARGV[0] doesn't exist\n"; } +if ( $ENV{'TMPDIR'} ) { # where to make tmp file names + $Tmp_prefix = $ENV{'TMPDIR'} ; +} else { + $Tmp_prefix ='$(TMPDIR)'; + $ENV{'TMPDIR'} = '$(TMPDIR)'; # set the env var as well +} + sub rm_temp_files { - system("rm -f $(TMPDIR)/ltx-*.$$"); + system("rm -f $Tmp_prefix/ltx-*.$$"); } sub rm_temp_files_and_exit { - system("rm -f $(TMPDIR)/ltx-*.$$"); + system("rm -f $Tmp_prefix/ltx-*.$$"); exit(1); } $SIG{'INT'} = 'rm_temp_files_and_exit'; @@ -165,8 +172,8 @@ sub something_more_needed { &slurp_aux_file('aux'); $BibTeX_run_needed = 1 if $Bibliography_requested && - -f "$(TMPDIR)/ltx-aux-cite.$$" && - -s "$(TMPDIR)/ltx-aux-cite.$$"; + -f "$Tmp_prefix/ltx-aux-cite.$$" && + -s "$Tmp_prefix/ltx-aux-cite.$$"; } else { # ltx had been run before (.aux-prev/.idx-prev files exist) @@ -175,7 +182,7 @@ sub something_more_needed { &slurp_aux_file('aux'); &slurp_aux_file('aux-prev'); - local($tmp_pre) = "$(TMPDIR)/ltx"; + local($tmp_pre) = "$Tmp_prefix/ltx"; if ((-s "$tmp_pre-.aux-cite.$$") # there are still \cite's in there && (system("cmp -s $tmp_pre-.aux-cite.$$ $tmp_pre-.aux-prev-cite.$$") >> 8)) { @@ -200,12 +207,12 @@ sub something_more_needed { sub slurp_aux_file { local($ext) = @_; - # copy all citations from slurpfile into $(TMPDIR)/ltx-$ext-cite.$$ + # copy all citations from slurpfile into $Tmp_prefix/ltx-$ext-cite.$$ open(SLURPF,"< $TeX_root.$ext") || &die_gracefully("$Pgm: Can't open $TeX_root.$ext for reading\n"); - open(CITEF,"> $(TMPDIR)/ltx-$ext-cite.$$") - || &die_gracefully("$Pgm: Can't open $(TMPDIR)/ltx-$ext-cite.$$ for writing\n"); + open(CITEF,"> $Tmp_prefix/ltx-$ext-cite.$$") + || &die_gracefully("$Pgm: Can't open $Tmp_prefix/ltx-$ext-cite.$$ for writing\n"); while (<SLURPF>) { print CITEF $_ if /\\citation/; diff --git a/glafp-utils/scripts/runstdtest.prl b/glafp-utils/scripts/runstdtest.prl index 4ba2f09e95fe5d9ed7d4728958180ec5f060977b..a6c964f03d962d651cc0de72882b36c0993d35b6 100644 --- a/glafp-utils/scripts/runstdtest.prl +++ b/glafp-utils/scripts/runstdtest.prl @@ -34,7 +34,12 @@ $Status = 0; @PgmArgs = (); $PgmExitStatus = 0; $PgmStdinFile = '/dev/null'; -$TmpPrefix = '$(TMPDIR)'; +if ( $ENV{'TMPDIR'} ) { # where to make tmp file names + $TmpPrefix = $ENV{'TMPDIR'}; +} else { + $TmpPrefix ="$(TMPDIR)"; + $ENV{'TMPDIR'} = '$(TMPDIR)'; # set the env var as well +} $ScriptFile = "$TmpPrefix/run_me$$"; $DefaultStdoutFile = "$TmpPrefix/no_stdout$$"; # can't use /dev/null (e.g. Alphas) $DefaultStderrFile = "$TmpPrefix/no_stderr$$";