Movatterモバイル変換


[0]ホーム

URL:


{-# LANGUAGE Trustworthy #-}{-# LANGUAGE NoImplicitPrelude, MagicHash, StandaloneDeriving, BangPatterns,             KindSignatures, DataKinds, ConstraintKinds,              MultiParamTypeClasses, FunctionalDependencies #-}{-# LANGUAGE UnboxedTuples #-}{-# LANGUAGE AllowAmbiguousTypes #-}-- ip :: IP x a => a  is strictly speaking ambiguous, but IP is magic{-# LANGUAGE UndecidableSuperClasses #-}-- Because of the type-variable superclasses for tuples{-# OPTIONS_GHC -Wno-unused-imports #-}-- -Wno-unused-imports needed for the GHC.Tuple import below. Sigh.{-# OPTIONS_GHC -Wno-unused-top-binds #-}-- -Wno-unused-top-binds is there (I hope) to stop Haddock complaining-- about the constraint tuples being defined but not used{-# LANGUAGE FlexibleInstances #-}{-# LANGUAGE UndecidableSuperClasses #-}{-# LANGUAGE ConstraintKinds #-}{-# OPTIONS_HADDOCK not-home #-}------------------------------------------------------------------------------- |-- Module      :  GHC.Classes-- Copyright   :  (c) The University of Glasgow, 1992-2002-- License     :  see libraries/base/LICENSE---- Maintainer  :  ghc-devs@haskell.org-- Stability   :  internal-- Portability :  non-portable (GHC extensions)---- Basic classes.-- Do not import this module directly.  It is an GHC internal only-- module.  Some of its contents are instead available from @Prelude@-- and @GHC.Int@.-------------------------------------------------------------------------------moduleGHC.Classes(-- * Implicit parametersIP(..),-- * Equality and ordering-- | Do not import these classes from this module. Import them-- from @Prelude@ instead.Eq(..),Ord(..),-- ** Monomorphic equality operators-- $matching_overloaded_methods_in_ruleseqInt,neInt,eqWord,neWord,eqChar,neChar,eqFloat,eqDouble,-- ** Monomorphic comparison operatorsgtInt,geInt,leInt,ltInt,compareInt,compareInt#,gtWord,geWord,leWord,ltWord,compareWord,compareWord#,-- * Functions over Bool-- | Do not import these functions from this module. Import them-- from @Prelude@ instead.(&&),(||),not,-- * Integer arithmeticdivInt#,divInt8#,divInt16#,divInt32#,modInt#,modInt8#,modInt16#,modInt32#,divModInt#,divModInt8#,divModInt16#,divModInt32#,-- * Constraint tuplesCUnit,CSolo,CTuple0,CTuple1,CTuple2,CTuple3,CTuple4,CTuple5,CTuple6,CTuple7,CTuple8,CTuple9,CTuple10,CTuple11,CTuple12,CTuple13,CTuple14,CTuple15,CTuple16,CTuple17,CTuple18,CTuple19,CTuple20,CTuple21,CTuple22,CTuple23,CTuple24,CTuple25,CTuple26,CTuple27,CTuple28,CTuple29,CTuple30,CTuple31,CTuple32,CTuple33,CTuple34,CTuple35,CTuple36,CTuple37,CTuple38,CTuple39,CTuple40,CTuple41,CTuple42,CTuple43,CTuple44,CTuple45,CTuple46,CTuple47,CTuple48,CTuple49,CTuple50,CTuple51,CTuple52,CTuple53,CTuple54,CTuple55,CTuple56,CTuple57,CTuple58,CTuple59,CTuple60,CTuple61,CTuple62,CTuple63,CTuple64,)where-- GHC.Magic is used in some derived instancesimportGHC.Magic()importGHC.PrimimportGHC.TupleimportGHC.CString(unpackCString#)importGHC.Typesinfix4==,/=,<,<=,>=,>infixr3&&infixr2||default()-- Double isn't available yet-- | The syntax @?x :: a@ is desugared into @IP "x" a@-- IP is declared very early, so that libraries can take-- advantage of the implicit-call-stack featureclassIP(x::Symbol)a|x->awhereip::a{- $matching_overloaded_methods_in_rulesMatching on class methods (e.g. @(==)@) in rewrite rules tends to be a bitfragile. For instance, consider this motivating example from the @bytestring@library,@break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)breakByte :: Word8 -> ByteString -> (ByteString, ByteString)\{\-\# RULES "break -> breakByte" forall a. break (== x) = breakByte x \#\-\}@Here we have two functions, with @breakByte@ providing an optimizedimplementation of @break@ where the predicate is merely testing for equalitywith a known @Word8@. As written, however, this rule will be quite fragile asthe @(==)@ class operation rule may rewrite the predicate before our @break@rule has a chance to fire.For this reason, most of the primitive types in @base@ have 'Eq' and 'Ord'instances defined in terms of helper functions with inlinings delayed to phase1. For instance, @Word8@\'s @Eq@ instance looks like,@instance Eq Word8 where    (==) = eqWord8    (/=) = neWord8eqWord8, neWord8 :: Word8 -> Word8 -> BooleqWord8 (W8# x) (W8# y) = ...neWord8 (W8# x) (W8# y) = ...\{\-\# INLINE [1] eqWord8 \#\-\}\{\-\# INLINE [1] neWord8 \#\-\}@This allows us to save our @break@ rule above by rewriting it to instead matchagainst @eqWord8@,@\{\-\# RULES "break -> breakByte" forall a. break (`eqWord8` x) = breakByte x \#\-\}@Currently this is only done for @('==')@, @('/=')@, @('<')@, @('<=')@, @('>')@,and @('>=')@ for the types in "GHC.Word" and "GHC.Int".-}-- | The 'Eq' class defines equality ('==') and inequality ('/=').-- All the basic datatypes exported by the "Prelude" are instances of 'Eq',-- and 'Eq' may be derived for any datatype whose constituents are also-- instances of 'Eq'.---- The Haskell Report defines no laws for 'Eq'. However, instances are-- encouraged to follow these properties:---- [__Reflexivity__]: @x == x@ = 'True'-- [__Symmetry__]: @x == y@ = @y == x@-- [__Transitivity__]: if @x == y && y == z@ = 'True', then @x == z@ = 'True'-- [__Extensionality__]: if @x == y@ = 'True' and @f@ is a function-- whose return type is an instance of 'Eq', then @f x == f y@ = 'True'-- [__Negation__]: @x /= y@ = @not (x == y)@classEqawhere(==),(/=)::a->a->Bool{-# INLINE(/=)#-}{-# INLINE(==)#-}ax/=ay=Bool -> Boolnot(axa -> a -> Boolforall a. Eq a => a -> a -> Bool==ay)ax==ay=Bool -> Boolnot(axa -> a -> Boolforall a. Eq a => a -> a -> Bool/=ay){-# MINIMAL(==)|(/=)#-}derivinginstanceEq()derivinginstanceEqa=>Eq(Soloa)derivinginstance(Eqa,Eqb)=>Eq(a,b)derivinginstance(Eqa,Eqb,Eqc)=>Eq(a,b,c)derivinginstance(Eqa,Eqb,Eqc,Eqd)=>Eq(a,b,c,d)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe)=>Eq(a,b,c,d,e)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf)=>Eq(a,b,c,d,e,f)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf,Eqg)=>Eq(a,b,c,d,e,f,g)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf,Eqg,Eqh)=>Eq(a,b,c,d,e,f,g,h)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf,Eqg,Eqh,Eqi)=>Eq(a,b,c,d,e,f,g,h,i)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf,Eqg,Eqh,Eqi,Eqj)=>Eq(a,b,c,d,e,f,g,h,i,j)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf,Eqg,Eqh,Eqi,Eqj,Eqk)=>Eq(a,b,c,d,e,f,g,h,i,j,k)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf,Eqg,Eqh,Eqi,Eqj,Eqk,Eql)=>Eq(a,b,c,d,e,f,g,h,i,j,k,l)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf,Eqg,Eqh,Eqi,Eqj,Eqk,Eql,Eqm)=>Eq(a,b,c,d,e,f,g,h,i,j,k,l,m)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf,Eqg,Eqh,Eqi,Eqj,Eqk,Eql,Eqm,Eqn)=>Eq(a,b,c,d,e,f,g,h,i,j,k,l,m,n)derivinginstance(Eqa,Eqb,Eqc,Eqd,Eqe,Eqf,Eqg,Eqh,Eqi,Eqj,Eqk,Eql,Eqm,Eqn,Eqo)=>Eq(a,b,c,d,e,f,g,h,i,j,k,l,m,n,o)instance(Eqa)=>Eq[a]where{-# SPECIALISEinstanceEq[[Char]]#-}{-# SPECIALISEinstanceEq[Char]#-}{-# SPECIALISEinstanceEq[Int]#-}[]== :: [a] -> [a] -> Bool==[]=BoolTrue(ax:[a]xs)==(ay:[a]ys)=axa -> a -> Boolforall a. Eq a => a -> a -> Bool==ayBool -> Bool -> Bool&&[a]xs[a] -> [a] -> Boolforall a. Eq a => a -> a -> Bool==[a]ys[a]_xs==[a]_ys=BoolFalsederivinginstanceEqModuleinstanceEqTrNamewhereTrNameSAddr#a== :: TrName -> TrName -> Bool==TrNameSAddr#b=Int# -> BoolisTrue#(Addr#aAddr# -> Addr# -> Int#`eqAddr#`Addr#b)TrNamea==TrNameb=TrName -> [Char]toStringTrNamea[Char] -> [Char] -> Boolforall a. Eq a => a -> a -> Bool==TrName -> [Char]toStringTrNamebwheretoString :: TrName -> [Char]toString(TrNameSAddr#s)=Addr# -> [Char]unpackCString#Addr#stoString(TrNameD[Char]s)=[Char]sderivinginstanceEqBoolderivinginstanceEqOrderinginstanceEqWordwhere== :: Word -> Word -> Bool(==)=Word -> Word -> BooleqWord/= :: Word -> Word -> Bool(/=)=Word -> Word -> BoolneWord-- See GHC.Classes#matching_overloaded_methods_in_rules{-# INLINE[1]eqWord#-}{-# INLINE[1]neWord#-}eqWord,neWord::Word->Word->Bool(W#Word#x)eqWord :: Word -> Word -> Bool`eqWord`(W#Word#y)=Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`eqWord#`Word#y)(W#Word#x)neWord :: Word -> Word -> Bool`neWord`(W#Word#y)=Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`neWord#`Word#y)-- See GHC.Classes#matching_overloaded_methods_in_rulesinstanceEqCharwhere== :: Char -> Char -> Bool(==)=Char -> Char -> BooleqChar/= :: Char -> Char -> Bool(/=)=Char -> Char -> BoolneChar-- See GHC.Classes#matching_overloaded_methods_in_rules{-# INLINE[1]eqChar#-}{-# INLINE[1]neChar#-}eqChar,neChar::Char->Char->Bool(C#Char#x)eqChar :: Char -> Char -> Bool`eqChar`(C#Char#y)=Int# -> BoolisTrue#(Char#xChar# -> Char# -> Int#`eqChar#`Char#y)(C#Char#x)neChar :: Char -> Char -> Bool`neChar`(C#Char#y)=Int# -> BoolisTrue#(Char#xChar# -> Char# -> Int#`neChar#`Char#y)-- | Note that due to the presence of @NaN@, `Float`'s 'Eq' instance does not-- satisfy reflexivity.---- >>> 0/0 == (0/0 :: Float)-- False---- Also note that `Float`'s 'Eq' instance does not satisfy extensionality:---- >>> 0 == (-0 :: Float)-- True-- >>> recip 0 == recip (-0 :: Float)-- FalseinstanceEqFloatwhere== :: Float -> Float -> Bool(==)=Float -> Float -> BooleqFloat-- See GHC.Classes#matching_overloaded_methods_in_rules{-# INLINE[1]eqFloat#-}eqFloat::Float->Float->Bool(F#Float#x)eqFloat :: Float -> Float -> Bool`eqFloat`(F#Float#y)=Int# -> BoolisTrue#(Float#xFloat# -> Float# -> Int#`eqFloat#`Float#y)-- | Note that due to the presence of @NaN@, `Double`'s 'Eq' instance does not-- satisfy reflexivity.---- >>> 0/0 == (0/0 :: Double)-- False---- Also note that `Double`'s 'Eq' instance does not satisfy substitutivity:---- >>> 0 == (-0 :: Double)-- True-- >>> recip 0 == recip (-0 :: Double)-- FalseinstanceEqDoublewhere== :: Double -> Double -> Bool(==)=Double -> Double -> BooleqDouble-- See GHC.Classes#matching_overloaded_methods_in_rules{-# INLINE[1]eqDouble#-}eqDouble::Double->Double->Bool(D#Double#x)eqDouble :: Double -> Double -> Bool`eqDouble`(D#Double#y)=Int# -> BoolisTrue#(Double#xDouble# -> Double# -> Int#==##Double#y)instanceEqIntwhere== :: Int -> Int -> Bool(==)=Int -> Int -> BooleqInt/= :: Int -> Int -> Bool(/=)=Int -> Int -> BoolneInt-- See GHC.Classes#matching_overloaded_methods_in_rules{-# INLINE[1]eqInt#-}{-# INLINE[1]neInt#-}eqInt,neInt::Int->Int->Bool(I#Int#x)eqInt :: Int -> Int -> Bool`eqInt`(I#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#==#Int#y)(I#Int#x)neInt :: Int -> Int -> Bool`neInt`(I#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#/=#Int#y)instanceEqTyConwhere== :: TyCon -> TyCon -> Bool(==)(TyConWord64#hi1Word64#lo1Module_TrName_Int#_KindRep_)(TyConWord64#hi2Word64#lo2Module_TrName_Int#_KindRep_)=Int# -> BoolisTrue#(Word64#hi1Word64# -> Word64# -> Int#`eqWord64#`Word64#hi2)Bool -> Bool -> Bool&&Int# -> BoolisTrue#(Word64#lo1Word64# -> Word64# -> Int#`eqWord64#`Word64#lo2)instanceOrdTyConwherecompare :: TyCon -> TyCon -> Orderingcompare(TyConWord64#hi1Word64#lo1Module_TrName_Int#_KindRep_)(TyConWord64#hi2Word64#lo2Module_TrName_Int#_KindRep_)|Int# -> BoolisTrue#(Word64#hi1Word64# -> Word64# -> Int#`gtWord64#`Word64#hi2)=OrderingGT|Int# -> BoolisTrue#(Word64#hi1Word64# -> Word64# -> Int#`ltWord64#`Word64#hi2)=OrderingLT|Int# -> BoolisTrue#(Word64#lo1Word64# -> Word64# -> Int#`gtWord64#`Word64#lo2)=OrderingGT|Int# -> BoolisTrue#(Word64#lo1Word64# -> Word64# -> Int#`ltWord64#`Word64#lo2)=OrderingLT|BoolTrue=OrderingEQ-- | The 'Ord' class is used for totally ordered datatypes.---- Instances of 'Ord' can be derived for any user-defined datatype whose-- constituent types are in 'Ord'. The declared order of the constructors in-- the data declaration determines the ordering in derived 'Ord' instances. The-- 'Ordering' datatype allows a single comparison to determine the precise-- ordering of two objects.---- 'Ord', as defined by the Haskell report, implements a total order and has the-- following properties:---- [__Comparability__]: @x <= y || y <= x@ = 'True'-- [__Transitivity__]: if @x <= y && y <= z@ = 'True', then @x <= z@ = 'True'-- [__Reflexivity__]: @x <= x@ = 'True'-- [__Antisymmetry__]: if @x <= y && y <= x@ = 'True', then @x == y@ = 'True'---- The following operator interactions are expected to hold:---- 1. @x >= y@ = @y <= x@-- 2. @x < y@ = @x <= y && x /= y@-- 3. @x > y@ = @y < x@-- 4. @x < y@ = @compare x y == LT@-- 5. @x > y@ = @compare x y == GT@-- 6. @x == y@ = @compare x y == EQ@-- 7. @min x y == if x <= y then x else y@ = 'True'-- 8. @max x y == if x >= y then x else y@ = 'True'---- Note that (7.) and (8.) do /not/ require 'min' and 'max' to return either of-- their arguments. The result is merely required to /equal/ one of the-- arguments in terms of '(==)'.---- Minimal complete definition: either 'compare' or '<='.-- Using 'compare' can be more efficient for complex types.--class(Eqa)=>Ordawherecompare::a->a->Ordering(<),(<=),(>),(>=)::a->a->Boolmax,min::a->a->acompareaxay=ifaxa -> a -> Boolforall a. Eq a => a -> a -> Bool==aythenOrderingEQ-- NB: must be '<=' not '<' to validate the-- above claim about the minimal things that-- can be defined for an instance of Ord:elseifaxa -> a -> Boolforall a. Ord a => a -> a -> Bool<=aythenOrderingLTelseOrderingGTax<=ay=casea -> a -> Orderingforall a. Ord a => a -> a -> Orderingcompareaxayof{OrderingGT->BoolFalse;Ordering_->BoolTrue}ax>=ay=aya -> a -> Boolforall a. Ord a => a -> a -> Bool<=axax>ay=Bool -> Boolnot(axa -> a -> Boolforall a. Ord a => a -> a -> Bool<=ay)ax<ay=Bool -> Boolnot(aya -> a -> Boolforall a. Ord a => a -> a -> Bool<=ax)-- These two default methods use '<=' rather than 'compare'-- because the latter is often more expensivemaxaxay=ifaxa -> a -> Boolforall a. Ord a => a -> a -> Bool<=aythenayelseaxminaxay=ifaxa -> a -> Boolforall a. Ord a => a -> a -> Bool<=aythenaxelseay{-# MINIMALcompare|(<=)#-}derivinginstanceOrd()derivinginstanceOrda=>Ord(Soloa)derivinginstance(Orda,Ordb)=>Ord(a,b)derivinginstance(Orda,Ordb,Ordc)=>Ord(a,b,c)derivinginstance(Orda,Ordb,Ordc,Ordd)=>Ord(a,b,c,d)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde)=>Ord(a,b,c,d,e)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf)=>Ord(a,b,c,d,e,f)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf,Ordg)=>Ord(a,b,c,d,e,f,g)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf,Ordg,Ordh)=>Ord(a,b,c,d,e,f,g,h)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf,Ordg,Ordh,Ordi)=>Ord(a,b,c,d,e,f,g,h,i)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf,Ordg,Ordh,Ordi,Ordj)=>Ord(a,b,c,d,e,f,g,h,i,j)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf,Ordg,Ordh,Ordi,Ordj,Ordk)=>Ord(a,b,c,d,e,f,g,h,i,j,k)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf,Ordg,Ordh,Ordi,Ordj,Ordk,Ordl)=>Ord(a,b,c,d,e,f,g,h,i,j,k,l)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf,Ordg,Ordh,Ordi,Ordj,Ordk,Ordl,Ordm)=>Ord(a,b,c,d,e,f,g,h,i,j,k,l,m)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf,Ordg,Ordh,Ordi,Ordj,Ordk,Ordl,Ordm,Ordn)=>Ord(a,b,c,d,e,f,g,h,i,j,k,l,m,n)derivinginstance(Orda,Ordb,Ordc,Ordd,Orde,Ordf,Ordg,Ordh,Ordi,Ordj,Ordk,Ordl,Ordm,Ordn,Ordo)=>Ord(a,b,c,d,e,f,g,h,i,j,k,l,m,n,o)instance(Orda)=>Ord[a]where{-# SPECIALISEinstanceOrd[[Char]]#-}{-# SPECIALISEinstanceOrd[Char]#-}{-# SPECIALISEinstanceOrd[Int]#-}compare :: [a] -> [a] -> Orderingcompare[][]=OrderingEQcompare[](a_:[a]_)=OrderingLTcompare(a_:[a]_)[]=OrderingGTcompare(ax:[a]xs)(ay:[a]ys)=casea -> a -> Orderingforall a. Ord a => a -> a -> OrderingcompareaxayofOrderingEQ->[a] -> [a] -> Orderingforall a. Ord a => a -> a -> Orderingcompare[a]xs[a]ysOrderingother->OrderingotherderivinginstanceOrdBoolderivinginstanceOrdOrdering-- We don't use deriving for Ord Char, because for Ord the derived-- instance defines only compare, which takes two primops.  Then-- '>' uses compare, and therefore takes two primops instead of one.instanceOrdCharwhere(C#Char#c1)> :: Char -> Char -> Bool>(C#Char#c2)=Int# -> BoolisTrue#(Char#c1Char# -> Char# -> Int#`gtChar#`Char#c2)(C#Char#c1)>= :: Char -> Char -> Bool>=(C#Char#c2)=Int# -> BoolisTrue#(Char#c1Char# -> Char# -> Int#`geChar#`Char#c2)(C#Char#c1)<= :: Char -> Char -> Bool<=(C#Char#c2)=Int# -> BoolisTrue#(Char#c1Char# -> Char# -> Int#`leChar#`Char#c2)(C#Char#c1)< :: Char -> Char -> Bool<(C#Char#c2)=Int# -> BoolisTrue#(Char#c1Char# -> Char# -> Int#`ltChar#`Char#c2)-- | See @instance@ 'Ord' 'Double' for discussion of deviations from IEEE 754 standard.instanceOrdFloatwhere(F#Float#x)compare :: Float -> Float -> Ordering`compare`(F#Float#y)=ifInt# -> BoolisTrue#(Float#xFloat# -> Float# -> Int#`ltFloat#`Float#y)thenOrderingLTelseifInt# -> BoolisTrue#(Float#xFloat# -> Float# -> Int#`eqFloat#`Float#y)thenOrderingEQelseOrderingGT(F#Float#x)< :: Float -> Float -> Bool<(F#Float#y)=Int# -> BoolisTrue#(Float#xFloat# -> Float# -> Int#`ltFloat#`Float#y)(F#Float#x)<= :: Float -> Float -> Bool<=(F#Float#y)=Int# -> BoolisTrue#(Float#xFloat# -> Float# -> Int#`leFloat#`Float#y)(F#Float#x)>= :: Float -> Float -> Bool>=(F#Float#y)=Int# -> BoolisTrue#(Float#xFloat# -> Float# -> Int#`geFloat#`Float#y)(F#Float#x)> :: Float -> Float -> Bool>(F#Float#y)=Int# -> BoolisTrue#(Float#xFloat# -> Float# -> Int#`gtFloat#`Float#y)-- | IEEE 754 'Double'-precision type includes not only numbers, but also-- positive and negative infinities and a special element called @NaN@-- (which can be quiet or signal).---- IEEE 754-2008, section 5.11 requires that if at least one of arguments of-- '<=', '<', '>', '>=' is @NaN@ then the result of the comparison is 'False',-- and @instance@ 'Ord' 'Double' complies with this requirement. This violates-- the reflexivity: both @NaN@ '<=' @NaN@ and @NaN@ '>=' @NaN@ are 'False'.---- IEEE 754-2008, section 5.10 defines @totalOrder@ predicate. Unfortunately,-- 'compare' on 'Double's violates the IEEE standard and does not define a total order.-- More specifically, both 'compare' @NaN@ @x@ and 'compare' @x@ @NaN@ always return 'GT'.---- Thus, users must be extremely cautious when using @instance@ 'Ord' 'Double'.-- For instance, one should avoid ordered containers with keys represented by 'Double',-- because data loss and corruption may happen. An IEEE-compliant 'compare' is available-- in @fp-ieee@ package as @TotallyOrdered@ newtype.---- Moving further, the behaviour of 'min' and 'max' with regards to @NaN@ is-- also non-compliant. IEEE 754-2008, section 5.3.1 defines that quiet @NaN@-- should be treated as a missing data by @minNum@ and @maxNum@ functions,-- for example, @minNum(NaN, 1) = minNum(1, NaN) = 1@. Some languages such as Java-- deviate from the standard implementing @minNum(NaN, 1) = minNum(1, NaN) = NaN@.-- However, 'min' / 'max' in @base@ are even worse: 'min' @NaN@ 1 is 1, but 'min' 1 @NaN@-- is @NaN@.---- IEEE 754-2008 compliant 'min' / 'max' can be found in @ieee754@ package under-- @minNum@ / @maxNum@ names. Implementations compliant with-- @minimumNumber@ / @maximumNumber@ from a newer-- [IEEE 754-2019](https://grouper.ieee.org/groups/msc/ANSI_IEEE-Std-754-2019/background/),-- section 9.6 are available from @fp-ieee@ package.--instanceOrdDoublewhere(D#Double#x)compare :: Double -> Double -> Ordering`compare`(D#Double#y)=ifInt# -> BoolisTrue#(Double#xDouble# -> Double# -> Int#<##Double#y)thenOrderingLTelseifInt# -> BoolisTrue#(Double#xDouble# -> Double# -> Int#==##Double#y)thenOrderingEQelseOrderingGT(D#Double#x)< :: Double -> Double -> Bool<(D#Double#y)=Int# -> BoolisTrue#(Double#xDouble# -> Double# -> Int#<##Double#y)(D#Double#x)<= :: Double -> Double -> Bool<=(D#Double#y)=Int# -> BoolisTrue#(Double#xDouble# -> Double# -> Int#<=##Double#y)(D#Double#x)>= :: Double -> Double -> Bool>=(D#Double#y)=Int# -> BoolisTrue#(Double#xDouble# -> Double# -> Int#>=##Double#y)(D#Double#x)> :: Double -> Double -> Bool>(D#Double#y)=Int# -> BoolisTrue#(Double#xDouble# -> Double# -> Int#>##Double#y)instanceOrdIntwherecompare :: Int -> Int -> Orderingcompare=Int -> Int -> OrderingcompareInt< :: Int -> Int -> Bool(<)=Int -> Int -> BoolltInt<= :: Int -> Int -> Bool(<=)=Int -> Int -> BoolleInt>= :: Int -> Int -> Bool(>=)=Int -> Int -> BoolgeInt> :: Int -> Int -> Bool(>)=Int -> Int -> BoolgtInt-- See GHC.Classes#matching_overloaded_methods_in_rules{-# INLINE[1]gtInt#-}{-# INLINE[1]geInt#-}{-# INLINE[1]ltInt#-}{-# INLINE[1]leInt#-}gtInt,geInt,ltInt,leInt::Int->Int->Bool(I#Int#x)gtInt :: Int -> Int -> Bool`gtInt`(I#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#y)(I#Int#x)geInt :: Int -> Int -> Bool`geInt`(I#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>=#Int#y)(I#Int#x)ltInt :: Int -> Int -> Bool`ltInt`(I#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<#Int#y)(I#Int#x)leInt :: Int -> Int -> Bool`leInt`(I#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<=#Int#y)compareInt::Int->Int->Ordering(I#Int#x#)compareInt :: Int -> Int -> Ordering`compareInt`(I#Int#y#)=Int# -> Int# -> OrderingcompareInt#Int#x#Int#y#compareInt#::Int#->Int#->OrderingcompareInt# :: Int# -> Int# -> OrderingcompareInt#Int#x#Int#y#|Int# -> BoolisTrue#(Int#x#Int# -> Int# -> Int#<#Int#y#)=OrderingLT|Int# -> BoolisTrue#(Int#x#Int# -> Int# -> Int#==#Int#y#)=OrderingEQ|BoolTrue=OrderingGTinstanceOrdWordwherecompare :: Word -> Word -> Orderingcompare=Word -> Word -> OrderingcompareWord< :: Word -> Word -> Bool(<)=Word -> Word -> BoolltWord<= :: Word -> Word -> Bool(<=)=Word -> Word -> BoolleWord>= :: Word -> Word -> Bool(>=)=Word -> Word -> BoolgeWord> :: Word -> Word -> Bool(>)=Word -> Word -> BoolgtWord-- See GHC.Classes#matching_overloaded_methods_in_rules{-# INLINE[1]gtWord#-}{-# INLINE[1]geWord#-}{-# INLINE[1]ltWord#-}{-# INLINE[1]leWord#-}gtWord,geWord,ltWord,leWord::Word->Word->Bool(W#Word#x)gtWord :: Word -> Word -> Bool`gtWord`(W#Word#y)=Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`gtWord#`Word#y)(W#Word#x)geWord :: Word -> Word -> Bool`geWord`(W#Word#y)=Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`geWord#`Word#y)(W#Word#x)ltWord :: Word -> Word -> Bool`ltWord`(W#Word#y)=Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`ltWord#`Word#y)(W#Word#x)leWord :: Word -> Word -> Bool`leWord`(W#Word#y)=Int# -> BoolisTrue#(Word#xWord# -> Word# -> Int#`leWord#`Word#y)compareWord::Word->Word->Ordering(W#Word#x#)compareWord :: Word -> Word -> Ordering`compareWord`(W#Word#y#)=Word# -> Word# -> OrderingcompareWord#Word#x#Word#y#compareWord#::Word#->Word#->OrderingcompareWord# :: Word# -> Word# -> OrderingcompareWord#Word#x#Word#y#|Int# -> BoolisTrue#(Word#x#Word# -> Word# -> Int#`ltWord#`Word#y#)=OrderingLT|Int# -> BoolisTrue#(Word#x#Word# -> Word# -> Int#`eqWord#`Word#y#)=OrderingEQ|BoolTrue=OrderingGT-- OK, so they're technically not part of a class...:-- Boolean functions-- | Boolean \"and\", lazy in the second argument(&&)::Bool->Bool->BoolBoolTrue&& :: Bool -> Bool -> Bool&&Boolx=BoolxBoolFalse&&Bool_=BoolFalse-- | Boolean \"or\", lazy in the second argument(||)::Bool->Bool->BoolBoolTrue|| :: Bool -> Bool -> Bool||Bool_=BoolTrueBoolFalse||Boolx=Boolx-- | Boolean \"not\"not::Bool->Boolnot :: Bool -> BoolnotBoolTrue=BoolFalsenotBoolFalse=BoolTrue-------------------------------------------------------------------------- These don't really belong here, but we don't have a better place to-- put them-- These functions have built-in rules.{-# INLINE[0]divInt##-}divInt#::Int#->Int#->Int#Int#x#divInt# :: Int# -> Int# -> Int#`divInt#`Int#y#=((Int#x#Int# -> Int# -> Int#+#Int#bias#)Int# -> Int# -> Int#`quotInt#`Int#y#)Int# -> Int# -> Int#-#Int#hard#where-- See Note [divInt# implementation]!yn# :: Int#yn#=Int#y#Int# -> Int# -> Int#<#Int#0#!c0# :: Int#c0#=(Int#x#Int# -> Int# -> Int#<#Int#0#)Int# -> Int# -> Int#`andI#`(Int# -> Int#notI#Int#yn#)!c1# :: Int#c1#=(Int#x#Int# -> Int# -> Int#>#Int#0#)Int# -> Int# -> Int#`andI#`Int#yn#!bias# :: Int#bias#=Int#c0#Int# -> Int# -> Int#-#Int#c1#!hard# :: Int#hard#=Int#c0#Int# -> Int# -> Int#`orI#`Int#c1#{-# INLINE[0]divInt8##-}divInt8#::Int8#->Int8#->Int8#Int8#x#divInt8# :: Int8# -> Int8# -> Int8#`divInt8#`Int8#y#=((Int8#x#Int8# -> Int8# -> Int8#`plusInt8#`Int8#bias#)Int8# -> Int8# -> Int8#`quotInt8#`Int8#y#)Int8# -> Int8# -> Int8#`subInt8#`Int8#hard#wherezero# :: Int8#zero#=Int# -> Int8#intToInt8#Int#0#Int8#xandInt8# :: Int8# -> Int8# -> Int8#`andInt8#`Int8#y=Word8# -> Int8#word8ToInt8#(Int8# -> Word8#int8ToWord8#Int8#xWord8# -> Word8# -> Word8#`andWord8#`Int8# -> Word8#int8ToWord8#Int8#y)Int8#xorInt8# :: Int8# -> Int8# -> Int8#`orInt8#`Int8#y=Word8# -> Int8#word8ToInt8#(Int8# -> Word8#int8ToWord8#Int8#xWord8# -> Word8# -> Word8#`orWord8#`Int8# -> Word8#int8ToWord8#Int8#y)notInt8# :: Int8# -> Int8#notInt8#Int8#x=Word8# -> Int8#word8ToInt8#(Word8# -> Word8#notWord8#(Int8# -> Word8#int8ToWord8#Int8#x))-- See Note [divInt# implementation]!yn# :: Int8#yn#=Int# -> Int8#intToInt8#(Int8#y#Int8# -> Int8# -> Int#`ltInt8#`Int8#zero#)!c0# :: Int8#c0#=Int# -> Int8#intToInt8#(Int8#x#Int8# -> Int8# -> Int#`ltInt8#`Int8#zero#)Int8# -> Int8# -> Int8#`andInt8#`(Int8# -> Int8#notInt8#Int8#yn#)!c1# :: Int8#c1#=Int# -> Int8#intToInt8#(Int8#x#Int8# -> Int8# -> Int#`gtInt8#`Int8#zero#)Int8# -> Int8# -> Int8#`andInt8#`Int8#yn#!bias# :: Int8#bias#=Int8#c0#Int8# -> Int8# -> Int8#`subInt8#`Int8#c1#!hard# :: Int8#hard#=Int8#c0#Int8# -> Int8# -> Int8#`orInt8#`Int8#c1#{-# INLINE[0]divInt16##-}divInt16#::Int16#->Int16#->Int16#Int16#x#divInt16# :: Int16# -> Int16# -> Int16#`divInt16#`Int16#y#=((Int16#x#Int16# -> Int16# -> Int16#`plusInt16#`Int16#bias#)Int16# -> Int16# -> Int16#`quotInt16#`Int16#y#)Int16# -> Int16# -> Int16#`subInt16#`Int16#hard#wherezero# :: Int16#zero#=Int# -> Int16#intToInt16#Int#0#Int16#xandInt16# :: Int16# -> Int16# -> Int16#`andInt16#`Int16#y=Word16# -> Int16#word16ToInt16#(Int16# -> Word16#int16ToWord16#Int16#xWord16# -> Word16# -> Word16#`andWord16#`Int16# -> Word16#int16ToWord16#Int16#y)Int16#xorInt16# :: Int16# -> Int16# -> Int16#`orInt16#`Int16#y=Word16# -> Int16#word16ToInt16#(Int16# -> Word16#int16ToWord16#Int16#xWord16# -> Word16# -> Word16#`orWord16#`Int16# -> Word16#int16ToWord16#Int16#y)notInt16# :: Int16# -> Int16#notInt16#Int16#x=Word16# -> Int16#word16ToInt16#(Word16# -> Word16#notWord16#(Int16# -> Word16#int16ToWord16#Int16#x))-- See Note [divInt# implementation]!yn# :: Int16#yn#=Int# -> Int16#intToInt16#(Int16#y#Int16# -> Int16# -> Int#`ltInt16#`Int16#zero#)!c0# :: Int16#c0#=Int# -> Int16#intToInt16#(Int16#x#Int16# -> Int16# -> Int#`ltInt16#`Int16#zero#)Int16# -> Int16# -> Int16#`andInt16#`(Int16# -> Int16#notInt16#Int16#yn#)!c1# :: Int16#c1#=Int# -> Int16#intToInt16#(Int16#x#Int16# -> Int16# -> Int#`gtInt16#`Int16#zero#)Int16# -> Int16# -> Int16#`andInt16#`Int16#yn#!bias# :: Int16#bias#=Int16#c0#Int16# -> Int16# -> Int16#`subInt16#`Int16#c1#!hard# :: Int16#hard#=Int16#c0#Int16# -> Int16# -> Int16#`orInt16#`Int16#c1#{-# INLINE[0]divInt32##-}divInt32#::Int32#->Int32#->Int32#Int32#x#divInt32# :: Int32# -> Int32# -> Int32#`divInt32#`Int32#y#=((Int32#x#Int32# -> Int32# -> Int32#`plusInt32#`Int32#bias#)Int32# -> Int32# -> Int32#`quotInt32#`Int32#y#)Int32# -> Int32# -> Int32#`subInt32#`Int32#hard#wherezero# :: Int32#zero#=Int# -> Int32#intToInt32#Int#0#Int32#xandInt32# :: Int32# -> Int32# -> Int32#`andInt32#`Int32#y=Word32# -> Int32#word32ToInt32#(Int32# -> Word32#int32ToWord32#Int32#xWord32# -> Word32# -> Word32#`andWord32#`Int32# -> Word32#int32ToWord32#Int32#y)Int32#xorInt32# :: Int32# -> Int32# -> Int32#`orInt32#`Int32#y=Word32# -> Int32#word32ToInt32#(Int32# -> Word32#int32ToWord32#Int32#xWord32# -> Word32# -> Word32#`orWord32#`Int32# -> Word32#int32ToWord32#Int32#y)notInt32# :: Int32# -> Int32#notInt32#Int32#x=Word32# -> Int32#word32ToInt32#(Word32# -> Word32#notWord32#(Int32# -> Word32#int32ToWord32#Int32#x))-- See Note [divInt# implementation]!yn# :: Int32#yn#=Int# -> Int32#intToInt32#(Int32#y#Int32# -> Int32# -> Int#`ltInt32#`Int32#zero#)!c0# :: Int32#c0#=Int# -> Int32#intToInt32#(Int32#x#Int32# -> Int32# -> Int#`ltInt32#`Int32#zero#)Int32# -> Int32# -> Int32#`andInt32#`(Int32# -> Int32#notInt32#Int32#yn#)!c1# :: Int32#c1#=Int# -> Int32#intToInt32#(Int32#x#Int32# -> Int32# -> Int#`gtInt32#`Int32#zero#)Int32# -> Int32# -> Int32#`andInt32#`Int32#yn#!bias# :: Int32#bias#=Int32#c0#Int32# -> Int32# -> Int32#`subInt32#`Int32#c1#!hard# :: Int32#hard#=Int32#c0#Int32# -> Int32# -> Int32#`orInt32#`Int32#c1#-- Note [divInt# implementation]-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~-- divInt# (truncated toward zero) is implemented with quotInt# (truncated-- toward negative infinity). They differ when inputs x and y have different signs:--  - x `rem` y has the sign of x and (x `quot` y)*y + (x `rem` y) == x--  - x `mod` y has the sign of y and (x `div`  y)*y + (x `mod` y) == x---- So we bias the input and the result of quotInt as follows:----         if isTrue# (x# ># 0#) && isTrue# (y# <# 0#) then ((x# -# 1#) `quotInt#` y#) -# 1#--    else if isTrue# (x# <# 0#) && isTrue# (y# ># 0#) then ((x# +# 1#) `quotInt#` y#) -# 1#--    else x# `quotInt#` y#---- However this leads to assembly code with lots of branches (#19636) while we-- would like simpler code that we could inline (#18067). So we use some-- branchless code instead as derived below:----         if isTrue# (x# ># 0#) && isTrue# (y# <# 0#) then ((x# -# 1#) `quotInt#` y#) -# 1#--    else if isTrue# (x# <# 0#) && isTrue# (y# ># 0#) then ((x# +# 1#) `quotInt#` y#) -# 1#--    else x# `quotInt#` y#----  ===> { Give names to constants and always use them }----    ((x# +# bias#) `quotInt#` y#) -# hard#--      where--        (bias#,hard#)--          | isTrue# (x# ># 0#) && isTrue# (y# <# 0#) = (-1#, 1#)--          | isTrue# (x# <# 0#) && isTrue# (y# ># 0#) = ( 1#, 1#)--          | otherwise                                = ( 0#, 0#)----  ===> { Compute bias# and hard# independently using Bool# (0#,1#) }----    ((x# +# bias#) `quotInt#` y#) -# hard#--      where--        c0#   = (x# <# 0#) &&# (y# ># 0#)--        c1#   = (x# ># 0#) &&# (y# <# 0#)--        bias# = c0# -# c1#  -- both cases are mutually exclusive so we can subtract them--        hard# = c0# ||# c1# -- (we could add them too here but OR is slightly better)----  ===> { Use yn# variable for "y# <# 0#" }----    ((x# +# bias#) `quotInt#` y#) -# hard#--      where--        -- y# ==# 0# throws an exception so we don't need to consider it--        yn#   = y# <# 0#--        c0#   = (x# <# 0#) &&# (notI# yn#)--        c1#   = (x# ># 0#) &&# yn#--        bias# = c0# -# c1#--        hard# = c0# ||# c1#------ Note that we need to be careful NOT to overflow if we do any additional-- arithmetic on the arguments...  the following previous version of this code-- had problems with overflow:--    | (x# ># 0#) && (y# <# 0#) = ((x# -# y#) -# 1#) `quotInt#` y#--    | (x# <# 0#) && (y# ># 0#) = ((x# -# y#) +# 1#) `quotInt#` y#{-# INLINE[0]modInt##-}modInt#::Int#->Int#->Int#Int#x#modInt# :: Int# -> Int# -> Int#`modInt#`Int#y#=Int#r#Int# -> Int# -> Int#+#Int#k#where-- See Note [modInt# implementation]!yn# :: Int#yn#=Int#y#Int# -> Int# -> Int#<#Int#0#!c0# :: Int#c0#=(Int#x#Int# -> Int# -> Int#<#Int#0#)Int# -> Int# -> Int#`andI#`(Int# -> Int#notI#Int#yn#)!c1# :: Int#c1#=(Int#x#Int# -> Int# -> Int#>#Int#0#)Int# -> Int# -> Int#`andI#`Int#yn#!s# :: Int#s#=Int#0#Int# -> Int# -> Int#-#((Int#c0#Int# -> Int# -> Int#`orI#`Int#c1#)Int# -> Int# -> Int#`andI#`(Int#r#Int# -> Int# -> Int#/=#Int#0#))!k# :: Int#k#=Int#s#Int# -> Int# -> Int#`andI#`Int#y#!r# :: Int#r#=Int#x#Int# -> Int# -> Int#`remInt#`Int#y#{-# INLINE[0]modInt8##-}modInt8#::Int8#->Int8#->Int8#Int8#x#modInt8# :: Int8# -> Int8# -> Int8#`modInt8#`Int8#y#=Int8#r#Int8# -> Int8# -> Int8#`plusInt8#`Int8#k#wherezero# :: Int8#zero#=Int# -> Int8#intToInt8#Int#0#Int8#xandInt8# :: Int8# -> Int8# -> Int8#`andInt8#`Int8#y=Word8# -> Int8#word8ToInt8#(Int8# -> Word8#int8ToWord8#Int8#xWord8# -> Word8# -> Word8#`andWord8#`Int8# -> Word8#int8ToWord8#Int8#y)Int8#xorInt8# :: Int8# -> Int8# -> Int8#`orInt8#`Int8#y=Word8# -> Int8#word8ToInt8#(Int8# -> Word8#int8ToWord8#Int8#xWord8# -> Word8# -> Word8#`orWord8#`Int8# -> Word8#int8ToWord8#Int8#y)notInt8# :: Int8# -> Int8#notInt8#Int8#x=Word8# -> Int8#word8ToInt8#(Word8# -> Word8#notWord8#(Int8# -> Word8#int8ToWord8#Int8#x))-- See Note [modInt# implementation]!yn# :: Int8#yn#=Int# -> Int8#intToInt8#(Int8#y#Int8# -> Int8# -> Int#`ltInt8#`Int8#zero#)!c0# :: Int8#c0#=Int# -> Int8#intToInt8#(Int8#x#Int8# -> Int8# -> Int#`ltInt8#`Int8#zero#)Int8# -> Int8# -> Int8#`andInt8#`(Int8# -> Int8#notInt8#Int8#yn#)!c1# :: Int8#c1#=Int# -> Int8#intToInt8#(Int8#x#Int8# -> Int8# -> Int#`gtInt8#`Int8#zero#)Int8# -> Int8# -> Int8#`andInt8#`Int8#yn#!s# :: Int8#s#=Int8#zero#Int8# -> Int8# -> Int8#`subInt8#`((Int8#c0#Int8# -> Int8# -> Int8#`orInt8#`Int8#c1#)Int8# -> Int8# -> Int8#`andInt8#`(Int# -> Int8#intToInt8#(Int8#r#Int8# -> Int8# -> Int#`neInt8#`Int8#zero#)))!k# :: Int8#k#=Int8#s#Int8# -> Int8# -> Int8#`andInt8#`Int8#y#!r# :: Int8#r#=Int8#x#Int8# -> Int8# -> Int8#`remInt8#`Int8#y#{-# INLINE[0]modInt16##-}modInt16#::Int16#->Int16#->Int16#Int16#x#modInt16# :: Int16# -> Int16# -> Int16#`modInt16#`Int16#y#=Int16#r#Int16# -> Int16# -> Int16#`plusInt16#`Int16#k#wherezero# :: Int16#zero#=Int# -> Int16#intToInt16#Int#0#Int16#xandInt16# :: Int16# -> Int16# -> Int16#`andInt16#`Int16#y=Word16# -> Int16#word16ToInt16#(Int16# -> Word16#int16ToWord16#Int16#xWord16# -> Word16# -> Word16#`andWord16#`Int16# -> Word16#int16ToWord16#Int16#y)Int16#xorInt16# :: Int16# -> Int16# -> Int16#`orInt16#`Int16#y=Word16# -> Int16#word16ToInt16#(Int16# -> Word16#int16ToWord16#Int16#xWord16# -> Word16# -> Word16#`orWord16#`Int16# -> Word16#int16ToWord16#Int16#y)notInt16# :: Int16# -> Int16#notInt16#Int16#x=Word16# -> Int16#word16ToInt16#(Word16# -> Word16#notWord16#(Int16# -> Word16#int16ToWord16#Int16#x))-- See Note [modInt# implementation]!yn# :: Int16#yn#=Int# -> Int16#intToInt16#(Int16#y#Int16# -> Int16# -> Int#`ltInt16#`Int16#zero#)!c0# :: Int16#c0#=Int# -> Int16#intToInt16#(Int16#x#Int16# -> Int16# -> Int#`ltInt16#`Int16#zero#)Int16# -> Int16# -> Int16#`andInt16#`(Int16# -> Int16#notInt16#Int16#yn#)!c1# :: Int16#c1#=Int# -> Int16#intToInt16#(Int16#x#Int16# -> Int16# -> Int#`gtInt16#`Int16#zero#)Int16# -> Int16# -> Int16#`andInt16#`Int16#yn#!s# :: Int16#s#=Int16#zero#Int16# -> Int16# -> Int16#`subInt16#`((Int16#c0#Int16# -> Int16# -> Int16#`orInt16#`Int16#c1#)Int16# -> Int16# -> Int16#`andInt16#`(Int# -> Int16#intToInt16#(Int16#r#Int16# -> Int16# -> Int#`neInt16#`Int16#zero#)))!k# :: Int16#k#=Int16#s#Int16# -> Int16# -> Int16#`andInt16#`Int16#y#!r# :: Int16#r#=Int16#x#Int16# -> Int16# -> Int16#`remInt16#`Int16#y#{-# INLINE[0]modInt32##-}modInt32#::Int32#->Int32#->Int32#Int32#x#modInt32# :: Int32# -> Int32# -> Int32#`modInt32#`Int32#y#=Int32#r#Int32# -> Int32# -> Int32#`plusInt32#`Int32#k#wherezero# :: Int32#zero#=Int# -> Int32#intToInt32#Int#0#Int32#xandInt32# :: Int32# -> Int32# -> Int32#`andInt32#`Int32#y=Word32# -> Int32#word32ToInt32#(Int32# -> Word32#int32ToWord32#Int32#xWord32# -> Word32# -> Word32#`andWord32#`Int32# -> Word32#int32ToWord32#Int32#y)Int32#xorInt32# :: Int32# -> Int32# -> Int32#`orInt32#`Int32#y=Word32# -> Int32#word32ToInt32#(Int32# -> Word32#int32ToWord32#Int32#xWord32# -> Word32# -> Word32#`orWord32#`Int32# -> Word32#int32ToWord32#Int32#y)notInt32# :: Int32# -> Int32#notInt32#Int32#x=Word32# -> Int32#word32ToInt32#(Word32# -> Word32#notWord32#(Int32# -> Word32#int32ToWord32#Int32#x))-- See Note [modInt# implementation]!yn# :: Int32#yn#=Int# -> Int32#intToInt32#(Int32#y#Int32# -> Int32# -> Int#`ltInt32#`Int32#zero#)!c0# :: Int32#c0#=Int# -> Int32#intToInt32#(Int32#x#Int32# -> Int32# -> Int#`ltInt32#`Int32#zero#)Int32# -> Int32# -> Int32#`andInt32#`(Int32# -> Int32#notInt32#Int32#yn#)!c1# :: Int32#c1#=Int# -> Int32#intToInt32#(Int32#x#Int32# -> Int32# -> Int#`gtInt32#`Int32#zero#)Int32# -> Int32# -> Int32#`andInt32#`Int32#yn#!s# :: Int32#s#=Int32#zero#Int32# -> Int32# -> Int32#`subInt32#`((Int32#c0#Int32# -> Int32# -> Int32#`orInt32#`Int32#c1#)Int32# -> Int32# -> Int32#`andInt32#`(Int# -> Int32#intToInt32#(Int32#r#Int32# -> Int32# -> Int#`neInt32#`Int32#zero#)))!k# :: Int32#k#=Int32#s#Int32# -> Int32# -> Int32#`andInt32#`Int32#y#!r# :: Int32#r#=Int32#x#Int32# -> Int32# -> Int32#`remInt32#`Int32#y#-- Note [modInt# implementation]-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~-- Similarly to divInt# (see Note [divInt# implementation]), we can derive the-- branchless implementation of modInt# as follows:----    = if isTrue# (x# ># 0#) && isTrue# (y# <# 0#) ||--         isTrue# (x# <# 0#) && isTrue# (y# ># 0#)--      then if isTrue# (r# /=# 0#) then r# +# y# else 0#--      else r#--    where--     r# = x# `remInt#` y#----  ===> { Introduce constant k# }----    r# +# k#--      where--        k# = if isTrue# (x# ># 0#) && isTrue# (y# <# 0#) ||--                isTrue# (x# <# 0#) && isTrue# (y# ># 0#)--             then if isTrue# (r# /=# 0#) then y# else 0#--             else 0#--        r# = x# `remInt#` y#----  ===> { Compute using Bool# }----    r# +# k#--      where--        yn# = y# <# 0# -- we don't need to consider y# ==# 0#--        c0# = (x# <# 0#) &&# (notI# yn#)--        c1# = (x# ># 0#) &&# yn#--        k#  = if isTrue# ((c0# ||# c1#) &&# (r# /=# 0#))--                then y#--                else 0#--        r#  = x# `remInt#` y#----  ===> { Select y# or 0# in branchless way }----    r# +# k#--      where--        yn# = y# <# 0#--        c0# = (x# <# 0#) &&# (notI# yn#)--        c1# = (x# ># 0#) &&# yn#--        -- s# is either equal to:--        --    0#  (00..00b)--        --    -1# (11..11b)--        -- So we can AND s# with y#--        s#  = 0# -# ((c0# ||# c1#) &&# (r# /=# 0#))--        k#  = s# &&# y#--        r#  = x# `remInt#` y#{-# INLINE[0]divModInt##-}divModInt#::Int#->Int#->(#Int#,Int##)Int#x#divModInt# :: Int# -> Int# -> (# Int#, Int# #)`divModInt#`Int#y#=case(Int#x#Int# -> Int# -> Int#+#Int#bias#)Int# -> Int# -> (# Int#, Int# #)`quotRemInt#`Int#y#of(#Int#q#,Int#r##)->(#Int#q#Int# -> Int# -> Int#-#Int#hard#,Int#r#Int# -> Int# -> Int#+#Int#k##)where-- See Note [divModInt# implementation]!yn# :: Int#yn#=Int#y#Int# -> Int# -> Int#<#Int#0#!c0# :: Int#c0#=(Int#x#Int# -> Int# -> Int#<#Int#0#)Int# -> Int# -> Int#`andI#`(Int# -> Int#notI#Int#yn#)!c1# :: Int#c1#=(Int#x#Int# -> Int# -> Int#>#Int#0#)Int# -> Int# -> Int#`andI#`Int#yn#!bias# :: Int#bias#=Int#c0#Int# -> Int# -> Int#-#Int#c1#!hard# :: Int#hard#=Int#c0#Int# -> Int# -> Int#`orI#`Int#c1#!s# :: Int#s#=Int#0#Int# -> Int# -> Int#-#Int#hard#!k# :: Int#k#=(Int#s#Int# -> Int# -> Int#`andI#`Int#y#)Int# -> Int# -> Int#-#Int#bias#{-# INLINE[0]divModInt8##-}divModInt8#::Int8#->Int8#->(#Int8#,Int8##)Int8#x#divModInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #)`divModInt8#`Int8#y#=case(Int8#x#Int8# -> Int8# -> Int8#`plusInt8#`Int8#bias#)Int8# -> Int8# -> (# Int8#, Int8# #)`quotRemInt8#`Int8#y#of(#Int8#q#,Int8#r##)->(#Int8#q#Int8# -> Int8# -> Int8#`subInt8#`Int8#hard#,Int8#r#Int8# -> Int8# -> Int8#`plusInt8#`Int8#k##)wherezero# :: Int8#zero#=Int# -> Int8#intToInt8#Int#0#Int8#xandInt8# :: Int8# -> Int8# -> Int8#`andInt8#`Int8#y=Word8# -> Int8#word8ToInt8#(Int8# -> Word8#int8ToWord8#Int8#xWord8# -> Word8# -> Word8#`andWord8#`Int8# -> Word8#int8ToWord8#Int8#y)Int8#xorInt8# :: Int8# -> Int8# -> Int8#`orInt8#`Int8#y=Word8# -> Int8#word8ToInt8#(Int8# -> Word8#int8ToWord8#Int8#xWord8# -> Word8# -> Word8#`orWord8#`Int8# -> Word8#int8ToWord8#Int8#y)notInt8# :: Int8# -> Int8#notInt8#Int8#x=Word8# -> Int8#word8ToInt8#(Word8# -> Word8#notWord8#(Int8# -> Word8#int8ToWord8#Int8#x))-- See Note [divModInt# implementation]!yn# :: Int8#yn#=Int# -> Int8#intToInt8#(Int8#y#Int8# -> Int8# -> Int#`ltInt8#`Int8#zero#)!c0# :: Int8#c0#=Int# -> Int8#intToInt8#(Int8#x#Int8# -> Int8# -> Int#`ltInt8#`Int8#zero#)Int8# -> Int8# -> Int8#`andInt8#`(Int8# -> Int8#notInt8#Int8#yn#)!c1# :: Int8#c1#=Int# -> Int8#intToInt8#(Int8#x#Int8# -> Int8# -> Int#`gtInt8#`Int8#zero#)Int8# -> Int8# -> Int8#`andInt8#`Int8#yn#!bias# :: Int8#bias#=Int8#c0#Int8# -> Int8# -> Int8#`subInt8#`Int8#c1#!hard# :: Int8#hard#=Int8#c0#Int8# -> Int8# -> Int8#`orInt8#`Int8#c1#!s# :: Int8#s#=Int8#zero#Int8# -> Int8# -> Int8#`subInt8#`Int8#hard#!k# :: Int8#k#=(Int8#s#Int8# -> Int8# -> Int8#`andInt8#`Int8#y#)Int8# -> Int8# -> Int8#`subInt8#`Int8#bias#{-# INLINE[0]divModInt16##-}divModInt16#::Int16#->Int16#->(#Int16#,Int16##)Int16#x#divModInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #)`divModInt16#`Int16#y#=case(Int16#x#Int16# -> Int16# -> Int16#`plusInt16#`Int16#bias#)Int16# -> Int16# -> (# Int16#, Int16# #)`quotRemInt16#`Int16#y#of(#Int16#q#,Int16#r##)->(#Int16#q#Int16# -> Int16# -> Int16#`subInt16#`Int16#hard#,Int16#r#Int16# -> Int16# -> Int16#`plusInt16#`Int16#k##)wherezero# :: Int16#zero#=Int# -> Int16#intToInt16#Int#0#Int16#xandInt16# :: Int16# -> Int16# -> Int16#`andInt16#`Int16#y=Word16# -> Int16#word16ToInt16#(Int16# -> Word16#int16ToWord16#Int16#xWord16# -> Word16# -> Word16#`andWord16#`Int16# -> Word16#int16ToWord16#Int16#y)Int16#xorInt16# :: Int16# -> Int16# -> Int16#`orInt16#`Int16#y=Word16# -> Int16#word16ToInt16#(Int16# -> Word16#int16ToWord16#Int16#xWord16# -> Word16# -> Word16#`orWord16#`Int16# -> Word16#int16ToWord16#Int16#y)notInt16# :: Int16# -> Int16#notInt16#Int16#x=Word16# -> Int16#word16ToInt16#(Word16# -> Word16#notWord16#(Int16# -> Word16#int16ToWord16#Int16#x))-- See Note [divModInt# implementation]!yn# :: Int16#yn#=Int# -> Int16#intToInt16#(Int16#y#Int16# -> Int16# -> Int#`ltInt16#`Int16#zero#)!c0# :: Int16#c0#=Int# -> Int16#intToInt16#(Int16#x#Int16# -> Int16# -> Int#`ltInt16#`Int16#zero#)Int16# -> Int16# -> Int16#`andInt16#`(Int16# -> Int16#notInt16#Int16#yn#)!c1# :: Int16#c1#=Int# -> Int16#intToInt16#(Int16#x#Int16# -> Int16# -> Int#`gtInt16#`Int16#zero#)Int16# -> Int16# -> Int16#`andInt16#`Int16#yn#!bias# :: Int16#bias#=Int16#c0#Int16# -> Int16# -> Int16#`subInt16#`Int16#c1#!hard# :: Int16#hard#=Int16#c0#Int16# -> Int16# -> Int16#`orInt16#`Int16#c1#!s# :: Int16#s#=Int16#zero#Int16# -> Int16# -> Int16#`subInt16#`Int16#hard#!k# :: Int16#k#=(Int16#s#Int16# -> Int16# -> Int16#`andInt16#`Int16#y#)Int16# -> Int16# -> Int16#`subInt16#`Int16#bias#{-# INLINE[0]divModInt32##-}divModInt32#::Int32#->Int32#->(#Int32#,Int32##)Int32#x#divModInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #)`divModInt32#`Int32#y#=case(Int32#x#Int32# -> Int32# -> Int32#`plusInt32#`Int32#bias#)Int32# -> Int32# -> (# Int32#, Int32# #)`quotRemInt32#`Int32#y#of(#Int32#q#,Int32#r##)->(#Int32#q#Int32# -> Int32# -> Int32#`subInt32#`Int32#hard#,Int32#r#Int32# -> Int32# -> Int32#`plusInt32#`Int32#k##)wherezero# :: Int32#zero#=Int# -> Int32#intToInt32#Int#0#Int32#xandInt32# :: Int32# -> Int32# -> Int32#`andInt32#`Int32#y=Word32# -> Int32#word32ToInt32#(Int32# -> Word32#int32ToWord32#Int32#xWord32# -> Word32# -> Word32#`andWord32#`Int32# -> Word32#int32ToWord32#Int32#y)Int32#xorInt32# :: Int32# -> Int32# -> Int32#`orInt32#`Int32#y=Word32# -> Int32#word32ToInt32#(Int32# -> Word32#int32ToWord32#Int32#xWord32# -> Word32# -> Word32#`orWord32#`Int32# -> Word32#int32ToWord32#Int32#y)notInt32# :: Int32# -> Int32#notInt32#Int32#x=Word32# -> Int32#word32ToInt32#(Word32# -> Word32#notWord32#(Int32# -> Word32#int32ToWord32#Int32#x))-- See Note [divModInt# implementation]!yn# :: Int32#yn#=Int# -> Int32#intToInt32#(Int32#y#Int32# -> Int32# -> Int#`ltInt32#`Int32#zero#)!c0# :: Int32#c0#=Int# -> Int32#intToInt32#(Int32#x#Int32# -> Int32# -> Int#`ltInt32#`Int32#zero#)Int32# -> Int32# -> Int32#`andInt32#`(Int32# -> Int32#notInt32#Int32#yn#)!c1# :: Int32#c1#=Int# -> Int32#intToInt32#(Int32#x#Int32# -> Int32# -> Int#`gtInt32#`Int32#zero#)Int32# -> Int32# -> Int32#`andInt32#`Int32#yn#!bias# :: Int32#bias#=Int32#c0#Int32# -> Int32# -> Int32#`subInt32#`Int32#c1#!hard# :: Int32#hard#=Int32#c0#Int32# -> Int32# -> Int32#`orInt32#`Int32#c1#!s# :: Int32#s#=Int32#zero#Int32# -> Int32# -> Int32#`subInt32#`Int32#hard#!k# :: Int32#k#=(Int32#s#Int32# -> Int32# -> Int32#`andInt32#`Int32#y#)Int32# -> Int32# -> Int32#`subInt32#`Int32#bias#-- Note [divModInt# implementation]-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~-- divModInt# is written by deriving the following code similarly to divInt# and-- modInt# (see Note [divInt# implementation] and Note [modInt#-- implementation]).----    x# `divModInt#` y#--     | isTrue# (x# ># 0#) && isTrue# (y# <# 0#) =--                                        case (x# -# 1#) `quotRemInt#` y# of--                                          (# q, r #) -> (# q -# 1#, r +# y# +# 1# #)--     | isTrue# (x# <# 0#) && isTrue# (y# ># 0#) =--                                        case (x# +# 1#) `quotRemInt#` y# of--                                          (# q, r #) -> (# q -# 1#, r +# y# -# 1# #)--     | otherwise                                =--                                        x# `quotRemInt#` y#----  ===> { Introduce constants }----    case (x# +# bias#) `quotRemInt#` y# of--      (# q#, r# #) -> (# q# -# hard#, r# +# k# #)--      where--       (bias#,hard#,k#)--        | isTrue# (x# ># 0#) && isTrue# (y# <# 0#) = (-1#, 1#, y#+1#)--        | isTrue# (x# <# 0#) && isTrue# (y# ># 0#) = ( 1#, 1#, y#-1#)--        | otherwise                                = ( 0#, 0#, 0#-0#)----  ===> { Compute using Bool# }----    case (x# +# bias#) `quotRemInt#` y# of--      (# q#, r# #) -> (# q# -# hard#, r# +# k# #)--      where--        yn#   = y# <# 0#--        c0#   = (x# <# 0#) `andI#` (notI# yn#)--        c1#   = (x# ># 0#) `andI#` yn#--        bias# = c0# -# c1#--        hard# = c0# `orI#` c1#--        s#    = 0# -# hard#--        k#    = (s# `andI#` y#) -# bias#--{- **************************************************************                                                              **               Constraint tuples                              **                                                              ************************************************************** -}typeCTuple0=(()::Constraint)typeCTuple1=CSoloclassCUnitclassa=>CSoloaclass(c1,c2)=>CTuple2c1c2class(c1,c2,c3)=>CTuple3c1c2c3class(c1,c2,c3,c4)=>CTuple4c1c2c3c4class(c1,c2,c3,c4,c5)=>CTuple5c1c2c3c4c5class(c1,c2,c3,c4,c5,c6)=>CTuple6c1c2c3c4c5c6class(c1,c2,c3,c4,c5,c6,c7)=>CTuple7c1c2c3c4c5c6c7class(c1,c2,c3,c4,c5,c6,c7,c8)=>CTuple8c1c2c3c4c5c6c7c8class(c1,c2,c3,c4,c5,c6,c7,c8,c9)=>CTuple9c1c2c3c4c5c6c7c8c9class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10)=>CTuple10c1c2c3c4c5c6c7c8c9c10class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11)=>CTuple11c1c2c3c4c5c6c7c8c9c10c11class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12)=>CTuple12c1c2c3c4c5c6c7c8c9c10c11c12class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13)=>CTuple13c1c2c3c4c5c6c7c8c9c10c11c12c13class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14)=>CTuple14c1c2c3c4c5c6c7c8c9c10c11c12c13c14class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15)=>CTuple15c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16)=>CTuple16c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17)=>CTuple17c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18)=>CTuple18c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19)=>CTuple19c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20)=>CTuple20c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21)=>CTuple21c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22)=>CTuple22c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23)=>CTuple23c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24)=>CTuple24c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25)=>CTuple25c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26)=>CTuple26c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27)=>CTuple27c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28)=>CTuple28c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29)=>CTuple29c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30)=>CTuple30c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31)=>CTuple31c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32)=>CTuple32c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33)=>CTuple33c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34)=>CTuple34c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35)=>CTuple35c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36)=>CTuple36c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37)=>CTuple37c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38)=>CTuple38c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39)=>CTuple39c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40)=>CTuple40c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41)=>CTuple41c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42)=>CTuple42c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43)=>CTuple43c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44)=>CTuple44c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45)=>CTuple45c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46)=>CTuple46c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47)=>CTuple47c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48)=>CTuple48c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49)=>CTuple49c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50)=>CTuple50c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51)=>CTuple51c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52)=>CTuple52c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53)=>CTuple53c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54)=>CTuple54c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55)=>CTuple55c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56)=>CTuple56c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57)=>CTuple57c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58)=>CTuple58c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59)=>CTuple59c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60)=>CTuple60c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60,c61)=>CTuple61c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60c61class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60,c61,c62)=>CTuple62c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60c61c62class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60,c61,c62,c63)=>CTuple63c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60c61c62c63class(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60,c61,c62,c63,c64)=>CTuple64c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60c61c62c63c64instance() :: ConstraintCUnitinstancea=>CSoloainstance(c1,c2)=>CTuple2c1c2instance(c1,c2,c3)=>CTuple3c1c2c3instance(c1,c2,c3,c4)=>CTuple4c1c2c3c4instance(c1,c2,c3,c4,c5)=>CTuple5c1c2c3c4c5instance(c1,c2,c3,c4,c5,c6)=>CTuple6c1c2c3c4c5c6instance(c1,c2,c3,c4,c5,c6,c7)=>CTuple7c1c2c3c4c5c6c7instance(c1,c2,c3,c4,c5,c6,c7,c8)=>CTuple8c1c2c3c4c5c6c7c8instance(c1,c2,c3,c4,c5,c6,c7,c8,c9)=>CTuple9c1c2c3c4c5c6c7c8c9instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10)=>CTuple10c1c2c3c4c5c6c7c8c9c10instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11)=>CTuple11c1c2c3c4c5c6c7c8c9c10c11instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12)=>CTuple12c1c2c3c4c5c6c7c8c9c10c11c12instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13)=>CTuple13c1c2c3c4c5c6c7c8c9c10c11c12c13instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14)=>CTuple14c1c2c3c4c5c6c7c8c9c10c11c12c13c14instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15)=>CTuple15c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16)=>CTuple16c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17)=>CTuple17c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18)=>CTuple18c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19)=>CTuple19c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20)=>CTuple20c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21)=>CTuple21c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22)=>CTuple22c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23)=>CTuple23c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24)=>CTuple24c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25)=>CTuple25c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26)=>CTuple26c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27)=>CTuple27c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28)=>CTuple28c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29)=>CTuple29c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30)=>CTuple30c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31)=>CTuple31c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32)=>CTuple32c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33)=>CTuple33c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34)=>CTuple34c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35)=>CTuple35c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36)=>CTuple36c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37)=>CTuple37c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38)=>CTuple38c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39)=>CTuple39c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40)=>CTuple40c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41)=>CTuple41c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42)=>CTuple42c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43)=>CTuple43c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44)=>CTuple44c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45)=>CTuple45c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46)=>CTuple46c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47)=>CTuple47c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48)=>CTuple48c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49)=>CTuple49c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50)=>CTuple50c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51)=>CTuple51c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52)=>CTuple52c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53)=>CTuple53c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54)=>CTuple54c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55)=>CTuple55c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56)=>CTuple56c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57)=>CTuple57c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58)=>CTuple58c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59)=>CTuple59c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60)=>CTuple60c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60,c61)=>CTuple61c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60c61instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60,c61,c62)=>CTuple62c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60c61c62instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60,c61,c62,c63)=>CTuple63c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60c61c62c63instance(c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12,c13,c14,c15,c16,c17,c18,c19,c20,c21,c22,c23,c24,c25,c26,c27,c28,c29,c30,c31,c32,c33,c34,c35,c36,c37,c38,c39,c40,c41,c42,c43,c44,c45,c46,c47,c48,c49,c50,c51,c52,c53,c54,c55,c56,c57,c58,c59,c60,c61,c62,c63,c64)=>CTuple64c1c2c3c4c5c6c7c8c9c10c11c12c13c14c15c16c17c18c19c20c21c22c23c24c25c26c27c28c29c30c31c32c33c34c35c36c37c38c39c40c41c42c43c44c45c46c47c48c49c50c51c52c53c54c55c56c57c58c59c60c61c62c63c64

[8]ページ先頭

©2009-2025 Movatter.jp