Movatterモバイル変換
[0]ホーム
{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, MagicHash, UnboxedTuples, StandaloneDeriving, NegativeLiterals #-}{-# OPTIONS_HADDOCK not-home #-}------------------------------------------------------------------------------- |-- Module : GHC.Int-- Copyright : (c) The University of Glasgow 1997-2002-- License : see libraries/base/LICENSE---- Maintainer : cvs-ghc@haskell.org-- Stability : internal-- Portability : non-portable (GHC Extensions)---- The sized integral datatypes, 'Int8', 'Int16', 'Int32', and 'Int64'.-------------------------------------------------------------------------------#include "MachDeps.h"moduleGHC.Int(Int(..),Int8(..),Int16(..),Int32(..),Int64(..),uncheckedIShiftL64#,uncheckedIShiftRA64#,-- * Equality operators-- | See GHC.Classes#matching_overloaded_methods_in_ruleseqInt,neInt,gtInt,geInt,ltInt,leInt,eqInt8,neInt8,gtInt8,geInt8,ltInt8,leInt8,eqInt16,neInt16,gtInt16,geInt16,ltInt16,leInt16,eqInt32,neInt32,gtInt32,geInt32,ltInt32,leInt32,eqInt64,neInt64,gtInt64,geInt64,ltInt64,leInt64)whereimportData.BitsimportData.Maybe#if WORD_SIZE_IN_BITS < 64importGHC.IntWord64#endifimportGHC.BaseimportGHC.EnumimportGHC.NumimportGHC.RealimportGHC.ReadimportGHC.ArrimportGHC.Wordhiding(uncheckedShiftL64#,uncheckedShiftRL64#)importGHC.Show-------------------------------------------------------------------------- type Int8-------------------------------------------------------------------------- Int8 is represented in the same way as Int. Operations may assume-- and must ensure that it holds only values from its logical range.data{-# CTYPE"HsInt8"#-}Int8=I8#Int#-- ^ 8-bit signed integer type-- See GHC.Classes#matching_overloaded_methods_in_rules-- | @since 2.01instanceEqInt8where== :: Int8 -> Int8 -> Bool(==)=Int8 -> Int8 -> BooleqInt8/= :: Int8 -> Int8 -> Bool(/=)=Int8 -> Int8 -> BoolneInt8eqInt8,neInt8::Int8->Int8->BooleqInt8 :: Int8 -> Int8 -> BooleqInt8(I8#Int#x)(I8#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#==#Int#y)neInt8 :: Int8 -> Int8 -> BoolneInt8(I8#Int#x)(I8#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#/=#Int#y){-# INLINE[1]eqInt8#-}{-# INLINE[1]neInt8#-}-- | @since 2.01instanceOrdInt8where< :: Int8 -> Int8 -> Bool(<)=Int8 -> Int8 -> BoolltInt8<= :: Int8 -> Int8 -> Bool(<=)=Int8 -> Int8 -> BoolleInt8>= :: Int8 -> Int8 -> Bool(>=)=Int8 -> Int8 -> BoolgeInt8> :: Int8 -> Int8 -> Bool(>)=Int8 -> Int8 -> BoolgtInt8{-# INLINE[1]gtInt8#-}{-# INLINE[1]geInt8#-}{-# INLINE[1]ltInt8#-}{-# INLINE[1]leInt8#-}gtInt8,geInt8,ltInt8,leInt8::Int8->Int8->Bool(I8#Int#x)gtInt8 :: Int8 -> Int8 -> Bool`gtInt8`(I8#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#y)(I8#Int#x)geInt8 :: Int8 -> Int8 -> Bool`geInt8`(I8#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>=#Int#y)(I8#Int#x)ltInt8 :: Int8 -> Int8 -> Bool`ltInt8`(I8#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<#Int#y)(I8#Int#x)leInt8 :: Int8 -> Int8 -> Bool`leInt8`(I8#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<=#Int#y)-- | @since 2.01instanceShowInt8whereshowsPrec :: Int -> Int8 -> ShowSshowsPrecIntpInt8x=Int -> Int -> ShowSforall a. Show a => Int -> a -> ShowSshowsPrecIntp(Int8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt8x::Int)-- | @since 2.01instanceNumInt8where(I8#Int#x#)+ :: Int8 -> Int8 -> Int8+(I8#Int#y#)=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#+#Int#y#))(I8#Int#x#)- :: Int8 -> Int8 -> Int8-(I8#Int#y#)=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#-#Int#y#))(I8#Int#x#)* :: Int8 -> Int8 -> Int8*(I8#Int#y#)=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#*#Int#y#))negate :: Int8 -> Int8negate(I8#Int#x#)=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int# -> Int#negateInt#Int#x#))abs :: Int8 -> Int8absInt8x|Int8xInt8 -> Int8 -> Boolforall a. Ord a => a -> a -> Bool>=Int80=Int8x|Boolotherwise=Int8 -> Int8forall a. Num a => a -> anegateInt8xsignum :: Int8 -> Int8signumInt8x|Int8xInt8 -> Int8 -> Boolforall a. Ord a => a -> a -> Bool>Int80=Int81signumInt80=Int80signumInt8_=Int8-1fromInteger :: Integer -> Int8fromIntegerIntegeri=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Integer -> Int#integerToIntIntegeri))-- | @since 2.01instanceRealInt8wheretoRational :: Int8 -> RationaltoRationalInt8x=Int8 -> Integerforall a. Integral a => a -> IntegertoIntegerInt8xInteger -> Integer -> Rationalforall a. Integral a => a -> a -> Ratio a%Integer1-- | @since 2.01instanceEnumInt8wheresucc :: Int8 -> Int8succInt8x|Int8xInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool/=Int8forall a. Bounded a => amaxBound=Int8xInt8 -> Int8 -> Int8forall a. Num a => a -> a -> a+Int81|Boolotherwise=String -> Int8forall a. String -> asuccErrorString"Int8"pred :: Int8 -> Int8predInt8x|Int8xInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool/=Int8forall a. Bounded a => aminBound=Int8xInt8 -> Int8 -> Int8forall a. Num a => a -> a -> a-Int81|Boolotherwise=String -> Int8forall a. String -> apredErrorString"Int8"toEnum :: Int -> Int8toEnumi :: Inti@(I#Int#i#)|IntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Int8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegral(Int8forall a. Bounded a => aminBound::Int8)Bool -> Bool -> Bool&&IntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegral(Int8forall a. Bounded a => amaxBound::Int8)=Int# -> Int8I8#Int#i#|Boolotherwise=String -> Int -> (Int8, Int8) -> Int8forall a b. Show a => String -> Int -> (a, a) -> btoEnumErrorString"Int8"Inti(Int8forall a. Bounded a => aminBound::Int8,Int8forall a. Bounded a => amaxBound::Int8)fromEnum :: Int8 -> IntfromEnum(I8#Int#x#)=Int# -> IntI#Int#x#enumFrom :: Int8 -> [Int8]enumFrom=Int8 -> [Int8]forall a. (Enum a, Bounded a) => a -> [a]boundedEnumFromenumFromThen :: Int8 -> Int8 -> [Int8]enumFromThen=Int8 -> Int8 -> [Int8]forall a. (Enum a, Bounded a) => a -> a -> [a]boundedEnumFromThen-- | @since 2.01instanceIntegralInt8wherequot :: Int8 -> Int8 -> Int8quotx :: Int8x@(I8#Int#x#)y :: Int8y@(I8#Int#y#)|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int80=Int8forall a. adivZeroError|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==(Int8-1)Bool -> Bool -> Bool&&Int8xInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int8forall a. Bounded a => aminBound=Int8forall a. aoverflowError-- Note [Order of tests]|Boolotherwise=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#`quotInt#`Int#y#))rem :: Int8 -> Int8 -> Int8rem(I8#Int#x#)y :: Int8y@(I8#Int#y#)|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int80=Int8forall a. adivZeroError|Boolotherwise=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#`remInt#`Int#y#))div :: Int8 -> Int8 -> Int8divx :: Int8x@(I8#Int#x#)y :: Int8y@(I8#Int#y#)|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int80=Int8forall a. adivZeroError|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==(Int8-1)Bool -> Bool -> Bool&&Int8xInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int8forall a. Bounded a => aminBound=Int8forall a. aoverflowError-- Note [Order of tests]|Boolotherwise=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#`divInt#`Int#y#))mod :: Int8 -> Int8 -> Int8mod(I8#Int#x#)y :: Int8y@(I8#Int#y#)|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int80=Int8forall a. adivZeroError|Boolotherwise=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#`modInt#`Int#y#))quotRem :: Int8 -> Int8 -> (Int8, Int8)quotRemx :: Int8x@(I8#Int#x#)y :: Int8y@(I8#Int#y#)|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int80=(Int8, Int8)forall a. adivZeroError-- Note [Order of tests]|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==(Int8-1)Bool -> Bool -> Bool&&Int8xInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int8forall a. Bounded a => aminBound=(Int8forall a. aoverflowError,Int80)|Boolotherwise=caseInt#x#Int# -> Int# -> (# Int#, Int# #)`quotRemInt#`Int#y#of(#Int#q,Int#r#)->(Int# -> Int8I8#(Int# -> Int#narrow8Int#Int#q),Int# -> Int8I8#(Int# -> Int#narrow8Int#Int#r))divMod :: Int8 -> Int8 -> (Int8, Int8)divModx :: Int8x@(I8#Int#x#)y :: Int8y@(I8#Int#y#)|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int80=(Int8, Int8)forall a. adivZeroError-- Note [Order of tests]|Int8yInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==(Int8-1)Bool -> Bool -> Bool&&Int8xInt8 -> Int8 -> Boolforall a. Eq a => a -> a -> Bool==Int8forall a. Bounded a => aminBound=(Int8forall a. aoverflowError,Int80)|Boolotherwise=caseInt#x#Int# -> Int# -> (# Int#, Int# #)`divModInt#`Int#y#of(#Int#d,Int#m#)->(Int# -> Int8I8#(Int# -> Int#narrow8Int#Int#d),Int# -> Int8I8#(Int# -> Int#narrow8Int#Int#m))toInteger :: Int8 -> IntegertoInteger(I8#Int#x#)=Int# -> IntegersmallIntegerInt#x#-- | @since 2.01instanceBoundedInt8whereminBound :: Int8minBound=Int8-0x80maxBound :: Int8maxBound=Int80x7F-- | @since 2.01instanceIxInt8whererange :: (Int8, Int8) -> [Int8]range(Int8m,Int8n)=[Int8m..Int8n]unsafeIndex :: (Int8, Int8) -> Int8 -> IntunsafeIndex(Int8m,Int8_)Int8i=Int8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt8iInt -> Int -> Intforall a. Num a => a -> a -> a-Int8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt8minRange :: (Int8, Int8) -> Int8 -> BoolinRange(Int8m,Int8n)Int8i=Int8mInt8 -> Int8 -> Boolforall a. Ord a => a -> a -> Bool<=Int8iBool -> Bool -> Bool&&Int8iInt8 -> Int8 -> Boolforall a. Ord a => a -> a -> Bool<=Int8n-- | @since 2.01instanceReadInt8wherereadsPrec :: Int -> ReadS Int8readsPrecIntpStrings=[(Int -> Int8forall a b. (Integral a, Num b) => a -> bfromIntegral(Intx::Int),Stringr)|(Intx,Stringr)<-Int -> ReadS Intforall a. Read a => Int -> ReadS areadsPrecIntpStrings]-- | @since 2.01instanceBitsInt8where{-# INLINEshift#-}{-# INLINEbit#-}{-# INLINEtestBit#-}{-# INLINEpopCount#-}(I8#Int#x#).&. :: Int8 -> Int8 -> Int8.&.(I8#Int#y#)=Int# -> Int8I8#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`and#`Int# -> Word#int2Word#Int#y#))(I8#Int#x#).|. :: Int8 -> Int8 -> Int8.|.(I8#Int#y#)=Int# -> Int8I8#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`or#`Int# -> Word#int2Word#Int#y#))(I8#Int#x#)xor :: Int8 -> Int8 -> Int8`xor`(I8#Int#y#)=Int# -> Int8I8#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`xor#`Int# -> Word#int2Word#Int#y#))complement :: Int8 -> Int8complement(I8#Int#x#)=Int# -> Int8I8#(Word# -> Int#word2Int#(Word# -> Word#not#(Int# -> Word#int2Word#Int#x#)))(I8#Int#x#)shift :: Int8 -> Int -> Int8`shift`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#`iShiftL#`Int#i#))|Boolotherwise=Int# -> Int8I8#(Int#x#Int# -> Int# -> Int#`iShiftRA#`Int# -> Int#negateInt#Int#i#)(I8#Int#x#)shiftL :: Int8 -> Int -> Int8`shiftL`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#`iShiftL#`Int#i#))|Boolotherwise=Int8forall a. aoverflowError(I8#Int#x#)unsafeShiftL :: Int8 -> Int -> Int8`unsafeShiftL`(I#Int#i#)=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Int#x#Int# -> Int# -> Int#`uncheckedIShiftL#`Int#i#))(I8#Int#x#)shiftR :: Int8 -> Int -> Int8`shiftR`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int8I8#(Int#x#Int# -> Int# -> Int#`iShiftRA#`Int#i#)|Boolotherwise=Int8forall a. aoverflowError(I8#Int#x#)unsafeShiftR :: Int8 -> Int -> Int8`unsafeShiftR`(I#Int#i#)=Int# -> Int8I8#(Int#x#Int# -> Int# -> Int#`uncheckedIShiftRA#`Int#i#)(I8#Int#x#)rotate :: Int8 -> Int -> Int8`rotate`(I#Int#i#)|Int# -> BoolisTrue#(Int#i'#Int# -> Int# -> Int#==#Int#0#)=Int# -> Int8I8#Int#x#|Boolotherwise=Int# -> Int8I8#(Int# -> Int#narrow8Int#(Word# -> Int#word2Int#((Word#x'#Word# -> Int# -> Word#`uncheckedShiftL#`Int#i'#)Word# -> Word# -> Word#`or#`(Word#x'#Word# -> Int# -> Word#`uncheckedShiftRL#`(Int#8#Int# -> Int# -> Int#-#Int#i'#)))))where!x'# :: Word#x'#=Word# -> Word#narrow8Word#(Int# -> Word#int2Word#Int#x#)!i'# :: Int#i'#=Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#i#Word# -> Word# -> Word#`and#`Word#7##)bitSizeMaybe :: Int8 -> Maybe IntbitSizeMaybeInt8i=Int -> Maybe Intforall a. a -> Maybe aJust(Int8 -> Intforall b. FiniteBits b => b -> IntfiniteBitSizeInt8i)bitSize :: Int8 -> IntbitSizeInt8i=Int8 -> Intforall b. FiniteBits b => b -> IntfiniteBitSizeInt8iisSigned :: Int8 -> BoolisSignedInt8_=BoolTruepopCount :: Int8 -> IntpopCount(I8#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#popCnt8#(Int# -> Word#int2Word#Int#x#)))bit :: Int -> Int8bit=Int -> Int8forall a. (Bits a, Num a) => Int -> abitDefaulttestBit :: Int8 -> Int -> BooltestBit=Int8 -> Int -> Boolforall a. (Bits a, Num a) => a -> Int -> BooltestBitDefault-- | @since 4.6.0.0instanceFiniteBitsInt8where{-# INLINEcountLeadingZeros#-}{-# INLINEcountTrailingZeros#-}finiteBitSize :: Int8 -> IntfiniteBitSizeInt8_=Int8countLeadingZeros :: Int8 -> IntcountLeadingZeros(I8#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#clz8#(Int# -> Word#int2Word#Int#x#)))countTrailingZeros :: Int8 -> IntcountTrailingZeros(I8#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#ctz8#(Int# -> Word#int2Word#Int#x#))){-# RULES"fromIntegral/Int8->Int8"fromIntegral=id::Int8->Int8"fromIntegral/a->Int8"fromIntegral=\x->casefromIntegralxofI#x#->I8#(narrow8Int#x#)"fromIntegral/Int8->a"fromIntegral=\(I8#x#)->fromIntegral(I#x#)#-}{-# RULES"properFraction/Float->(Int8,Float)"properFraction=\x->caseproperFractionxof{(n,y)->((fromIntegral::Int->Int8)n,y::Float)}"truncate/Float->Int8"truncate=(fromIntegral::Int->Int8).(truncate::Float->Int)"floor/Float->Int8"floor=(fromIntegral::Int->Int8).(floor::Float->Int)"ceiling/Float->Int8"ceiling=(fromIntegral::Int->Int8).(ceiling::Float->Int)"round/Float->Int8"round=(fromIntegral::Int->Int8).(round::Float->Int)#-}{-# RULES"properFraction/Double->(Int8,Double)"properFraction=\x->caseproperFractionxof{(n,y)->((fromIntegral::Int->Int8)n,y::Double)}"truncate/Double->Int8"truncate=(fromIntegral::Int->Int8).(truncate::Double->Int)"floor/Double->Int8"floor=(fromIntegral::Int->Int8).(floor::Double->Int)"ceiling/Double->Int8"ceiling=(fromIntegral::Int->Int8).(ceiling::Double->Int)"round/Double->Int8"round=(fromIntegral::Int->Int8).(round::Double->Int)#-}-------------------------------------------------------------------------- type Int16-------------------------------------------------------------------------- Int16 is represented in the same way as Int. Operations may assume-- and must ensure that it holds only values from its logical range.data{-# CTYPE"HsInt16"#-}Int16=I16#Int#-- ^ 16-bit signed integer type-- See GHC.Classes#matching_overloaded_methods_in_rules-- | @since 2.01instanceEqInt16where== :: Int16 -> Int16 -> Bool(==)=Int16 -> Int16 -> BooleqInt16/= :: Int16 -> Int16 -> Bool(/=)=Int16 -> Int16 -> BoolneInt16eqInt16,neInt16::Int16->Int16->BooleqInt16 :: Int16 -> Int16 -> BooleqInt16(I16#Int#x)(I16#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#==#Int#y)neInt16 :: Int16 -> Int16 -> BoolneInt16(I16#Int#x)(I16#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#/=#Int#y){-# INLINE[1]eqInt16#-}{-# INLINE[1]neInt16#-}-- | @since 2.01instanceOrdInt16where< :: Int16 -> Int16 -> Bool(<)=Int16 -> Int16 -> BoolltInt16<= :: Int16 -> Int16 -> Bool(<=)=Int16 -> Int16 -> BoolleInt16>= :: Int16 -> Int16 -> Bool(>=)=Int16 -> Int16 -> BoolgeInt16> :: Int16 -> Int16 -> Bool(>)=Int16 -> Int16 -> BoolgtInt16{-# INLINE[1]gtInt16#-}{-# INLINE[1]geInt16#-}{-# INLINE[1]ltInt16#-}{-# INLINE[1]leInt16#-}gtInt16,geInt16,ltInt16,leInt16::Int16->Int16->Bool(I16#Int#x)gtInt16 :: Int16 -> Int16 -> Bool`gtInt16`(I16#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#y)(I16#Int#x)geInt16 :: Int16 -> Int16 -> Bool`geInt16`(I16#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>=#Int#y)(I16#Int#x)ltInt16 :: Int16 -> Int16 -> Bool`ltInt16`(I16#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<#Int#y)(I16#Int#x)leInt16 :: Int16 -> Int16 -> Bool`leInt16`(I16#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<=#Int#y)-- | @since 2.01instanceShowInt16whereshowsPrec :: Int -> Int16 -> ShowSshowsPrecIntpInt16x=Int -> Int -> ShowSforall a. Show a => Int -> a -> ShowSshowsPrecIntp(Int16 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt16x::Int)-- | @since 2.01instanceNumInt16where(I16#Int#x#)+ :: Int16 -> Int16 -> Int16+(I16#Int#y#)=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#+#Int#y#))(I16#Int#x#)- :: Int16 -> Int16 -> Int16-(I16#Int#y#)=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#-#Int#y#))(I16#Int#x#)* :: Int16 -> Int16 -> Int16*(I16#Int#y#)=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#*#Int#y#))negate :: Int16 -> Int16negate(I16#Int#x#)=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int# -> Int#negateInt#Int#x#))abs :: Int16 -> Int16absInt16x|Int16xInt16 -> Int16 -> Boolforall a. Ord a => a -> a -> Bool>=Int160=Int16x|Boolotherwise=Int16 -> Int16forall a. Num a => a -> anegateInt16xsignum :: Int16 -> Int16signumInt16x|Int16xInt16 -> Int16 -> Boolforall a. Ord a => a -> a -> Bool>Int160=Int161signumInt160=Int160signumInt16_=Int16-1fromInteger :: Integer -> Int16fromIntegerIntegeri=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Integer -> Int#integerToIntIntegeri))-- | @since 2.01instanceRealInt16wheretoRational :: Int16 -> RationaltoRationalInt16x=Int16 -> Integerforall a. Integral a => a -> IntegertoIntegerInt16xInteger -> Integer -> Rationalforall a. Integral a => a -> a -> Ratio a%Integer1-- | @since 2.01instanceEnumInt16wheresucc :: Int16 -> Int16succInt16x|Int16xInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool/=Int16forall a. Bounded a => amaxBound=Int16xInt16 -> Int16 -> Int16forall a. Num a => a -> a -> a+Int161|Boolotherwise=String -> Int16forall a. String -> asuccErrorString"Int16"pred :: Int16 -> Int16predInt16x|Int16xInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool/=Int16forall a. Bounded a => aminBound=Int16xInt16 -> Int16 -> Int16forall a. Num a => a -> a -> a-Int161|Boolotherwise=String -> Int16forall a. String -> apredErrorString"Int16"toEnum :: Int -> Int16toEnumi :: Inti@(I#Int#i#)|IntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Int16 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegral(Int16forall a. Bounded a => aminBound::Int16)Bool -> Bool -> Bool&&IntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int16 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegral(Int16forall a. Bounded a => amaxBound::Int16)=Int# -> Int16I16#Int#i#|Boolotherwise=String -> Int -> (Int16, Int16) -> Int16forall a b. Show a => String -> Int -> (a, a) -> btoEnumErrorString"Int16"Inti(Int16forall a. Bounded a => aminBound::Int16,Int16forall a. Bounded a => amaxBound::Int16)fromEnum :: Int16 -> IntfromEnum(I16#Int#x#)=Int# -> IntI#Int#x#enumFrom :: Int16 -> [Int16]enumFrom=Int16 -> [Int16]forall a. (Enum a, Bounded a) => a -> [a]boundedEnumFromenumFromThen :: Int16 -> Int16 -> [Int16]enumFromThen=Int16 -> Int16 -> [Int16]forall a. (Enum a, Bounded a) => a -> a -> [a]boundedEnumFromThen-- | @since 2.01instanceIntegralInt16wherequot :: Int16 -> Int16 -> Int16quotx :: Int16x@(I16#Int#x#)y :: Int16y@(I16#Int#y#)|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int160=Int16forall a. adivZeroError|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==(Int16-1)Bool -> Bool -> Bool&&Int16xInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int16forall a. Bounded a => aminBound=Int16forall a. aoverflowError-- Note [Order of tests]|Boolotherwise=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#`quotInt#`Int#y#))rem :: Int16 -> Int16 -> Int16rem(I16#Int#x#)y :: Int16y@(I16#Int#y#)|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int160=Int16forall a. adivZeroError|Boolotherwise=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#`remInt#`Int#y#))div :: Int16 -> Int16 -> Int16divx :: Int16x@(I16#Int#x#)y :: Int16y@(I16#Int#y#)|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int160=Int16forall a. adivZeroError|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==(Int16-1)Bool -> Bool -> Bool&&Int16xInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int16forall a. Bounded a => aminBound=Int16forall a. aoverflowError-- Note [Order of tests]|Boolotherwise=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#`divInt#`Int#y#))mod :: Int16 -> Int16 -> Int16mod(I16#Int#x#)y :: Int16y@(I16#Int#y#)|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int160=Int16forall a. adivZeroError|Boolotherwise=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#`modInt#`Int#y#))quotRem :: Int16 -> Int16 -> (Int16, Int16)quotRemx :: Int16x@(I16#Int#x#)y :: Int16y@(I16#Int#y#)|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int160=(Int16, Int16)forall a. adivZeroError-- Note [Order of tests]|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==(Int16-1)Bool -> Bool -> Bool&&Int16xInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int16forall a. Bounded a => aminBound=(Int16forall a. aoverflowError,Int160)|Boolotherwise=caseInt#x#Int# -> Int# -> (# Int#, Int# #)`quotRemInt#`Int#y#of(#Int#q,Int#r#)->(Int# -> Int16I16#(Int# -> Int#narrow16Int#Int#q),Int# -> Int16I16#(Int# -> Int#narrow16Int#Int#r))divMod :: Int16 -> Int16 -> (Int16, Int16)divModx :: Int16x@(I16#Int#x#)y :: Int16y@(I16#Int#y#)|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int160=(Int16, Int16)forall a. adivZeroError-- Note [Order of tests]|Int16yInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==(Int16-1)Bool -> Bool -> Bool&&Int16xInt16 -> Int16 -> Boolforall a. Eq a => a -> a -> Bool==Int16forall a. Bounded a => aminBound=(Int16forall a. aoverflowError,Int160)|Boolotherwise=caseInt#x#Int# -> Int# -> (# Int#, Int# #)`divModInt#`Int#y#of(#Int#d,Int#m#)->(Int# -> Int16I16#(Int# -> Int#narrow16Int#Int#d),Int# -> Int16I16#(Int# -> Int#narrow16Int#Int#m))toInteger :: Int16 -> IntegertoInteger(I16#Int#x#)=Int# -> IntegersmallIntegerInt#x#-- | @since 2.01instanceBoundedInt16whereminBound :: Int16minBound=Int16-0x8000maxBound :: Int16maxBound=Int160x7FFF-- | @since 2.01instanceIxInt16whererange :: (Int16, Int16) -> [Int16]range(Int16m,Int16n)=[Int16m..Int16n]unsafeIndex :: (Int16, Int16) -> Int16 -> IntunsafeIndex(Int16m,Int16_)Int16i=Int16 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt16iInt -> Int -> Intforall a. Num a => a -> a -> a-Int16 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt16minRange :: (Int16, Int16) -> Int16 -> BoolinRange(Int16m,Int16n)Int16i=Int16mInt16 -> Int16 -> Boolforall a. Ord a => a -> a -> Bool<=Int16iBool -> Bool -> Bool&&Int16iInt16 -> Int16 -> Boolforall a. Ord a => a -> a -> Bool<=Int16n-- | @since 2.01instanceReadInt16wherereadsPrec :: Int -> ReadS Int16readsPrecIntpStrings=[(Int -> Int16forall a b. (Integral a, Num b) => a -> bfromIntegral(Intx::Int),Stringr)|(Intx,Stringr)<-Int -> ReadS Intforall a. Read a => Int -> ReadS areadsPrecIntpStrings]-- | @since 2.01instanceBitsInt16where{-# INLINEshift#-}{-# INLINEbit#-}{-# INLINEtestBit#-}{-# INLINEpopCount#-}(I16#Int#x#).&. :: Int16 -> Int16 -> Int16.&.(I16#Int#y#)=Int# -> Int16I16#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`and#`Int# -> Word#int2Word#Int#y#))(I16#Int#x#).|. :: Int16 -> Int16 -> Int16.|.(I16#Int#y#)=Int# -> Int16I16#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`or#`Int# -> Word#int2Word#Int#y#))(I16#Int#x#)xor :: Int16 -> Int16 -> Int16`xor`(I16#Int#y#)=Int# -> Int16I16#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`xor#`Int# -> Word#int2Word#Int#y#))complement :: Int16 -> Int16complement(I16#Int#x#)=Int# -> Int16I16#(Word# -> Int#word2Int#(Word# -> Word#not#(Int# -> Word#int2Word#Int#x#)))(I16#Int#x#)shift :: Int16 -> Int -> Int16`shift`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#`iShiftL#`Int#i#))|Boolotherwise=Int# -> Int16I16#(Int#x#Int# -> Int# -> Int#`iShiftRA#`Int# -> Int#negateInt#Int#i#)(I16#Int#x#)shiftL :: Int16 -> Int -> Int16`shiftL`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#`iShiftL#`Int#i#))|Boolotherwise=Int16forall a. aoverflowError(I16#Int#x#)unsafeShiftL :: Int16 -> Int -> Int16`unsafeShiftL`(I#Int#i#)=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Int#x#Int# -> Int# -> Int#`uncheckedIShiftL#`Int#i#))(I16#Int#x#)shiftR :: Int16 -> Int -> Int16`shiftR`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int16I16#(Int#x#Int# -> Int# -> Int#`iShiftRA#`Int#i#)|Boolotherwise=Int16forall a. aoverflowError(I16#Int#x#)unsafeShiftR :: Int16 -> Int -> Int16`unsafeShiftR`(I#Int#i#)=Int# -> Int16I16#(Int#x#Int# -> Int# -> Int#`uncheckedIShiftRA#`Int#i#)(I16#Int#x#)rotate :: Int16 -> Int -> Int16`rotate`(I#Int#i#)|Int# -> BoolisTrue#(Int#i'#Int# -> Int# -> Int#==#Int#0#)=Int# -> Int16I16#Int#x#|Boolotherwise=Int# -> Int16I16#(Int# -> Int#narrow16Int#(Word# -> Int#word2Int#((Word#x'#Word# -> Int# -> Word#`uncheckedShiftL#`Int#i'#)Word# -> Word# -> Word#`or#`(Word#x'#Word# -> Int# -> Word#`uncheckedShiftRL#`(Int#16#Int# -> Int# -> Int#-#Int#i'#)))))where!x'# :: Word#x'#=Word# -> Word#narrow16Word#(Int# -> Word#int2Word#Int#x#)!i'# :: Int#i'#=Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#i#Word# -> Word# -> Word#`and#`Word#15##)bitSizeMaybe :: Int16 -> Maybe IntbitSizeMaybeInt16i=Int -> Maybe Intforall a. a -> Maybe aJust(Int16 -> Intforall b. FiniteBits b => b -> IntfiniteBitSizeInt16i)bitSize :: Int16 -> IntbitSizeInt16i=Int16 -> Intforall b. FiniteBits b => b -> IntfiniteBitSizeInt16iisSigned :: Int16 -> BoolisSignedInt16_=BoolTruepopCount :: Int16 -> IntpopCount(I16#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#popCnt16#(Int# -> Word#int2Word#Int#x#)))bit :: Int -> Int16bit=Int -> Int16forall a. (Bits a, Num a) => Int -> abitDefaulttestBit :: Int16 -> Int -> BooltestBit=Int16 -> Int -> Boolforall a. (Bits a, Num a) => a -> Int -> BooltestBitDefault-- | @since 4.6.0.0instanceFiniteBitsInt16where{-# INLINEcountLeadingZeros#-}{-# INLINEcountTrailingZeros#-}finiteBitSize :: Int16 -> IntfiniteBitSizeInt16_=Int16countLeadingZeros :: Int16 -> IntcountLeadingZeros(I16#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#clz16#(Int# -> Word#int2Word#Int#x#)))countTrailingZeros :: Int16 -> IntcountTrailingZeros(I16#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#ctz16#(Int# -> Word#int2Word#Int#x#))){-# RULES"fromIntegral/Word8->Int16"fromIntegral=\(W8#x#)->I16#(word2Int#x#)"fromIntegral/Int8->Int16"fromIntegral=\(I8#x#)->I16#x#"fromIntegral/Int16->Int16"fromIntegral=id::Int16->Int16"fromIntegral/a->Int16"fromIntegral=\x->casefromIntegralxofI#x#->I16#(narrow16Int#x#)"fromIntegral/Int16->a"fromIntegral=\(I16#x#)->fromIntegral(I#x#)#-}{-# RULES"properFraction/Float->(Int16,Float)"properFraction=\x->caseproperFractionxof{(n,y)->((fromIntegral::Int->Int16)n,y::Float)}"truncate/Float->Int16"truncate=(fromIntegral::Int->Int16).(truncate::Float->Int)"floor/Float->Int16"floor=(fromIntegral::Int->Int16).(floor::Float->Int)"ceiling/Float->Int16"ceiling=(fromIntegral::Int->Int16).(ceiling::Float->Int)"round/Float->Int16"round=(fromIntegral::Int->Int16).(round::Float->Int)#-}{-# RULES"properFraction/Double->(Int16,Double)"properFraction=\x->caseproperFractionxof{(n,y)->((fromIntegral::Int->Int16)n,y::Double)}"truncate/Double->Int16"truncate=(fromIntegral::Int->Int16).(truncate::Double->Int)"floor/Double->Int16"floor=(fromIntegral::Int->Int16).(floor::Double->Int)"ceiling/Double->Int16"ceiling=(fromIntegral::Int->Int16).(ceiling::Double->Int)"round/Double->Int16"round=(fromIntegral::Int->Int16).(round::Double->Int)#-}-------------------------------------------------------------------------- type Int32-------------------------------------------------------------------------- Int32 is represented in the same way as Int.#if WORD_SIZE_IN_BITS > 32-- Operations may assume and must ensure that it holds only values-- from its logical range.#endifdata{-# CTYPE"HsInt32"#-}Int32=I32#Int#-- ^ 32-bit signed integer type-- See GHC.Classes#matching_overloaded_methods_in_rules-- | @since 2.01instanceEqInt32where== :: Int32 -> Int32 -> Bool(==)=Int32 -> Int32 -> BooleqInt32/= :: Int32 -> Int32 -> Bool(/=)=Int32 -> Int32 -> BoolneInt32eqInt32,neInt32::Int32->Int32->BooleqInt32 :: Int32 -> Int32 -> BooleqInt32(I32#Int#x)(I32#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#==#Int#y)neInt32 :: Int32 -> Int32 -> BoolneInt32(I32#Int#x)(I32#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#/=#Int#y){-# INLINE[1]eqInt32#-}{-# INLINE[1]neInt32#-}-- | @since 2.01instanceOrdInt32where< :: Int32 -> Int32 -> Bool(<)=Int32 -> Int32 -> BoolltInt32<= :: Int32 -> Int32 -> Bool(<=)=Int32 -> Int32 -> BoolleInt32>= :: Int32 -> Int32 -> Bool(>=)=Int32 -> Int32 -> BoolgeInt32> :: Int32 -> Int32 -> Bool(>)=Int32 -> Int32 -> BoolgtInt32{-# INLINE[1]gtInt32#-}{-# INLINE[1]geInt32#-}{-# INLINE[1]ltInt32#-}{-# INLINE[1]leInt32#-}gtInt32,geInt32,ltInt32,leInt32::Int32->Int32->Bool(I32#Int#x)gtInt32 :: Int32 -> Int32 -> Bool`gtInt32`(I32#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#y)(I32#Int#x)geInt32 :: Int32 -> Int32 -> Bool`geInt32`(I32#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>=#Int#y)(I32#Int#x)ltInt32 :: Int32 -> Int32 -> Bool`ltInt32`(I32#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<#Int#y)(I32#Int#x)leInt32 :: Int32 -> Int32 -> Bool`leInt32`(I32#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<=#Int#y)-- | @since 2.01instanceShowInt32whereshowsPrec :: Int -> Int32 -> ShowSshowsPrecIntpInt32x=Int -> Int -> ShowSforall a. Show a => Int -> a -> ShowSshowsPrecIntp(Int32 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt32x::Int)-- | @since 2.01instanceNumInt32where(I32#Int#x#)+ :: Int32 -> Int32 -> Int32+(I32#Int#y#)=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#+#Int#y#))(I32#Int#x#)- :: Int32 -> Int32 -> Int32-(I32#Int#y#)=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#-#Int#y#))(I32#Int#x#)* :: Int32 -> Int32 -> Int32*(I32#Int#y#)=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#*#Int#y#))negate :: Int32 -> Int32negate(I32#Int#x#)=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int# -> Int#negateInt#Int#x#))abs :: Int32 -> Int32absInt32x|Int32xInt32 -> Int32 -> Boolforall a. Ord a => a -> a -> Bool>=Int320=Int32x|Boolotherwise=Int32 -> Int32forall a. Num a => a -> anegateInt32xsignum :: Int32 -> Int32signumInt32x|Int32xInt32 -> Int32 -> Boolforall a. Ord a => a -> a -> Bool>Int320=Int321signumInt320=Int320signumInt32_=Int32-1fromInteger :: Integer -> Int32fromIntegerIntegeri=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Integer -> Int#integerToIntIntegeri))-- | @since 2.01instanceEnumInt32wheresucc :: Int32 -> Int32succInt32x|Int32xInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool/=Int32forall a. Bounded a => amaxBound=Int32xInt32 -> Int32 -> Int32forall a. Num a => a -> a -> a+Int321|Boolotherwise=String -> Int32forall a. String -> asuccErrorString"Int32"pred :: Int32 -> Int32predInt32x|Int32xInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool/=Int32forall a. Bounded a => aminBound=Int32xInt32 -> Int32 -> Int32forall a. Num a => a -> a -> a-Int321|Boolotherwise=String -> Int32forall a. String -> apredErrorString"Int32"#if WORD_SIZE_IN_BITS == 32toEnum(I#i#)=I32#i##elsetoEnum :: Int -> Int32toEnumi :: Inti@(I#Int#i#)|IntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Int32 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegral(Int32forall a. Bounded a => aminBound::Int32)Bool -> Bool -> Bool&&IntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int32 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegral(Int32forall a. Bounded a => amaxBound::Int32)=Int# -> Int32I32#Int#i#|Boolotherwise=String -> Int -> (Int32, Int32) -> Int32forall a b. Show a => String -> Int -> (a, a) -> btoEnumErrorString"Int32"Inti(Int32forall a. Bounded a => aminBound::Int32,Int32forall a. Bounded a => amaxBound::Int32)#endiffromEnum :: Int32 -> IntfromEnum(I32#Int#x#)=Int# -> IntI#Int#x#enumFrom :: Int32 -> [Int32]enumFrom=Int32 -> [Int32]forall a. (Enum a, Bounded a) => a -> [a]boundedEnumFromenumFromThen :: Int32 -> Int32 -> [Int32]enumFromThen=Int32 -> Int32 -> [Int32]forall a. (Enum a, Bounded a) => a -> a -> [a]boundedEnumFromThen-- | @since 2.01instanceIntegralInt32wherequot :: Int32 -> Int32 -> Int32quotx :: Int32x@(I32#Int#x#)y :: Int32y@(I32#Int#y#)|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int320=Int32forall a. adivZeroError|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==(Int32-1)Bool -> Bool -> Bool&&Int32xInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int32forall a. Bounded a => aminBound=Int32forall a. aoverflowError-- Note [Order of tests]|Boolotherwise=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#`quotInt#`Int#y#))rem :: Int32 -> Int32 -> Int32rem(I32#Int#x#)y :: Int32y@(I32#Int#y#)|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int320=Int32forall a. adivZeroError-- The quotRem CPU instruction fails for minBound `quotRem` -1,-- but minBound `rem` -1 is well-defined (0). We therefore-- special-case it.|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==(Int32-1)=Int320|Boolotherwise=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#`remInt#`Int#y#))div :: Int32 -> Int32 -> Int32divx :: Int32x@(I32#Int#x#)y :: Int32y@(I32#Int#y#)|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int320=Int32forall a. adivZeroError|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==(Int32-1)Bool -> Bool -> Bool&&Int32xInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int32forall a. Bounded a => aminBound=Int32forall a. aoverflowError-- Note [Order of tests]|Boolotherwise=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#`divInt#`Int#y#))mod :: Int32 -> Int32 -> Int32mod(I32#Int#x#)y :: Int32y@(I32#Int#y#)|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int320=Int32forall a. adivZeroError-- The divMod CPU instruction fails for minBound `divMod` -1,-- but minBound `mod` -1 is well-defined (0). We therefore-- special-case it.|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==(Int32-1)=Int320|Boolotherwise=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#`modInt#`Int#y#))quotRem :: Int32 -> Int32 -> (Int32, Int32)quotRemx :: Int32x@(I32#Int#x#)y :: Int32y@(I32#Int#y#)|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int320=(Int32, Int32)forall a. adivZeroError-- Note [Order of tests]|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==(Int32-1)Bool -> Bool -> Bool&&Int32xInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int32forall a. Bounded a => aminBound=(Int32forall a. aoverflowError,Int320)|Boolotherwise=caseInt#x#Int# -> Int# -> (# Int#, Int# #)`quotRemInt#`Int#y#of(#Int#q,Int#r#)->(Int# -> Int32I32#(Int# -> Int#narrow32Int#Int#q),Int# -> Int32I32#(Int# -> Int#narrow32Int#Int#r))divMod :: Int32 -> Int32 -> (Int32, Int32)divModx :: Int32x@(I32#Int#x#)y :: Int32y@(I32#Int#y#)|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int320=(Int32, Int32)forall a. adivZeroError-- Note [Order of tests]|Int32yInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==(Int32-1)Bool -> Bool -> Bool&&Int32xInt32 -> Int32 -> Boolforall a. Eq a => a -> a -> Bool==Int32forall a. Bounded a => aminBound=(Int32forall a. aoverflowError,Int320)|Boolotherwise=caseInt#x#Int# -> Int# -> (# Int#, Int# #)`divModInt#`Int#y#of(#Int#d,Int#m#)->(Int# -> Int32I32#(Int# -> Int#narrow32Int#Int#d),Int# -> Int32I32#(Int# -> Int#narrow32Int#Int#m))toInteger :: Int32 -> IntegertoInteger(I32#Int#x#)=Int# -> IntegersmallIntegerInt#x#-- | @since 2.01instanceReadInt32wherereadsPrec :: Int -> ReadS Int32readsPrecIntpStrings=[(Int -> Int32forall a b. (Integral a, Num b) => a -> bfromIntegral(Intx::Int),Stringr)|(Intx,Stringr)<-Int -> ReadS Intforall a. Read a => Int -> ReadS areadsPrecIntpStrings]-- | @since 2.01instanceBitsInt32where{-# INLINEshift#-}{-# INLINEbit#-}{-# INLINEtestBit#-}{-# INLINEpopCount#-}(I32#Int#x#).&. :: Int32 -> Int32 -> Int32.&.(I32#Int#y#)=Int# -> Int32I32#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`and#`Int# -> Word#int2Word#Int#y#))(I32#Int#x#).|. :: Int32 -> Int32 -> Int32.|.(I32#Int#y#)=Int# -> Int32I32#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`or#`Int# -> Word#int2Word#Int#y#))(I32#Int#x#)xor :: Int32 -> Int32 -> Int32`xor`(I32#Int#y#)=Int# -> Int32I32#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`xor#`Int# -> Word#int2Word#Int#y#))complement :: Int32 -> Int32complement(I32#Int#x#)=Int# -> Int32I32#(Word# -> Int#word2Int#(Word# -> Word#not#(Int# -> Word#int2Word#Int#x#)))(I32#Int#x#)shift :: Int32 -> Int -> Int32`shift`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#`iShiftL#`Int#i#))|Boolotherwise=Int# -> Int32I32#(Int#x#Int# -> Int# -> Int#`iShiftRA#`Int# -> Int#negateInt#Int#i#)(I32#Int#x#)shiftL :: Int32 -> Int -> Int32`shiftL`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#`iShiftL#`Int#i#))|Boolotherwise=Int32forall a. aoverflowError(I32#Int#x#)unsafeShiftL :: Int32 -> Int -> Int32`unsafeShiftL`(I#Int#i#)=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Int#x#Int# -> Int# -> Int#`uncheckedIShiftL#`Int#i#))(I32#Int#x#)shiftR :: Int32 -> Int -> Int32`shiftR`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int32I32#(Int#x#Int# -> Int# -> Int#`iShiftRA#`Int#i#)|Boolotherwise=Int32forall a. aoverflowError(I32#Int#x#)unsafeShiftR :: Int32 -> Int -> Int32`unsafeShiftR`(I#Int#i#)=Int# -> Int32I32#(Int#x#Int# -> Int# -> Int#`uncheckedIShiftRA#`Int#i#)(I32#Int#x#)rotate :: Int32 -> Int -> Int32`rotate`(I#Int#i#)|Int# -> BoolisTrue#(Int#i'#Int# -> Int# -> Int#==#Int#0#)=Int# -> Int32I32#Int#x#|Boolotherwise=Int# -> Int32I32#(Int# -> Int#narrow32Int#(Word# -> Int#word2Int#((Word#x'#Word# -> Int# -> Word#`uncheckedShiftL#`Int#i'#)Word# -> Word# -> Word#`or#`(Word#x'#Word# -> Int# -> Word#`uncheckedShiftRL#`(Int#32#Int# -> Int# -> Int#-#Int#i'#)))))where!x'# :: Word#x'#=Word# -> Word#narrow32Word#(Int# -> Word#int2Word#Int#x#)!i'# :: Int#i'#=Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#i#Word# -> Word# -> Word#`and#`Word#31##)bitSizeMaybe :: Int32 -> Maybe IntbitSizeMaybeInt32i=Int -> Maybe Intforall a. a -> Maybe aJust(Int32 -> Intforall b. FiniteBits b => b -> IntfiniteBitSizeInt32i)bitSize :: Int32 -> IntbitSizeInt32i=Int32 -> Intforall b. FiniteBits b => b -> IntfiniteBitSizeInt32iisSigned :: Int32 -> BoolisSignedInt32_=BoolTruepopCount :: Int32 -> IntpopCount(I32#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#popCnt32#(Int# -> Word#int2Word#Int#x#)))bit :: Int -> Int32bit=Int -> Int32forall a. (Bits a, Num a) => Int -> abitDefaulttestBit :: Int32 -> Int -> BooltestBit=Int32 -> Int -> Boolforall a. (Bits a, Num a) => a -> Int -> BooltestBitDefault-- | @since 4.6.0.0instanceFiniteBitsInt32where{-# INLINEcountLeadingZeros#-}{-# INLINEcountTrailingZeros#-}finiteBitSize :: Int32 -> IntfiniteBitSizeInt32_=Int32countLeadingZeros :: Int32 -> IntcountLeadingZeros(I32#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#clz32#(Int# -> Word#int2Word#Int#x#)))countTrailingZeros :: Int32 -> IntcountTrailingZeros(I32#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#ctz32#(Int# -> Word#int2Word#Int#x#))){-# RULES"fromIntegral/Word8->Int32"fromIntegral=\(W8#x#)->I32#(word2Int#x#)"fromIntegral/Word16->Int32"fromIntegral=\(W16#x#)->I32#(word2Int#x#)"fromIntegral/Int8->Int32"fromIntegral=\(I8#x#)->I32#x#"fromIntegral/Int16->Int32"fromIntegral=\(I16#x#)->I32#x#"fromIntegral/Int32->Int32"fromIntegral=id::Int32->Int32"fromIntegral/a->Int32"fromIntegral=\x->casefromIntegralxofI#x#->I32#(narrow32Int#x#)"fromIntegral/Int32->a"fromIntegral=\(I32#x#)->fromIntegral(I#x#)#-}{-# RULES"properFraction/Float->(Int32,Float)"properFraction=\x->caseproperFractionxof{(n,y)->((fromIntegral::Int->Int32)n,y::Float)}"truncate/Float->Int32"truncate=(fromIntegral::Int->Int32).(truncate::Float->Int)"floor/Float->Int32"floor=(fromIntegral::Int->Int32).(floor::Float->Int)"ceiling/Float->Int32"ceiling=(fromIntegral::Int->Int32).(ceiling::Float->Int)"round/Float->Int32"round=(fromIntegral::Int->Int32).(round::Float->Int)#-}{-# RULES"properFraction/Double->(Int32,Double)"properFraction=\x->caseproperFractionxof{(n,y)->((fromIntegral::Int->Int32)n,y::Double)}"truncate/Double->Int32"truncate=(fromIntegral::Int->Int32).(truncate::Double->Int)"floor/Double->Int32"floor=(fromIntegral::Int->Int32).(floor::Double->Int)"ceiling/Double->Int32"ceiling=(fromIntegral::Int->Int32).(ceiling::Double->Int)"round/Double->Int32"round=(fromIntegral::Int->Int32).(round::Double->Int)#-}-- | @since 2.01instanceRealInt32wheretoRational :: Int32 -> RationaltoRationalInt32x=Int32 -> Integerforall a. Integral a => a -> IntegertoIntegerInt32xInteger -> Integer -> Rationalforall a. Integral a => a -> a -> Ratio a%Integer1-- | @since 2.01instanceBoundedInt32whereminBound :: Int32minBound=Int32-0x80000000maxBound :: Int32maxBound=Int320x7FFFFFFF-- | @since 2.01instanceIxInt32whererange :: (Int32, Int32) -> [Int32]range(Int32m,Int32n)=[Int32m..Int32n]unsafeIndex :: (Int32, Int32) -> Int32 -> IntunsafeIndex(Int32m,Int32_)Int32i=Int32 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt32iInt -> Int -> Intforall a. Num a => a -> a -> a-Int32 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt32minRange :: (Int32, Int32) -> Int32 -> BoolinRange(Int32m,Int32n)Int32i=Int32mInt32 -> Int32 -> Boolforall a. Ord a => a -> a -> Bool<=Int32iBool -> Bool -> Bool&&Int32iInt32 -> Int32 -> Boolforall a. Ord a => a -> a -> Bool<=Int32n-------------------------------------------------------------------------- type Int64------------------------------------------------------------------------#if WORD_SIZE_IN_BITS < 64data{-# CTYPE"HsInt64"#-}Int64=I64#Int64#-- ^ 64-bit signed integer type-- See GHC.Classes#matching_overloaded_methods_in_rules-- | @since 2.01instanceEqInt64where(==)=eqInt64(/=)=neInt64eqInt64,neInt64::Int64->Int64->BooleqInt64(I64#x)(I64#y)=isTrue#(x`eqInt64#`y)neInt64(I64#x)(I64#y)=isTrue#(x`neInt64#`y){-# INLINE[1]eqInt64#-}{-# INLINE[1]neInt64#-}-- | @since 2.01instanceOrdInt64where(<)=ltInt64(<=)=leInt64(>=)=geInt64(>)=gtInt64{-# INLINE[1]gtInt64#-}{-# INLINE[1]geInt64#-}{-# INLINE[1]ltInt64#-}{-# INLINE[1]leInt64#-}gtInt64,geInt64,ltInt64,leInt64::Int64->Int64->Bool(I64#x)`gtInt64`(I64#y)=isTrue#(x`gtInt64#`y)(I64#x)`geInt64`(I64#y)=isTrue#(x`geInt64#`y)(I64#x)`ltInt64`(I64#y)=isTrue#(x`ltInt64#`y)(I64#x)`leInt64`(I64#y)=isTrue#(x`leInt64#`y)-- | @since 2.01instanceShowInt64whereshowsPrecpx=showsPrecp(toIntegerx)-- | @since 2.01instanceNumInt64where(I64#x#)+(I64#y#)=I64#(x#`plusInt64#`y#)(I64#x#)-(I64#y#)=I64#(x#`minusInt64#`y#)(I64#x#)*(I64#y#)=I64#(x#`timesInt64#`y#)negate(I64#x#)=I64#(negateInt64#x#)absx|x>=0=x|otherwise=negatexsignumx|x>0=1signum0=0signum_=-1fromIntegeri=I64#(integerToInt64i)-- | @since 2.01instanceEnumInt64wheresuccx|x/=maxBound=x+1|otherwise=succError"Int64"predx|x/=minBound=x-1|otherwise=predError"Int64"toEnum(I#i#)=I64#(intToInt64#i#)fromEnumx@(I64#x#)|x>=fromIntegral(minBound::Int)&&x<=fromIntegral(maxBound::Int)=I#(int64ToInt#x#)|otherwise=fromEnumError"Int64"xenumFrom=integralEnumFromenumFromThen=integralEnumFromThenenumFromTo=integralEnumFromToenumFromThenTo=integralEnumFromThenTo-- | @since 2.01instanceIntegralInt64wherequotx@(I64#x#)y@(I64#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I64#(x#`quotInt64#`y#)rem(I64#x#)y@(I64#y#)|y==0=divZeroError-- The quotRem CPU instruction fails for minBound `quotRem` -1,-- but minBound `rem` -1 is well-defined (0). We therefore-- special-case it.|y==(-1)=0|otherwise=I64#(x#`remInt64#`y#)divx@(I64#x#)y@(I64#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I64#(x#`divInt64#`y#)mod(I64#x#)y@(I64#y#)|y==0=divZeroError-- The divMod CPU instruction fails for minBound `divMod` -1,-- but minBound `mod` -1 is well-defined (0). We therefore-- special-case it.|y==(-1)=0|otherwise=I64#(x#`modInt64#`y#)quotRemx@(I64#x#)y@(I64#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=(I64#(x#`quotInt64#`y#),I64#(x#`remInt64#`y#))divModx@(I64#x#)y@(I64#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=(I64#(x#`divInt64#`y#),I64#(x#`modInt64#`y#))toInteger(I64#x)=int64ToIntegerxdivInt64#,modInt64#::Int64#->Int64#->Int64#-- Define div in terms of quot, being careful to avoid overflow (#7233)x#`divInt64#`y#|isTrue#(x#`gtInt64#`zero)&&isTrue#(y#`ltInt64#`zero)=((x#`minusInt64#`one)`quotInt64#`y#)`minusInt64#`one|isTrue#(x#`ltInt64#`zero)&&isTrue#(y#`gtInt64#`zero)=((x#`plusInt64#`one)`quotInt64#`y#)`minusInt64#`one|otherwise=x#`quotInt64#`y#where!zero=intToInt64#0#!one=intToInt64#1#x#`modInt64#`y#|isTrue#(x#`gtInt64#`zero)&&isTrue#(y#`ltInt64#`zero)||isTrue#(x#`ltInt64#`zero)&&isTrue#(y#`gtInt64#`zero)=ifisTrue#(r#`neInt64#`zero)thenr#`plusInt64#`y#elsezero|otherwise=r#where!zero=intToInt64#0#!r#=x#`remInt64#`y#-- | @since 2.01instanceReadInt64wherereadsPrecps=[(fromIntegerx,r)|(x,r)<-readsPrecps]-- | @since 2.01instanceBitsInt64where{-# INLINEshift#-}{-# INLINEbit#-}{-# INLINEtestBit#-}{-# INLINEpopCount#-}(I64#x#).&.(I64#y#)=I64#(word64ToInt64#(int64ToWord64#x#`and64#`int64ToWord64#y#))(I64#x#).|.(I64#y#)=I64#(word64ToInt64#(int64ToWord64#x#`or64#`int64ToWord64#y#))(I64#x#)`xor`(I64#y#)=I64#(word64ToInt64#(int64ToWord64#x#`xor64#`int64ToWord64#y#))complement(I64#x#)=I64#(word64ToInt64#(not64#(int64ToWord64#x#)))(I64#x#)`shift`(I#i#)|isTrue#(i#>=#0#)=I64#(x#`iShiftL64#`i#)|otherwise=I64#(x#`iShiftRA64#`negateInt#i#)(I64#x#)`shiftL`(I#i#)|isTrue#(i#>=#0#)=I64#(x#`iShiftL64#`i#)|otherwise=overflowError(I64#x#)`unsafeShiftL`(I#i#)=I64#(x#`uncheckedIShiftL64#`i#)(I64#x#)`shiftR`(I#i#)|isTrue#(i#>=#0#)=I64#(x#`iShiftRA64#`i#)|otherwise=overflowError(I64#x#)`unsafeShiftR`(I#i#)=I64#(x#`uncheckedIShiftRA64#`i#)(I64#x#)`rotate`(I#i#)|isTrue#(i'#==#0#)=I64#x#|otherwise=I64#(word64ToInt64#((x'#`uncheckedShiftL64#`i'#)`or64#`(x'#`uncheckedShiftRL64#`(64#-#i'#))))where!x'#=int64ToWord64#x#!i'#=word2Int#(int2Word#i#`and#`63##)bitSizeMaybei=Just(finiteBitSizei)bitSizei=finiteBitSizeiisSigned_=TruepopCount(I64#x#)=I#(word2Int#(popCnt64#(int64ToWord64#x#)))bit=bitDefaulttestBit=testBitDefault-- give the 64-bit shift operations the same treatment as the 32-bit-- ones (see GHC.Base), namely we wrap them in tests to catch the-- cases when we're shifting more than 64 bits to avoid unspecified-- behaviour in the C shift operations.iShiftL64#,iShiftRA64#::Int64#->Int#->Int64#a`iShiftL64#`b|isTrue#(b>=#64#)=intToInt64#0#|otherwise=a`uncheckedIShiftL64#`ba`iShiftRA64#`b|isTrue#(b>=#64#)=ifisTrue#(a`ltInt64#`(intToInt64#0#))thenintToInt64#(-1#)elseintToInt64#0#|otherwise=a`uncheckedIShiftRA64#`b{-# RULES"fromIntegral/Int->Int64"fromIntegral=\(I#x#)->I64#(intToInt64#x#)"fromIntegral/Word->Int64"fromIntegral=\(W#x#)->I64#(word64ToInt64#(wordToWord64#x#))"fromIntegral/Word64->Int64"fromIntegral=\(W64#x#)->I64#(word64ToInt64#x#)"fromIntegral/Int64->Int"fromIntegral=\(I64#x#)->I#(int64ToInt#x#)"fromIntegral/Int64->Word"fromIntegral=\(I64#x#)->W#(int2Word#(int64ToInt#x#))"fromIntegral/Int64->Word64"fromIntegral=\(I64#x#)->W64#(int64ToWord64#x#)"fromIntegral/Int64->Int64"fromIntegral=id::Int64->Int64#-}-- No RULES for RealFrac methods if Int is smaller than Int64, we can't-- go through Int and whether going through Integer is faster is uncertain.#else-- Int64 is represented in the same way as Int.-- Operations may assume and must ensure that it holds only values-- from its logical range.data{-# CTYPE"HsInt64"#-}Int64=I64#Int#-- ^ 64-bit signed integer type-- See GHC.Classes#matching_overloaded_methods_in_rules-- | @since 2.01instanceEqInt64where== :: Int64 -> Int64 -> Bool(==)=Int64 -> Int64 -> BooleqInt64/= :: Int64 -> Int64 -> Bool(/=)=Int64 -> Int64 -> BoolneInt64eqInt64,neInt64::Int64->Int64->BooleqInt64 :: Int64 -> Int64 -> BooleqInt64(I64#Int#x)(I64#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#==#Int#y)neInt64 :: Int64 -> Int64 -> BoolneInt64(I64#Int#x)(I64#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#/=#Int#y){-# INLINE[1]eqInt64#-}{-# INLINE[1]neInt64#-}-- | @since 2.01instanceOrdInt64where< :: Int64 -> Int64 -> Bool(<)=Int64 -> Int64 -> BoolltInt64<= :: Int64 -> Int64 -> Bool(<=)=Int64 -> Int64 -> BoolleInt64>= :: Int64 -> Int64 -> Bool(>=)=Int64 -> Int64 -> BoolgeInt64> :: Int64 -> Int64 -> Bool(>)=Int64 -> Int64 -> BoolgtInt64{-# INLINE[1]gtInt64#-}{-# INLINE[1]geInt64#-}{-# INLINE[1]ltInt64#-}{-# INLINE[1]leInt64#-}gtInt64,geInt64,ltInt64,leInt64::Int64->Int64->Bool(I64#Int#x)gtInt64 :: Int64 -> Int64 -> Bool`gtInt64`(I64#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>#Int#y)(I64#Int#x)geInt64 :: Int64 -> Int64 -> Bool`geInt64`(I64#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#>=#Int#y)(I64#Int#x)ltInt64 :: Int64 -> Int64 -> Bool`ltInt64`(I64#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<#Int#y)(I64#Int#x)leInt64 :: Int64 -> Int64 -> Bool`leInt64`(I64#Int#y)=Int# -> BoolisTrue#(Int#xInt# -> Int# -> Int#<=#Int#y)-- | @since 2.01instanceShowInt64whereshowsPrec :: Int -> Int64 -> ShowSshowsPrecIntpInt64x=Int -> Int -> ShowSforall a. Show a => Int -> a -> ShowSshowsPrecIntp(Int64 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt64x::Int)-- | @since 2.01instanceNumInt64where(I64#Int#x#)+ :: Int64 -> Int64 -> Int64+(I64#Int#y#)=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#+#Int#y#)(I64#Int#x#)- :: Int64 -> Int64 -> Int64-(I64#Int#y#)=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#-#Int#y#)(I64#Int#x#)* :: Int64 -> Int64 -> Int64*(I64#Int#y#)=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#*#Int#y#)negate :: Int64 -> Int64negate(I64#Int#x#)=Int# -> Int64I64#(Int# -> Int#negateInt#Int#x#)abs :: Int64 -> Int64absInt64x|Int64xInt64 -> Int64 -> Boolforall a. Ord a => a -> a -> Bool>=Int640=Int64x|Boolotherwise=Int64 -> Int64forall a. Num a => a -> anegateInt64xsignum :: Int64 -> Int64signumInt64x|Int64xInt64 -> Int64 -> Boolforall a. Ord a => a -> a -> Bool>Int640=Int641signumInt640=Int640signumInt64_=Int64-1fromInteger :: Integer -> Int64fromIntegerIntegeri=Int# -> Int64I64#(Integer -> Int#integerToIntIntegeri)-- | @since 2.01instanceEnumInt64wheresucc :: Int64 -> Int64succInt64x|Int64xInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool/=Int64forall a. Bounded a => amaxBound=Int64xInt64 -> Int64 -> Int64forall a. Num a => a -> a -> a+Int641|Boolotherwise=String -> Int64forall a. String -> asuccErrorString"Int64"pred :: Int64 -> Int64predInt64x|Int64xInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool/=Int64forall a. Bounded a => aminBound=Int64xInt64 -> Int64 -> Int64forall a. Num a => a -> a -> a-Int641|Boolotherwise=String -> Int64forall a. String -> apredErrorString"Int64"toEnum :: Int -> Int64toEnum(I#Int#i#)=Int# -> Int64I64#Int#i#fromEnum :: Int64 -> IntfromEnum(I64#Int#x#)=Int# -> IntI#Int#x#enumFrom :: Int64 -> [Int64]enumFrom=Int64 -> [Int64]forall a. (Enum a, Bounded a) => a -> [a]boundedEnumFromenumFromThen :: Int64 -> Int64 -> [Int64]enumFromThen=Int64 -> Int64 -> [Int64]forall a. (Enum a, Bounded a) => a -> a -> [a]boundedEnumFromThen-- | @since 2.01instanceIntegralInt64wherequot :: Int64 -> Int64 -> Int64quotx :: Int64x@(I64#Int#x#)y :: Int64y@(I64#Int#y#)|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int640=Int64forall a. adivZeroError|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==(Int64-1)Bool -> Bool -> Bool&&Int64xInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int64forall a. Bounded a => aminBound=Int64forall a. aoverflowError-- Note [Order of tests]|Boolotherwise=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`quotInt#`Int#y#)rem :: Int64 -> Int64 -> Int64rem(I64#Int#x#)y :: Int64y@(I64#Int#y#)|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int640=Int64forall a. adivZeroError-- The quotRem CPU instruction fails for minBound `quotRem` -1,-- but minBound `rem` -1 is well-defined (0). We therefore-- special-case it.|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==(Int64-1)=Int640|Boolotherwise=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`remInt#`Int#y#)div :: Int64 -> Int64 -> Int64divx :: Int64x@(I64#Int#x#)y :: Int64y@(I64#Int#y#)|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int640=Int64forall a. adivZeroError|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==(Int64-1)Bool -> Bool -> Bool&&Int64xInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int64forall a. Bounded a => aminBound=Int64forall a. aoverflowError-- Note [Order of tests]|Boolotherwise=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`divInt#`Int#y#)mod :: Int64 -> Int64 -> Int64mod(I64#Int#x#)y :: Int64y@(I64#Int#y#)|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int640=Int64forall a. adivZeroError-- The divMod CPU instruction fails for minBound `divMod` -1,-- but minBound `mod` -1 is well-defined (0). We therefore-- special-case it.|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==(Int64-1)=Int640|Boolotherwise=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`modInt#`Int#y#)quotRem :: Int64 -> Int64 -> (Int64, Int64)quotRemx :: Int64x@(I64#Int#x#)y :: Int64y@(I64#Int#y#)|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int640=(Int64, Int64)forall a. adivZeroError-- Note [Order of tests]|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==(Int64-1)Bool -> Bool -> Bool&&Int64xInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int64forall a. Bounded a => aminBound=(Int64forall a. aoverflowError,Int640)|Boolotherwise=caseInt#x#Int# -> Int# -> (# Int#, Int# #)`quotRemInt#`Int#y#of(#Int#q,Int#r#)->(Int# -> Int64I64#Int#q,Int# -> Int64I64#Int#r)divMod :: Int64 -> Int64 -> (Int64, Int64)divModx :: Int64x@(I64#Int#x#)y :: Int64y@(I64#Int#y#)|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int640=(Int64, Int64)forall a. adivZeroError-- Note [Order of tests]|Int64yInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==(Int64-1)Bool -> Bool -> Bool&&Int64xInt64 -> Int64 -> Boolforall a. Eq a => a -> a -> Bool==Int64forall a. Bounded a => aminBound=(Int64forall a. aoverflowError,Int640)|Boolotherwise=caseInt#x#Int# -> Int# -> (# Int#, Int# #)`divModInt#`Int#y#of(#Int#d,Int#m#)->(Int# -> Int64I64#Int#d,Int# -> Int64I64#Int#m)toInteger :: Int64 -> IntegertoInteger(I64#Int#x#)=Int# -> IntegersmallIntegerInt#x#-- | @since 2.01instanceReadInt64wherereadsPrec :: Int -> ReadS Int64readsPrecIntpStrings=[(Int -> Int64forall a b. (Integral a, Num b) => a -> bfromIntegral(Intx::Int),Stringr)|(Intx,Stringr)<-Int -> ReadS Intforall a. Read a => Int -> ReadS areadsPrecIntpStrings]-- | @since 2.01instanceBitsInt64where{-# INLINEshift#-}{-# INLINEbit#-}{-# INLINEtestBit#-}{-# INLINEpopCount#-}(I64#Int#x#).&. :: Int64 -> Int64 -> Int64.&.(I64#Int#y#)=Int# -> Int64I64#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`and#`Int# -> Word#int2Word#Int#y#))(I64#Int#x#).|. :: Int64 -> Int64 -> Int64.|.(I64#Int#y#)=Int# -> Int64I64#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`or#`Int# -> Word#int2Word#Int#y#))(I64#Int#x#)xor :: Int64 -> Int64 -> Int64`xor`(I64#Int#y#)=Int# -> Int64I64#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`xor#`Int# -> Word#int2Word#Int#y#))complement :: Int64 -> Int64complement(I64#Int#x#)=Int# -> Int64I64#(Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#x#Word# -> Word# -> Word#`xor#`Int# -> Word#int2Word#(Int#-1#)))(I64#Int#x#)shift :: Int64 -> Int -> Int64`shift`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`iShiftL#`Int#i#)|Boolotherwise=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`iShiftRA#`Int# -> Int#negateInt#Int#i#)(I64#Int#x#)shiftL :: Int64 -> Int -> Int64`shiftL`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`iShiftL#`Int#i#)|Boolotherwise=Int64forall a. aoverflowError(I64#Int#x#)unsafeShiftL :: Int64 -> Int -> Int64`unsafeShiftL`(I#Int#i#)=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`uncheckedIShiftL#`Int#i#)(I64#Int#x#)shiftR :: Int64 -> Int -> Int64`shiftR`(I#Int#i#)|Int# -> BoolisTrue#(Int#i#Int# -> Int# -> Int#>=#Int#0#)=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`iShiftRA#`Int#i#)|Boolotherwise=Int64forall a. aoverflowError(I64#Int#x#)unsafeShiftR :: Int64 -> Int -> Int64`unsafeShiftR`(I#Int#i#)=Int# -> Int64I64#(Int#x#Int# -> Int# -> Int#`uncheckedIShiftRA#`Int#i#)(I64#Int#x#)rotate :: Int64 -> Int -> Int64`rotate`(I#Int#i#)|Int# -> BoolisTrue#(Int#i'#Int# -> Int# -> Int#==#Int#0#)=Int# -> Int64I64#Int#x#|Boolotherwise=Int# -> Int64I64#(Word# -> Int#word2Int#((Word#x'#Word# -> Int# -> Word#`uncheckedShiftL#`Int#i'#)Word# -> Word# -> Word#`or#`(Word#x'#Word# -> Int# -> Word#`uncheckedShiftRL#`(Int#64#Int# -> Int# -> Int#-#Int#i'#))))where!x'# :: Word#x'#=Int# -> Word#int2Word#Int#x#!i'# :: Int#i'#=Word# -> Int#word2Int#(Int# -> Word#int2Word#Int#i#Word# -> Word# -> Word#`and#`Word#63##)bitSizeMaybe :: Int64 -> Maybe IntbitSizeMaybeInt64i=Int -> Maybe Intforall a. a -> Maybe aJust(Int64 -> Intforall b. FiniteBits b => b -> IntfiniteBitSizeInt64i)bitSize :: Int64 -> IntbitSizeInt64i=Int64 -> Intforall b. FiniteBits b => b -> IntfiniteBitSizeInt64iisSigned :: Int64 -> BoolisSignedInt64_=BoolTruepopCount :: Int64 -> IntpopCount(I64#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#popCnt64#(Int# -> Word#int2Word#Int#x#)))bit :: Int -> Int64bit=Int -> Int64forall a. (Bits a, Num a) => Int -> abitDefaulttestBit :: Int64 -> Int -> BooltestBit=Int64 -> Int -> Boolforall a. (Bits a, Num a) => a -> Int -> BooltestBitDefault{-# RULES"fromIntegral/a->Int64"fromIntegral=\x->casefromIntegralxofI#x#->I64#x#"fromIntegral/Int64->a"fromIntegral=\(I64#x#)->fromIntegral(I#x#)#-}{-# RULES"properFraction/Float->(Int64,Float)"properFraction=\x->caseproperFractionxof{(n,y)->((fromIntegral::Int->Int64)n,y::Float)}"truncate/Float->Int64"truncate=(fromIntegral::Int->Int64).(truncate::Float->Int)"floor/Float->Int64"floor=(fromIntegral::Int->Int64).(floor::Float->Int)"ceiling/Float->Int64"ceiling=(fromIntegral::Int->Int64).(ceiling::Float->Int)"round/Float->Int64"round=(fromIntegral::Int->Int64).(round::Float->Int)#-}{-# RULES"properFraction/Double->(Int64,Double)"properFraction=\x->caseproperFractionxof{(n,y)->((fromIntegral::Int->Int64)n,y::Double)}"truncate/Double->Int64"truncate=(fromIntegral::Int->Int64).(truncate::Double->Int)"floor/Double->Int64"floor=(fromIntegral::Int->Int64).(floor::Double->Int)"ceiling/Double->Int64"ceiling=(fromIntegral::Int->Int64).(ceiling::Double->Int)"round/Double->Int64"round=(fromIntegral::Int->Int64).(round::Double->Int)#-}uncheckedIShiftL64#::Int#->Int#->Int#uncheckedIShiftL64# :: Int# -> Int# -> Int#uncheckedIShiftL64#=Int# -> Int# -> Int#uncheckedIShiftL#uncheckedIShiftRA64#::Int#->Int#->Int#uncheckedIShiftRA64# :: Int# -> Int# -> Int#uncheckedIShiftRA64#=Int# -> Int# -> Int#uncheckedIShiftRA##endif-- | @since 4.6.0.0instanceFiniteBitsInt64where{-# INLINEcountLeadingZeros#-}{-# INLINEcountTrailingZeros#-}finiteBitSize :: Int64 -> IntfiniteBitSizeInt64_=Int64#if WORD_SIZE_IN_BITS < 64countLeadingZeros(I64#x#)=I#(word2Int#(clz64#(int64ToWord64#x#)))countTrailingZeros(I64#x#)=I#(word2Int#(ctz64#(int64ToWord64#x#)))#elsecountLeadingZeros :: Int64 -> IntcountLeadingZeros(I64#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#clz64#(Int# -> Word#int2Word#Int#x#)))countTrailingZeros :: Int64 -> IntcountTrailingZeros(I64#Int#x#)=Int# -> IntI#(Word# -> Int#word2Int#(Word# -> Word#ctz64#(Int# -> Word#int2Word#Int#x#)))#endif-- | @since 2.01instanceRealInt64wheretoRational :: Int64 -> RationaltoRationalInt64x=Int64 -> Integerforall a. Integral a => a -> IntegertoIntegerInt64xInteger -> Integer -> Rationalforall a. Integral a => a -> a -> Ratio a%Integer1-- | @since 2.01instanceBoundedInt64whereminBound :: Int64minBound=Int64-0x8000000000000000maxBound :: Int64maxBound=Int640x7FFFFFFFFFFFFFFF-- | @since 2.01instanceIxInt64whererange :: (Int64, Int64) -> [Int64]range(Int64m,Int64n)=[Int64m..Int64n]unsafeIndex :: (Int64, Int64) -> Int64 -> IntunsafeIndex(Int64m,Int64_)Int64i=Int64 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt64iInt -> Int -> Intforall a. Num a => a -> a -> a-Int64 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralInt64minRange :: (Int64, Int64) -> Int64 -> BoolinRange(Int64m,Int64n)Int64i=Int64mInt64 -> Int64 -> Boolforall a. Ord a => a -> a -> Bool<=Int64iBool -> Bool -> Bool&&Int64iInt64 -> Int64 -> Boolforall a. Ord a => a -> a -> Bool<=Int64n-------------------------------------------------------------------------------{-# RULES"fromIntegral/Natural->Int8"fromIntegral=(fromIntegral::Int->Int8).naturalToInt"fromIntegral/Natural->Int16"fromIntegral=(fromIntegral::Int->Int16).naturalToInt"fromIntegral/Natural->Int32"fromIntegral=(fromIntegral::Int->Int32).naturalToInt#-}{-# RULES"fromIntegral/Int8->Natural"fromIntegral=intToNatural.(fromIntegral::Int8->Int)"fromIntegral/Int16->Natural"fromIntegral=intToNatural.(fromIntegral::Int16->Int)"fromIntegral/Int32->Natural"fromIntegral=intToNatural.(fromIntegral::Int32->Int)#-}#if WORD_SIZE_IN_BITS == 64-- these RULES are valid for Word==Word64 & Int==Int64{-# RULES"fromIntegral/Natural->Int64"fromIntegral=(fromIntegral::Int->Int64).naturalToInt"fromIntegral/Int64->Natural"fromIntegral=intToNatural.(fromIntegral::Int64->Int)#-}#endif{- Note [Order of tests]~~~~~~~~~~~~~~~~~~~~~~~~~(See #3065, #5161.) Suppose we had a definition like: quot x y | y == 0 = divZeroError | x == minBound && y == (-1) = overflowError | otherwise = x `primQuot` yNote in particular that the x == minBoundtest comes before the y == (-1)test.this expands to something like: case y of 0 -> divZeroError _ -> case x of -9223372036854775808 -> case y of -1 -> overflowError _ -> x `primQuot` y _ -> x `primQuot` yNow if we have the call (x `quot` 2), and quot gets inlined, then we get: case 2 of 0 -> divZeroError _ -> case x of -9223372036854775808 -> case 2 of -1 -> overflowError _ -> x `primQuot` 2 _ -> x `primQuot` 2which simplifies to: case x of -9223372036854775808 -> x `primQuot` 2 _ -> x `primQuot` 2Now we have a case with two identical branches, which would beeliminated (assuming it doesn't affect strictness, which it doesn't inthis case), leaving the desired: x `primQuot` 2except in the minBound branch we know what x is, and GHC cleverly doesthe division at compile time, giving: case x of -9223372036854775808 -> -4611686018427387904 _ -> x `primQuot` 2So instead we use a definition like: quot x y | y == 0 = divZeroError | y == (-1) && x == minBound = overflowError | otherwise = x `primQuot` ywhich gives us: case y of 0 -> divZeroError -1 -> case x of -9223372036854775808 -> overflowError _ -> x `primQuot` y _ -> x `primQuot` yfor which our call (x `quot` 2) expands to: case 2 of 0 -> divZeroError -1 -> case x of -9223372036854775808 -> overflowError _ -> x `primQuot` 2 _ -> x `primQuot` 2which simplifies to: x `primQuot` 2as required.But we now have the same problem with a constant numerator: the call(2 `quot` y) expands to case y of 0 -> divZeroError -1 -> case 2 of -9223372036854775808 -> overflowError _ -> 2 `primQuot` y _ -> 2 `primQuot` ywhich simplifies to: case y of 0 -> divZeroError -1 -> 2 `primQuot` y _ -> 2 `primQuot` ywhich simplifies to: case y of 0 -> divZeroError -1 -> -2 _ -> 2 `primQuot` yHowever, constant denominators are more common than constant numerators,so the y == (-1) && x == minBoundorder gives us better code in the common case.-}
[8]ページ先頭