Movatterモバイル変換


[0]ホーム

URL:


{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, MagicHash, UnboxedTuples,             StandaloneDeriving, NegativeLiterals #-}{-# OPTIONS_HADDOCK hide #-}------------------------------------------------------------------------------- |-- 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(==)=eqInt8(/=)=neInt8eqInt8,neInt8::Int8->Int8->BooleqInt8(I8#x)(I8#y)=isTrue#(x==#y)neInt8(I8#x)(I8#y)=isTrue#(x/=#y){-# INLINE[1]eqInt8#-}{-# INLINE[1]neInt8#-}-- | @since 2.01instanceOrdInt8where(<)=ltInt8(<=)=leInt8(>=)=geInt8(>)=gtInt8{-# INLINE[1]gtInt8#-}{-# INLINE[1]geInt8#-}{-# INLINE[1]ltInt8#-}{-# INLINE[1]leInt8#-}gtInt8,geInt8,ltInt8,leInt8::Int8->Int8->Bool(I8#x)`gtInt8`(I8#y)=isTrue#(x>#y)(I8#x)`geInt8`(I8#y)=isTrue#(x>=#y)(I8#x)`ltInt8`(I8#y)=isTrue#(x<#y)(I8#x)`leInt8`(I8#y)=isTrue#(x<=#y)-- | @since 2.01instanceShowInt8whereshowsPrecpx=showsPrecp(fromIntegralx::Int)-- | @since 2.01instanceNumInt8where(I8#x#)+(I8#y#)=I8#(narrow8Int#(x#+#y#))(I8#x#)-(I8#y#)=I8#(narrow8Int#(x#-#y#))(I8#x#)*(I8#y#)=I8#(narrow8Int#(x#*#y#))negate(I8#x#)=I8#(narrow8Int#(negateInt#x#))absx|x>=0=x|otherwise=negatexsignumx|x>0=1signum0=0signum_=-1fromIntegeri=I8#(narrow8Int#(integerToInti))-- | @since 2.01instanceRealInt8wheretoRationalx=toIntegerx%1-- | @since 2.01instanceEnumInt8wheresuccx|x/=maxBound=x+1|otherwise=succError"Int8"predx|x/=minBound=x-1|otherwise=predError"Int8"toEnumi@(I#i#)|i>=fromIntegral(minBound::Int8)&&i<=fromIntegral(maxBound::Int8)=I8#i#|otherwise=toEnumError"Int8"i(minBound::Int8,maxBound::Int8)fromEnum(I8#x#)=I#x#enumFrom=boundedEnumFromenumFromThen=boundedEnumFromThen-- | @since 2.01instanceIntegralInt8wherequotx@(I8#x#)y@(I8#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I8#(narrow8Int#(x#`quotInt#`y#))rem(I8#x#)y@(I8#y#)|y==0=divZeroError|otherwise=I8#(narrow8Int#(x#`remInt#`y#))divx@(I8#x#)y@(I8#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I8#(narrow8Int#(x#`divInt#`y#))mod(I8#x#)y@(I8#y#)|y==0=divZeroError|otherwise=I8#(narrow8Int#(x#`modInt#`y#))quotRemx@(I8#x#)y@(I8#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=casex#`quotRemInt#`y#of(#q,r#)->(I8#(narrow8Int#q),I8#(narrow8Int#r))divModx@(I8#x#)y@(I8#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=casex#`divModInt#`y#of(#d,m#)->(I8#(narrow8Int#d),I8#(narrow8Int#m))toInteger(I8#x#)=smallIntegerx#-- | @since 2.01instanceBoundedInt8whereminBound=-0x80maxBound=0x7F-- | @since 2.01instanceIxInt8whererange(m,n)=[m..n]unsafeIndex(m,_)i=fromIntegrali-fromIntegralminRange(m,n)i=m<=i&&i<=n-- | @since 2.01instanceReadInt8wherereadsPrecps=[(fromIntegral(x::Int),r)|(x,r)<-readsPrecps]-- | @since 2.01instanceBitsInt8where{-# INLINEshift#-}{-# INLINEbit#-}{-# INLINEtestBit#-}(I8#x#).&.(I8#y#)=I8#(word2Int#(int2Word#x#`and#`int2Word#y#))(I8#x#).|.(I8#y#)=I8#(word2Int#(int2Word#x#`or#`int2Word#y#))(I8#x#)`xor`(I8#y#)=I8#(word2Int#(int2Word#x#`xor#`int2Word#y#))complement(I8#x#)=I8#(word2Int#(not#(int2Word#x#)))(I8#x#)`shift`(I#i#)|isTrue#(i#>=#0#)=I8#(narrow8Int#(x#`iShiftL#`i#))|otherwise=I8#(x#`iShiftRA#`negateInt#i#)(I8#x#)`shiftL`(I#i#)=I8#(narrow8Int#(x#`iShiftL#`i#))(I8#x#)`unsafeShiftL`(I#i#)=I8#(narrow8Int#(x#`uncheckedIShiftL#`i#))(I8#x#)`shiftR`(I#i#)=I8#(x#`iShiftRA#`i#)(I8#x#)`unsafeShiftR`(I#i#)=I8#(x#`uncheckedIShiftRA#`i#)(I8#x#)`rotate`(I#i#)|isTrue#(i'#==#0#)=I8#x#|otherwise=I8#(narrow8Int#(word2Int#((x'#`uncheckedShiftL#`i'#)`or#`(x'#`uncheckedShiftRL#`(8#-#i'#)))))where!x'#=narrow8Word#(int2Word#x#)!i'#=word2Int#(int2Word#i#`and#`7##)bitSizeMaybei=Just(finiteBitSizei)bitSizei=finiteBitSizeiisSigned_=TruepopCount(I8#x#)=I#(word2Int#(popCnt8#(int2Word#x#)))bit=bitDefaulttestBit=testBitDefault-- | @since 4.6.0.0instanceFiniteBitsInt8wherefiniteBitSize_=8countLeadingZeros(I8#x#)=I#(word2Int#(clz8#(int2Word#x#)))countTrailingZeros(I8#x#)=I#(word2Int#(ctz8#(int2Word#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(==)=eqInt16(/=)=neInt16eqInt16,neInt16::Int16->Int16->BooleqInt16(I16#x)(I16#y)=isTrue#(x==#y)neInt16(I16#x)(I16#y)=isTrue#(x/=#y){-# INLINE[1]eqInt16#-}{-# INLINE[1]neInt16#-}-- | @since 2.01instanceOrdInt16where(<)=ltInt16(<=)=leInt16(>=)=geInt16(>)=gtInt16{-# INLINE[1]gtInt16#-}{-# INLINE[1]geInt16#-}{-# INLINE[1]ltInt16#-}{-# INLINE[1]leInt16#-}gtInt16,geInt16,ltInt16,leInt16::Int16->Int16->Bool(I16#x)`gtInt16`(I16#y)=isTrue#(x>#y)(I16#x)`geInt16`(I16#y)=isTrue#(x>=#y)(I16#x)`ltInt16`(I16#y)=isTrue#(x<#y)(I16#x)`leInt16`(I16#y)=isTrue#(x<=#y)-- | @since 2.01instanceShowInt16whereshowsPrecpx=showsPrecp(fromIntegralx::Int)-- | @since 2.01instanceNumInt16where(I16#x#)+(I16#y#)=I16#(narrow16Int#(x#+#y#))(I16#x#)-(I16#y#)=I16#(narrow16Int#(x#-#y#))(I16#x#)*(I16#y#)=I16#(narrow16Int#(x#*#y#))negate(I16#x#)=I16#(narrow16Int#(negateInt#x#))absx|x>=0=x|otherwise=negatexsignumx|x>0=1signum0=0signum_=-1fromIntegeri=I16#(narrow16Int#(integerToInti))-- | @since 2.01instanceRealInt16wheretoRationalx=toIntegerx%1-- | @since 2.01instanceEnumInt16wheresuccx|x/=maxBound=x+1|otherwise=succError"Int16"predx|x/=minBound=x-1|otherwise=predError"Int16"toEnumi@(I#i#)|i>=fromIntegral(minBound::Int16)&&i<=fromIntegral(maxBound::Int16)=I16#i#|otherwise=toEnumError"Int16"i(minBound::Int16,maxBound::Int16)fromEnum(I16#x#)=I#x#enumFrom=boundedEnumFromenumFromThen=boundedEnumFromThen-- | @since 2.01instanceIntegralInt16wherequotx@(I16#x#)y@(I16#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I16#(narrow16Int#(x#`quotInt#`y#))rem(I16#x#)y@(I16#y#)|y==0=divZeroError|otherwise=I16#(narrow16Int#(x#`remInt#`y#))divx@(I16#x#)y@(I16#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I16#(narrow16Int#(x#`divInt#`y#))mod(I16#x#)y@(I16#y#)|y==0=divZeroError|otherwise=I16#(narrow16Int#(x#`modInt#`y#))quotRemx@(I16#x#)y@(I16#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=casex#`quotRemInt#`y#of(#q,r#)->(I16#(narrow16Int#q),I16#(narrow16Int#r))divModx@(I16#x#)y@(I16#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=casex#`divModInt#`y#of(#d,m#)->(I16#(narrow16Int#d),I16#(narrow16Int#m))toInteger(I16#x#)=smallIntegerx#-- | @since 2.01instanceBoundedInt16whereminBound=-0x8000maxBound=0x7FFF-- | @since 2.01instanceIxInt16whererange(m,n)=[m..n]unsafeIndex(m,_)i=fromIntegrali-fromIntegralminRange(m,n)i=m<=i&&i<=n-- | @since 2.01instanceReadInt16wherereadsPrecps=[(fromIntegral(x::Int),r)|(x,r)<-readsPrecps]-- | @since 2.01instanceBitsInt16where{-# INLINEshift#-}{-# INLINEbit#-}{-# INLINEtestBit#-}(I16#x#).&.(I16#y#)=I16#(word2Int#(int2Word#x#`and#`int2Word#y#))(I16#x#).|.(I16#y#)=I16#(word2Int#(int2Word#x#`or#`int2Word#y#))(I16#x#)`xor`(I16#y#)=I16#(word2Int#(int2Word#x#`xor#`int2Word#y#))complement(I16#x#)=I16#(word2Int#(not#(int2Word#x#)))(I16#x#)`shift`(I#i#)|isTrue#(i#>=#0#)=I16#(narrow16Int#(x#`iShiftL#`i#))|otherwise=I16#(x#`iShiftRA#`negateInt#i#)(I16#x#)`shiftL`(I#i#)=I16#(narrow16Int#(x#`iShiftL#`i#))(I16#x#)`unsafeShiftL`(I#i#)=I16#(narrow16Int#(x#`uncheckedIShiftL#`i#))(I16#x#)`shiftR`(I#i#)=I16#(x#`iShiftRA#`i#)(I16#x#)`unsafeShiftR`(I#i#)=I16#(x#`uncheckedIShiftRA#`i#)(I16#x#)`rotate`(I#i#)|isTrue#(i'#==#0#)=I16#x#|otherwise=I16#(narrow16Int#(word2Int#((x'#`uncheckedShiftL#`i'#)`or#`(x'#`uncheckedShiftRL#`(16#-#i'#)))))where!x'#=narrow16Word#(int2Word#x#)!i'#=word2Int#(int2Word#i#`and#`15##)bitSizeMaybei=Just(finiteBitSizei)bitSizei=finiteBitSizeiisSigned_=TruepopCount(I16#x#)=I#(word2Int#(popCnt16#(int2Word#x#)))bit=bitDefaulttestBit=testBitDefault-- | @since 4.6.0.0instanceFiniteBitsInt16wherefiniteBitSize_=16countLeadingZeros(I16#x#)=I#(word2Int#(clz16#(int2Word#x#)))countTrailingZeros(I16#x#)=I#(word2Int#(ctz16#(int2Word#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(==)=eqInt32(/=)=neInt32eqInt32,neInt32::Int32->Int32->BooleqInt32(I32#x)(I32#y)=isTrue#(x==#y)neInt32(I32#x)(I32#y)=isTrue#(x/=#y){-# INLINE[1]eqInt32#-}{-# INLINE[1]neInt32#-}-- | @since 2.01instanceOrdInt32where(<)=ltInt32(<=)=leInt32(>=)=geInt32(>)=gtInt32{-# INLINE[1]gtInt32#-}{-# INLINE[1]geInt32#-}{-# INLINE[1]ltInt32#-}{-# INLINE[1]leInt32#-}gtInt32,geInt32,ltInt32,leInt32::Int32->Int32->Bool(I32#x)`gtInt32`(I32#y)=isTrue#(x>#y)(I32#x)`geInt32`(I32#y)=isTrue#(x>=#y)(I32#x)`ltInt32`(I32#y)=isTrue#(x<#y)(I32#x)`leInt32`(I32#y)=isTrue#(x<=#y)-- | @since 2.01instanceShowInt32whereshowsPrecpx=showsPrecp(fromIntegralx::Int)-- | @since 2.01instanceNumInt32where(I32#x#)+(I32#y#)=I32#(narrow32Int#(x#+#y#))(I32#x#)-(I32#y#)=I32#(narrow32Int#(x#-#y#))(I32#x#)*(I32#y#)=I32#(narrow32Int#(x#*#y#))negate(I32#x#)=I32#(narrow32Int#(negateInt#x#))absx|x>=0=x|otherwise=negatexsignumx|x>0=1signum0=0signum_=-1fromIntegeri=I32#(narrow32Int#(integerToInti))-- | @since 2.01instanceEnumInt32wheresuccx|x/=maxBound=x+1|otherwise=succError"Int32"predx|x/=minBound=x-1|otherwise=predError"Int32"#if WORD_SIZE_IN_BITS == 32toEnum(I#i#)=I32#i##elsetoEnumi@(I#i#)|i>=fromIntegral(minBound::Int32)&&i<=fromIntegral(maxBound::Int32)=I32#i#|otherwise=toEnumError"Int32"i(minBound::Int32,maxBound::Int32)#endiffromEnum(I32#x#)=I#x#enumFrom=boundedEnumFromenumFromThen=boundedEnumFromThen-- | @since 2.01instanceIntegralInt32wherequotx@(I32#x#)y@(I32#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I32#(narrow32Int#(x#`quotInt#`y#))rem(I32#x#)y@(I32#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=I32#(narrow32Int#(x#`remInt#`y#))divx@(I32#x#)y@(I32#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I32#(narrow32Int#(x#`divInt#`y#))mod(I32#x#)y@(I32#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=I32#(narrow32Int#(x#`modInt#`y#))quotRemx@(I32#x#)y@(I32#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=casex#`quotRemInt#`y#of(#q,r#)->(I32#(narrow32Int#q),I32#(narrow32Int#r))divModx@(I32#x#)y@(I32#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=casex#`divModInt#`y#of(#d,m#)->(I32#(narrow32Int#d),I32#(narrow32Int#m))toInteger(I32#x#)=smallIntegerx#-- | @since 2.01instanceReadInt32wherereadsPrecps=[(fromIntegral(x::Int),r)|(x,r)<-readsPrecps]-- | @since 2.01instanceBitsInt32where{-# INLINEshift#-}{-# INLINEbit#-}{-# INLINEtestBit#-}(I32#x#).&.(I32#y#)=I32#(word2Int#(int2Word#x#`and#`int2Word#y#))(I32#x#).|.(I32#y#)=I32#(word2Int#(int2Word#x#`or#`int2Word#y#))(I32#x#)`xor`(I32#y#)=I32#(word2Int#(int2Word#x#`xor#`int2Word#y#))complement(I32#x#)=I32#(word2Int#(not#(int2Word#x#)))(I32#x#)`shift`(I#i#)|isTrue#(i#>=#0#)=I32#(narrow32Int#(x#`iShiftL#`i#))|otherwise=I32#(x#`iShiftRA#`negateInt#i#)(I32#x#)`shiftL`(I#i#)=I32#(narrow32Int#(x#`iShiftL#`i#))(I32#x#)`unsafeShiftL`(I#i#)=I32#(narrow32Int#(x#`uncheckedIShiftL#`i#))(I32#x#)`shiftR`(I#i#)=I32#(x#`iShiftRA#`i#)(I32#x#)`unsafeShiftR`(I#i#)=I32#(x#`uncheckedIShiftRA#`i#)(I32#x#)`rotate`(I#i#)|isTrue#(i'#==#0#)=I32#x#|otherwise=I32#(narrow32Int#(word2Int#((x'#`uncheckedShiftL#`i'#)`or#`(x'#`uncheckedShiftRL#`(32#-#i'#)))))where!x'#=narrow32Word#(int2Word#x#)!i'#=word2Int#(int2Word#i#`and#`31##)bitSizeMaybei=Just(finiteBitSizei)bitSizei=finiteBitSizeiisSigned_=TruepopCount(I32#x#)=I#(word2Int#(popCnt32#(int2Word#x#)))bit=bitDefaulttestBit=testBitDefault-- | @since 4.6.0.0instanceFiniteBitsInt32wherefiniteBitSize_=32countLeadingZeros(I32#x#)=I#(word2Int#(clz32#(int2Word#x#)))countTrailingZeros(I32#x#)=I#(word2Int#(ctz32#(int2Word#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.01instanceRealInt32wheretoRationalx=toIntegerx%1-- | @since 2.01instanceBoundedInt32whereminBound=-0x80000000maxBound=0x7FFFFFFF-- | @since 2.01instanceIxInt32whererange(m,n)=[m..n]unsafeIndex(m,_)i=fromIntegrali-fromIntegralminRange(m,n)i=m<=i&&i<=n-------------------------------------------------------------------------- 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#-}(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#)=I64#(x#`iShiftL64#`i#)(I64#x#)`unsafeShiftL`(I#i#)=I64#(x#`uncheckedIShiftL64#`i#)(I64#x#)`shiftR`(I#i#)=I64#(x#`iShiftRA64#`i#)(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(==)=eqInt64(/=)=neInt64eqInt64,neInt64::Int64->Int64->BooleqInt64(I64#x)(I64#y)=isTrue#(x==#y)neInt64(I64#x)(I64#y)=isTrue#(x/=#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>#y)(I64#x)`geInt64`(I64#y)=isTrue#(x>=#y)(I64#x)`ltInt64`(I64#y)=isTrue#(x<#y)(I64#x)`leInt64`(I64#y)=isTrue#(x<=#y)-- | @since 2.01instanceShowInt64whereshowsPrecpx=showsPrecp(fromIntegralx::Int)-- | @since 2.01instanceNumInt64where(I64#x#)+(I64#y#)=I64#(x#+#y#)(I64#x#)-(I64#y#)=I64#(x#-#y#)(I64#x#)*(I64#y#)=I64#(x#*#y#)negate(I64#x#)=I64#(negateInt#x#)absx|x>=0=x|otherwise=negatexsignumx|x>0=1signum0=0signum_=-1fromIntegeri=I64#(integerToInti)-- | @since 2.01instanceEnumInt64wheresuccx|x/=maxBound=x+1|otherwise=succError"Int64"predx|x/=minBound=x-1|otherwise=predError"Int64"toEnum(I#i#)=I64#i#fromEnum(I64#x#)=I#x#enumFrom=boundedEnumFromenumFromThen=boundedEnumFromThen-- | @since 2.01instanceIntegralInt64wherequotx@(I64#x#)y@(I64#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I64#(x#`quotInt#`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#`remInt#`y#)divx@(I64#x#)y@(I64#y#)|y==0=divZeroError|y==(-1)&&x==minBound=overflowError-- Note [Order of tests]|otherwise=I64#(x#`divInt#`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#`modInt#`y#)quotRemx@(I64#x#)y@(I64#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=casex#`quotRemInt#`y#of(#q,r#)->(I64#q,I64#r)divModx@(I64#x#)y@(I64#y#)|y==0=divZeroError-- Note [Order of tests]|y==(-1)&&x==minBound=(overflowError,0)|otherwise=casex#`divModInt#`y#of(#d,m#)->(I64#d,I64#m)toInteger(I64#x#)=smallIntegerx#-- | @since 2.01instanceReadInt64wherereadsPrecps=[(fromIntegral(x::Int),r)|(x,r)<-readsPrecps]-- | @since 2.01instanceBitsInt64where{-# INLINEshift#-}{-# INLINEbit#-}{-# INLINEtestBit#-}(I64#x#).&.(I64#y#)=I64#(word2Int#(int2Word#x#`and#`int2Word#y#))(I64#x#).|.(I64#y#)=I64#(word2Int#(int2Word#x#`or#`int2Word#y#))(I64#x#)`xor`(I64#y#)=I64#(word2Int#(int2Word#x#`xor#`int2Word#y#))complement(I64#x#)=I64#(word2Int#(int2Word#x#`xor#`int2Word#(-1#)))(I64#x#)`shift`(I#i#)|isTrue#(i#>=#0#)=I64#(x#`iShiftL#`i#)|otherwise=I64#(x#`iShiftRA#`negateInt#i#)(I64#x#)`shiftL`(I#i#)=I64#(x#`iShiftL#`i#)(I64#x#)`unsafeShiftL`(I#i#)=I64#(x#`uncheckedIShiftL#`i#)(I64#x#)`shiftR`(I#i#)=I64#(x#`iShiftRA#`i#)(I64#x#)`unsafeShiftR`(I#i#)=I64#(x#`uncheckedIShiftRA#`i#)(I64#x#)`rotate`(I#i#)|isTrue#(i'#==#0#)=I64#x#|otherwise=I64#(word2Int#((x'#`uncheckedShiftL#`i'#)`or#`(x'#`uncheckedShiftRL#`(64#-#i'#))))where!x'#=int2Word#x#!i'#=word2Int#(int2Word#i#`and#`63##)bitSizeMaybei=Just(finiteBitSizei)bitSizei=finiteBitSizeiisSigned_=TruepopCount(I64#x#)=I#(word2Int#(popCnt64#(int2Word#x#)))bit=bitDefaulttestBit=testBitDefault{-# 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#=uncheckedIShiftL#uncheckedIShiftRA64#::Int#->Int#->Int#uncheckedIShiftRA64#=uncheckedIShiftRA##endif-- | @since 4.6.0.0instanceFiniteBitsInt64wherefiniteBitSize_=64#if WORD_SIZE_IN_BITS < 64countLeadingZeros(I64#x#)=I#(word2Int#(clz64#(int64ToWord64#x#)))countTrailingZeros(I64#x#)=I#(word2Int#(ctz64#(int64ToWord64#x#)))#elsecountLeadingZeros(I64#x#)=I#(word2Int#(clz64#(int2Word#x#)))countTrailingZeros(I64#x#)=I#(word2Int#(ctz64#(int2Word#x#)))#endif-- | @since 2.01instanceRealInt64wheretoRationalx=toIntegerx%1-- | @since 2.01instanceBoundedInt64whereminBound=-0x8000000000000000maxBound=0x7FFFFFFFFFFFFFFF-- | @since 2.01instanceIxInt64whererange(m,n)=[m..n]unsafeIndex(m,_)i=fromIntegrali-fromIntegralminRange(m,n)i=m<=i&&i<=n-------------------------------------------------------------------------------{-# 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 Trac #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]ページ先頭

©2009-2025 Movatter.jp