(original) (raw)
{-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, MagicHash, UnboxedTuples, StandaloneDeriving, NegativeLiterals #-} {-# OPTIONS_HADDOCK hide #-}
#include "MachDeps.h"
module GHC.Int ( Int(..), Int8(..), Int16(..), Int32(..), Int64(..), uncheckedIShiftL64#, uncheckedIShiftRA64#,
eqInt, neInt, gtInt, geInt, ltInt, leInt,
[eqInt8](GHC.Int.html#eqInt8), [neInt8](GHC.Int.html#neInt8), [gtInt8](GHC.Int.html#gtInt8), [geInt8](GHC.Int.html#geInt8), [ltInt8](GHC.Int.html#ltInt8), [leInt8](GHC.Int.html#leInt8),
[eqInt16](GHC.Int.html#eqInt16), [neInt16](GHC.Int.html#neInt16), [gtInt16](GHC.Int.html#gtInt16), [geInt16](GHC.Int.html#geInt16), [ltInt16](GHC.Int.html#ltInt16), [leInt16](GHC.Int.html#leInt16),
[eqInt32](GHC.Int.html#eqInt32), [neInt32](GHC.Int.html#neInt32), [gtInt32](GHC.Int.html#gtInt32), [geInt32](GHC.Int.html#geInt32), [ltInt32](GHC.Int.html#ltInt32), [leInt32](GHC.Int.html#leInt32),
[eqInt64](GHC.Int.html#eqInt64), [neInt64](GHC.Int.html#neInt64), [gtInt64](GHC.Int.html#gtInt64), [geInt64](GHC.Int.html#geInt64), [ltInt64](GHC.Int.html#ltInt64), [leInt64](GHC.Int.html#leInt64)
) where
import Data.Bits import Data.Maybe
#if WORD_SIZE_IN_BITS < 64 import GHC.IntWord64 #endif
import GHC.Base import GHC.Enum import GHC.Num import GHC.Real import GHC.Read import GHC.Arr import GHC.Word hiding (uncheckedShiftL64#, uncheckedShiftRL64#) import GHC.Show
data {-# CTYPE "HsInt8" #-} Int8 = I8# Int#
instance Eq Int8 where (==) = eqInt8 (/=) = neInt8
eqInt8, neInt8 :: Int8 -> Int8 -> Bool eqInt8 (I8# x) (I8# y) = isTrue# (x ==# y) neInt8 (I8# x) (I8# y) = isTrue# (x /=# y) {-# INLINE [1] eqInt8 #-} {-# INLINE [1] neInt8 #-}
instance Ord Int8 where (<) = 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](GHC.Int.html#gtInt8)
(I8# y) = isTrue# (x ># y)
(I8# x) [geInt8](GHC.Int.html#geInt8)
(I8# y) = isTrue# (x >=# y)
(I8# x) [ltInt8](GHC.Int.html#ltInt8)
(I8# y) = isTrue# (x <# y)
(I8# x) [leInt8](GHC.Int.html#leInt8)
(I8# y) = isTrue# (x <=# y)
instance Show Int8 where showsPrec p x = showsPrec p (fromIntegral x :: Int)
instance Num Int8 where (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#)) abs x | x >= 0 = x | otherwise = negate x signum x | x > 0 = 1 signum 0 = 0 signum _ = -1 fromInteger i = I8# (narrow8Int# (integerToInt i))
instance Real Int8 where toRational x = toInteger x % 1
instance Enum Int8 where succ x | x /= maxBound = x + 1 | otherwise = succError "Int8" pred x | x /= minBound = x - 1 | otherwise = predError "Int8" toEnum i@(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 = boundedEnumFrom enumFromThen = boundedEnumFromThen
instance Integral Int8 where
quot x@(I8# x#) y@(I8# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = overflowError
| otherwise = I8# (narrow8Int# (x# quotInt#
y#))
rem (I8# x#) y@(I8# y#)
| y == 0 = divZeroError
| otherwise = I8# (narrow8Int# (x# remInt#
y#))
div x@(I8# x#) y@(I8# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = overflowError
| otherwise = I8# (narrow8Int# (x# divInt#
y#))
mod (I8# x#) y@(I8# y#)
| y == 0 = divZeroError
| otherwise = I8# (narrow8Int# (x# modInt#
y#))
quotRem x@(I8# x#) y@(I8# y#)
| y == 0 = divZeroError
| [y](#local-6989586621679090102) == (-1) && [x](#local-6989586621679090100) == [minBound](GHC.Enum.html#minBound) = ([overflowError](GHC.Real.html#overflowError), 0)
| [otherwise](GHC.Base.html#otherwise) = case [x#](#local-6989586621679090101) `quotRemInt#` [y#](#local-6989586621679090103) of
(# [q](#local-6989586621679090104), [r](#local-6989586621679090105) #) ->
([I8#](GHC.Int.html#I8%23) (narrow8Int# [q](#local-6989586621679090104)),
[I8#](GHC.Int.html#I8%23) (narrow8Int# [r](#local-6989586621679090105)))
[divMod](GHC.Real.html#divMod) [x](#local-6989586621679090106)@([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090107)) [y](#local-6989586621679090108)@([I8#](GHC.Int.html#I8%23) [y#](#local-6989586621679090109))
| [y](#local-6989586621679090108) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679090108) == (-1) && [x](#local-6989586621679090106) == [minBound](GHC.Enum.html#minBound) = ([overflowError](GHC.Real.html#overflowError), 0)
| [otherwise](GHC.Base.html#otherwise) = case [x#](#local-6989586621679090107) `[divModInt#](GHC.Base.html#divModInt%23)` [y#](#local-6989586621679090109) of
(# [d](#local-6989586621679090110), [m](#local-6989586621679090111) #) ->
([I8#](GHC.Int.html#I8%23) (narrow8Int# [d](#local-6989586621679090110)),
[I8#](GHC.Int.html#I8%23) (narrow8Int# [m](#local-6989586621679090111)))
[toInteger](GHC.Real.html#toInteger) ([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090112)) = smallInteger [x#](#local-6989586621679090112)
instance Bounded Int8 where minBound = -0x80 maxBound = 0x7F
instance Ix Int8 where range (m,n) = [m..n] unsafeIndex (m,_) i = fromIntegral i - fromIntegral m inRange (m,n) i = m <= i && i <= n
instance Read Int8 where readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
instance Bits Int8 where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-}
([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090051)) [.&.](Data.Bits.html#.%26.) ([I8#](GHC.Int.html#I8%23) [y#](#local-6989586621679090052)) = [I8#](GHC.Int.html#I8%23) (word2Int# (int2Word# [x#](#local-6989586621679090051) `and#` int2Word# [y#](#local-6989586621679090052)))
([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090053)) [.|.](Data.Bits.html#.%7C.) ([I8#](GHC.Int.html#I8%23) [y#](#local-6989586621679090054)) = [I8#](GHC.Int.html#I8%23) (word2Int# (int2Word# [x#](#local-6989586621679090053) `or#` int2Word# [y#](#local-6989586621679090054)))
([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090055)) `[xor](Data.Bits.html#xor)` ([I8#](GHC.Int.html#I8%23) [y#](#local-6989586621679090056)) = [I8#](GHC.Int.html#I8%23) (word2Int# (int2Word# [x#](#local-6989586621679090055) `xor#` int2Word# [y#](#local-6989586621679090056)))
[complement](Data.Bits.html#complement) ([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090057)) = [I8#](GHC.Int.html#I8%23) (word2Int# (not# (int2Word# [x#](#local-6989586621679090057))))
([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090058)) `[shift](Data.Bits.html#shift)` (I# [i#](#local-6989586621679090059))
| isTrue# ([i#](#local-6989586621679090059) >=# 0#) = [I8#](GHC.Int.html#I8%23) (narrow8Int# ([x#](#local-6989586621679090058) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679090059)))
| [otherwise](GHC.Base.html#otherwise) = [I8#](GHC.Int.html#I8%23) ([x#](#local-6989586621679090058) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` negateInt# [i#](#local-6989586621679090059))
([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090060)) `[shiftL](Data.Bits.html#shiftL)` (I# [i#](#local-6989586621679090061)) = [I8#](GHC.Int.html#I8%23) (narrow8Int# ([x#](#local-6989586621679090060) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679090061)))
([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090062)) `[unsafeShiftL](Data.Bits.html#unsafeShiftL)` (I# [i#](#local-6989586621679090063)) = [I8#](GHC.Int.html#I8%23) (narrow8Int# ([x#](#local-6989586621679090062) `uncheckedIShiftL#` [i#](#local-6989586621679090063)))
([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090064)) `[shiftR](Data.Bits.html#shiftR)` (I# [i#](#local-6989586621679090065)) = [I8#](GHC.Int.html#I8%23) ([x#](#local-6989586621679090064) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` [i#](#local-6989586621679090065))
([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090066)) `[unsafeShiftR](Data.Bits.html#unsafeShiftR)` (I# [i#](#local-6989586621679090067)) = [I8#](GHC.Int.html#I8%23) ([x#](#local-6989586621679090066) `uncheckedIShiftRA#` [i#](#local-6989586621679090067))
([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090068)) `[rotate](Data.Bits.html#rotate)` (I# [i#](#local-6989586621679090069))
| isTrue# ([i'#](#local-6989586621679090071) ==# 0#)
= [I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090068)
| [otherwise](GHC.Base.html#otherwise)
= [I8#](GHC.Int.html#I8%23) (narrow8Int# (word2Int# (([x'#](#local-6989586621679090070) `uncheckedShiftL#` [i'#](#local-6989586621679090071)) `or#`
([x'#](#local-6989586621679090070) `uncheckedShiftRL#` (8# -# [i'#](#local-6989586621679090071))))))
where
![x'#](#local-6989586621679090070) = narrow8Word# (int2Word# [x#](#local-6989586621679090068))
![i'#](#local-6989586621679090071) = word2Int# (int2Word# [i#](#local-6989586621679090069) `and#` 7##)
[bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [i](#local-6989586621679090072) = [Just](GHC.Maybe.html#Just) ([finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679090072))
[bitSize](Data.Bits.html#bitSize) [i](#local-6989586621679090073) = [finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679090073)
[isSigned](Data.Bits.html#isSigned) _ = True
[popCount](Data.Bits.html#popCount) ([I8#](GHC.Int.html#I8%23) [x#](#local-6989586621679090074)) = I# (word2Int# (popCnt8# (int2Word# [x#](#local-6989586621679090074))))
[bit](Data.Bits.html#bit) = [bitDefault](Data.Bits.html#bitDefault)
[testBit](Data.Bits.html#testBit) = [testBitDefault](Data.Bits.html#testBitDefault)
instance FiniteBits Int8 where finiteBitSize _ = 8 countLeadingZeros (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 -> case fromIntegral x of I# x# -> I8# (narrow8Int# x#) "fromIntegral/Int8->a" fromIntegral = (I8# x#) -> fromIntegral (I# x#) #-}
{-# RULES "properFraction/Float->(Int8,Float)" properFraction = \x -> case properFraction x of { (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 -> case properFraction x of { (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) #-}
data {-# CTYPE "HsInt16" #-} Int16 = I16# Int#
instance Eq Int16 where (==) = eqInt16 (/=) = neInt16
eqInt16, neInt16 :: Int16 -> Int16 -> Bool eqInt16 (I16# x) (I16# y) = isTrue# (x ==# y) neInt16 (I16# x) (I16# y) = isTrue# (x /=# y) {-# INLINE [1] eqInt16 #-} {-# INLINE [1] neInt16 #-}
instance Ord Int16 where (<) = 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](GHC.Int.html#gtInt16)
(I16# y) = isTrue# (x ># y)
(I16# x) [geInt16](GHC.Int.html#geInt16)
(I16# y) = isTrue# (x >=# y)
(I16# x) [ltInt16](GHC.Int.html#ltInt16)
(I16# y) = isTrue# (x <# y)
(I16# x) [leInt16](GHC.Int.html#leInt16)
(I16# y) = isTrue# (x <=# y)
instance Show Int16 where showsPrec p x = showsPrec p (fromIntegral x :: Int)
instance Num Int16 where (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#)) abs x | x >= 0 = x | otherwise = negate x signum x | x > 0 = 1 signum 0 = 0 signum _ = -1 fromInteger i = I16# (narrow16Int# (integerToInt i))
instance Real Int16 where toRational x = toInteger x % 1
instance Enum Int16 where succ x | x /= maxBound = x + 1 | otherwise = succError "Int16" pred x | x /= minBound = x - 1 | otherwise = predError "Int16" toEnum i@(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 = boundedEnumFrom enumFromThen = boundedEnumFromThen
instance Integral Int16 where
quot x@(I16# x#) y@(I16# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = overflowError
| otherwise = I16# (narrow16Int# (x# quotInt#
y#))
rem (I16# x#) y@(I16# y#)
| y == 0 = divZeroError
| otherwise = I16# (narrow16Int# (x# remInt#
y#))
div x@(I16# x#) y@(I16# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = overflowError
| otherwise = I16# (narrow16Int# (x# divInt#
y#))
mod (I16# x#) y@(I16# y#)
| y == 0 = divZeroError
| otherwise = I16# (narrow16Int# (x# modInt#
y#))
quotRem x@(I16# x#) y@(I16# y#)
| y == 0 = divZeroError
| [y](#local-6989586621679090020) == (-1) && [x](#local-6989586621679090018) == [minBound](GHC.Enum.html#minBound) = ([overflowError](GHC.Real.html#overflowError), 0)
| [otherwise](GHC.Base.html#otherwise) = case [x#](#local-6989586621679090019) `quotRemInt#` [y#](#local-6989586621679090021) of
(# [q](#local-6989586621679090022), [r](#local-6989586621679090023) #) ->
([I16#](GHC.Int.html#I16%23) (narrow16Int# [q](#local-6989586621679090022)),
[I16#](GHC.Int.html#I16%23) (narrow16Int# [r](#local-6989586621679090023)))
[divMod](GHC.Real.html#divMod) [x](#local-6989586621679090024)@([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679090025)) [y](#local-6989586621679090026)@([I16#](GHC.Int.html#I16%23) [y#](#local-6989586621679090027))
| [y](#local-6989586621679090026) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679090026) == (-1) && [x](#local-6989586621679090024) == [minBound](GHC.Enum.html#minBound) = ([overflowError](GHC.Real.html#overflowError), 0)
| [otherwise](GHC.Base.html#otherwise) = case [x#](#local-6989586621679090025) `[divModInt#](GHC.Base.html#divModInt%23)` [y#](#local-6989586621679090027) of
(# [d](#local-6989586621679090028), [m](#local-6989586621679090029) #) ->
([I16#](GHC.Int.html#I16%23) (narrow16Int# [d](#local-6989586621679090028)),
[I16#](GHC.Int.html#I16%23) (narrow16Int# [m](#local-6989586621679090029)))
[toInteger](GHC.Real.html#toInteger) ([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679090030)) = smallInteger [x#](#local-6989586621679090030)
instance Bounded Int16 where minBound = -0x8000 maxBound = 0x7FFF
instance Ix Int16 where range (m,n) = [m..n] unsafeIndex (m,_) i = fromIntegral i - fromIntegral m inRange (m,n) i = m <= i && i <= n
instance Read Int16 where readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
instance Bits Int16 where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-}
([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089969)) [.&.](Data.Bits.html#.%26.) ([I16#](GHC.Int.html#I16%23) [y#](#local-6989586621679089970)) = [I16#](GHC.Int.html#I16%23) (word2Int# (int2Word# [x#](#local-6989586621679089969) `and#` int2Word# [y#](#local-6989586621679089970)))
([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089971)) [.|.](Data.Bits.html#.%7C.) ([I16#](GHC.Int.html#I16%23) [y#](#local-6989586621679089972)) = [I16#](GHC.Int.html#I16%23) (word2Int# (int2Word# [x#](#local-6989586621679089971) `or#` int2Word# [y#](#local-6989586621679089972)))
([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089973)) `[xor](Data.Bits.html#xor)` ([I16#](GHC.Int.html#I16%23) [y#](#local-6989586621679089974)) = [I16#](GHC.Int.html#I16%23) (word2Int# (int2Word# [x#](#local-6989586621679089973) `xor#` int2Word# [y#](#local-6989586621679089974)))
[complement](Data.Bits.html#complement) ([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089975)) = [I16#](GHC.Int.html#I16%23) (word2Int# (not# (int2Word# [x#](#local-6989586621679089975))))
([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089976)) `[shift](Data.Bits.html#shift)` (I# [i#](#local-6989586621679089977))
| isTrue# ([i#](#local-6989586621679089977) >=# 0#) = [I16#](GHC.Int.html#I16%23) (narrow16Int# ([x#](#local-6989586621679089976) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679089977)))
| [otherwise](GHC.Base.html#otherwise) = [I16#](GHC.Int.html#I16%23) ([x#](#local-6989586621679089976) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` negateInt# [i#](#local-6989586621679089977))
([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089978)) `[shiftL](Data.Bits.html#shiftL)` (I# [i#](#local-6989586621679089979)) = [I16#](GHC.Int.html#I16%23) (narrow16Int# ([x#](#local-6989586621679089978) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679089979)))
([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089980)) `[unsafeShiftL](Data.Bits.html#unsafeShiftL)` (I# [i#](#local-6989586621679089981)) = [I16#](GHC.Int.html#I16%23) (narrow16Int# ([x#](#local-6989586621679089980) `uncheckedIShiftL#` [i#](#local-6989586621679089981)))
([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089982)) `[shiftR](Data.Bits.html#shiftR)` (I# [i#](#local-6989586621679089983)) = [I16#](GHC.Int.html#I16%23) ([x#](#local-6989586621679089982) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` [i#](#local-6989586621679089983))
([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089984)) `[unsafeShiftR](Data.Bits.html#unsafeShiftR)` (I# [i#](#local-6989586621679089985)) = [I16#](GHC.Int.html#I16%23) ([x#](#local-6989586621679089984) `uncheckedIShiftRA#` [i#](#local-6989586621679089985))
([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089986)) `[rotate](Data.Bits.html#rotate)` (I# [i#](#local-6989586621679089987))
| isTrue# ([i'#](#local-6989586621679089989) ==# 0#)
= [I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089986)
| [otherwise](GHC.Base.html#otherwise)
= [I16#](GHC.Int.html#I16%23) (narrow16Int# (word2Int# (([x'#](#local-6989586621679089988) `uncheckedShiftL#` [i'#](#local-6989586621679089989)) `or#`
([x'#](#local-6989586621679089988) `uncheckedShiftRL#` (16# -# [i'#](#local-6989586621679089989))))))
where
![x'#](#local-6989586621679089988) = narrow16Word# (int2Word# [x#](#local-6989586621679089986))
![i'#](#local-6989586621679089989) = word2Int# (int2Word# [i#](#local-6989586621679089987) `and#` 15##)
[bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [i](#local-6989586621679089990) = [Just](GHC.Maybe.html#Just) ([finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679089990))
[bitSize](Data.Bits.html#bitSize) [i](#local-6989586621679089991) = [finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679089991)
[isSigned](Data.Bits.html#isSigned) _ = True
[popCount](Data.Bits.html#popCount) ([I16#](GHC.Int.html#I16%23) [x#](#local-6989586621679089992)) = I# (word2Int# (popCnt16# (int2Word# [x#](#local-6989586621679089992))))
[bit](Data.Bits.html#bit) = [bitDefault](Data.Bits.html#bitDefault)
[testBit](Data.Bits.html#testBit) = [testBitDefault](Data.Bits.html#testBitDefault)
instance FiniteBits Int16 where finiteBitSize _ = 16 countLeadingZeros (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 -> case fromIntegral x of I# x# -> I16# (narrow16Int# x#) "fromIntegral/Int16->a" fromIntegral = (I16# x#) -> fromIntegral (I# x#) #-}
{-# RULES "properFraction/Float->(Int16,Float)" properFraction = \x -> case properFraction x of { (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 -> case properFraction x of { (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) #-}
#if WORD_SIZE_IN_BITS > 32
#endif
data {-# CTYPE "HsInt32" #-} Int32 = I32# Int#
instance Eq Int32 where (==) = eqInt32 (/=) = neInt32
eqInt32, neInt32 :: Int32 -> Int32 -> Bool eqInt32 (I32# x) (I32# y) = isTrue# (x ==# y) neInt32 (I32# x) (I32# y) = isTrue# (x /=# y) {-# INLINE [1] eqInt32 #-} {-# INLINE [1] neInt32 #-}
instance Ord Int32 where (<) = 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](GHC.Int.html#gtInt32)
(I32# y) = isTrue# (x ># y)
(I32# x) [geInt32](GHC.Int.html#geInt32)
(I32# y) = isTrue# (x >=# y)
(I32# x) [ltInt32](GHC.Int.html#ltInt32)
(I32# y) = isTrue# (x <# y)
(I32# x) [leInt32](GHC.Int.html#leInt32)
(I32# y) = isTrue# (x <=# y)
instance Show Int32 where showsPrec p x = showsPrec p (fromIntegral x :: Int)
instance Num Int32 where (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#)) abs x | x >= 0 = x | otherwise = negate x signum x | x > 0 = 1 signum 0 = 0 signum _ = -1 fromInteger i = I32# (narrow32Int# (integerToInt i))
instance Enum Int32 where succ x | x /= maxBound = x + 1 | otherwise = succError "Int32" pred x | x /= minBound = x - 1 | otherwise = predError "Int32" #if WORD_SIZE_IN_BITS == 32 toEnum (I# i#) = I32# i# #else toEnum i@(I# i#) | i >= fromIntegral (minBound::Int32) && i <= fromIntegral (maxBound::Int32) = I32# i# | otherwise = toEnumError "Int32" i (minBound::Int32, maxBound::Int32) #endif fromEnum (I32# x#) = I# x# enumFrom = boundedEnumFrom enumFromThen = boundedEnumFromThen
instance Integral Int32 where
quot x@(I32# x#) y@(I32# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = overflowError
| otherwise = I32# (narrow32Int# (x# quotInt#
y#))
rem (I32# x#) y@(I32# y#)
| y == 0 = divZeroError
| [y](#local-6989586621679089928) == (-1) = 0
| [otherwise](GHC.Base.html#otherwise) = [I32#](GHC.Int.html#I32%23) (narrow32Int# ([x#](#local-6989586621679089927) `remInt#` [y#](#local-6989586621679089929)))
[div](GHC.Real.html#div) [x](#local-6989586621679089930)@([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089931)) [y](#local-6989586621679089932)@([I32#](GHC.Int.html#I32%23) [y#](#local-6989586621679089933))
| [y](#local-6989586621679089932) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679089932) == (-1) && [x](#local-6989586621679089930) == [minBound](GHC.Enum.html#minBound) = [overflowError](GHC.Real.html#overflowError)
| [otherwise](GHC.Base.html#otherwise) = [I32#](GHC.Int.html#I32%23) (narrow32Int# ([x#](#local-6989586621679089931) `divInt#` [y#](#local-6989586621679089933)))
[mod](GHC.Real.html#mod) ([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089934)) [y](#local-6989586621679089935)@([I32#](GHC.Int.html#I32%23) [y#](#local-6989586621679089936))
| [y](#local-6989586621679089935) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679089935) == (-1) = 0
| [otherwise](GHC.Base.html#otherwise) = [I32#](GHC.Int.html#I32%23) (narrow32Int# ([x#](#local-6989586621679089934) `modInt#` [y#](#local-6989586621679089936)))
[quotRem](GHC.Real.html#quotRem) [x](#local-6989586621679089937)@([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089938)) [y](#local-6989586621679089939)@([I32#](GHC.Int.html#I32%23) [y#](#local-6989586621679089940))
| [y](#local-6989586621679089939) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679089939) == (-1) && [x](#local-6989586621679089937) == [minBound](GHC.Enum.html#minBound) = ([overflowError](GHC.Real.html#overflowError), 0)
| [otherwise](GHC.Base.html#otherwise) = case [x#](#local-6989586621679089938) `quotRemInt#` [y#](#local-6989586621679089940) of
(# [q](#local-6989586621679089941), [r](#local-6989586621679089942) #) ->
([I32#](GHC.Int.html#I32%23) (narrow32Int# [q](#local-6989586621679089941)),
[I32#](GHC.Int.html#I32%23) (narrow32Int# [r](#local-6989586621679089942)))
[divMod](GHC.Real.html#divMod) [x](#local-6989586621679089943)@([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089944)) [y](#local-6989586621679089945)@([I32#](GHC.Int.html#I32%23) [y#](#local-6989586621679089946))
| [y](#local-6989586621679089945) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679089945) == (-1) && [x](#local-6989586621679089943) == [minBound](GHC.Enum.html#minBound) = ([overflowError](GHC.Real.html#overflowError), 0)
| [otherwise](GHC.Base.html#otherwise) = case [x#](#local-6989586621679089944) `[divModInt#](GHC.Base.html#divModInt%23)` [y#](#local-6989586621679089946) of
(# [d](#local-6989586621679089947), [m](#local-6989586621679089948) #) ->
([I32#](GHC.Int.html#I32%23) (narrow32Int# [d](#local-6989586621679089947)),
[I32#](GHC.Int.html#I32%23) (narrow32Int# [m](#local-6989586621679089948)))
[toInteger](GHC.Real.html#toInteger) ([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089949)) = smallInteger [x#](#local-6989586621679089949)
instance Read Int32 where readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
instance Bits Int32 where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-}
([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089895)) [.&.](Data.Bits.html#.%26.) ([I32#](GHC.Int.html#I32%23) [y#](#local-6989586621679089896)) = [I32#](GHC.Int.html#I32%23) (word2Int# (int2Word# [x#](#local-6989586621679089895) `and#` int2Word# [y#](#local-6989586621679089896)))
([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089897)) [.|.](Data.Bits.html#.%7C.) ([I32#](GHC.Int.html#I32%23) [y#](#local-6989586621679089898)) = [I32#](GHC.Int.html#I32%23) (word2Int# (int2Word# [x#](#local-6989586621679089897) `or#` int2Word# [y#](#local-6989586621679089898)))
([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089899)) `[xor](Data.Bits.html#xor)` ([I32#](GHC.Int.html#I32%23) [y#](#local-6989586621679089900)) = [I32#](GHC.Int.html#I32%23) (word2Int# (int2Word# [x#](#local-6989586621679089899) `xor#` int2Word# [y#](#local-6989586621679089900)))
[complement](Data.Bits.html#complement) ([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089901)) = [I32#](GHC.Int.html#I32%23) (word2Int# (not# (int2Word# [x#](#local-6989586621679089901))))
([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089902)) `[shift](Data.Bits.html#shift)` (I# [i#](#local-6989586621679089903))
| isTrue# ([i#](#local-6989586621679089903) >=# 0#) = [I32#](GHC.Int.html#I32%23) (narrow32Int# ([x#](#local-6989586621679089902) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679089903)))
| [otherwise](GHC.Base.html#otherwise) = [I32#](GHC.Int.html#I32%23) ([x#](#local-6989586621679089902) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` negateInt# [i#](#local-6989586621679089903))
([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089904)) `[shiftL](Data.Bits.html#shiftL)` (I# [i#](#local-6989586621679089905)) = [I32#](GHC.Int.html#I32%23) (narrow32Int# ([x#](#local-6989586621679089904) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679089905)))
([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089906)) `[unsafeShiftL](Data.Bits.html#unsafeShiftL)` (I# [i#](#local-6989586621679089907)) =
[I32#](GHC.Int.html#I32%23) (narrow32Int# ([x#](#local-6989586621679089906) `uncheckedIShiftL#` [i#](#local-6989586621679089907)))
([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089908)) `[shiftR](Data.Bits.html#shiftR)` (I# [i#](#local-6989586621679089909)) = [I32#](GHC.Int.html#I32%23) ([x#](#local-6989586621679089908) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` [i#](#local-6989586621679089909))
([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089910)) `[unsafeShiftR](Data.Bits.html#unsafeShiftR)` (I# [i#](#local-6989586621679089911)) = [I32#](GHC.Int.html#I32%23) ([x#](#local-6989586621679089910) `uncheckedIShiftRA#` [i#](#local-6989586621679089911))
([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089912)) `[rotate](Data.Bits.html#rotate)` (I# [i#](#local-6989586621679089913))
| isTrue# ([i'#](#local-6989586621679089915) ==# 0#)
= [I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089912)
| [otherwise](GHC.Base.html#otherwise)
= [I32#](GHC.Int.html#I32%23) (narrow32Int# (word2Int# (([x'#](#local-6989586621679089914) `uncheckedShiftL#` [i'#](#local-6989586621679089915)) `or#`
([x'#](#local-6989586621679089914) `uncheckedShiftRL#` (32# -# [i'#](#local-6989586621679089915))))))
where
![x'#](#local-6989586621679089914) = narrow32Word# (int2Word# [x#](#local-6989586621679089912))
![i'#](#local-6989586621679089915) = word2Int# (int2Word# [i#](#local-6989586621679089913) `and#` 31##)
[bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [i](#local-6989586621679089916) = [Just](GHC.Maybe.html#Just) ([finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679089916))
[bitSize](Data.Bits.html#bitSize) [i](#local-6989586621679089917) = [finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679089917)
[isSigned](Data.Bits.html#isSigned) _ = True
[popCount](Data.Bits.html#popCount) ([I32#](GHC.Int.html#I32%23) [x#](#local-6989586621679089918)) = I# (word2Int# (popCnt32# (int2Word# [x#](#local-6989586621679089918))))
[bit](Data.Bits.html#bit) = [bitDefault](Data.Bits.html#bitDefault)
[testBit](Data.Bits.html#testBit) = [testBitDefault](Data.Bits.html#testBitDefault)
instance FiniteBits Int32 where finiteBitSize _ = 32 countLeadingZeros (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 -> case fromIntegral x of I# x# -> I32# (narrow32Int# x#) "fromIntegral/Int32->a" fromIntegral = (I32# x#) -> fromIntegral (I# x#) #-}
{-# RULES "properFraction/Float->(Int32,Float)" properFraction = \x -> case properFraction x of { (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 -> case properFraction x of { (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) #-}
instance Real Int32 where toRational x = toInteger x % 1
instance Bounded Int32 where minBound = -0x80000000 maxBound = 0x7FFFFFFF
instance Ix Int32 where range (m,n) = [m..n] unsafeIndex (m,_) i = fromIntegral i - fromIntegral m inRange (m,n) i = m <= i && i <= n
#if WORD_SIZE_IN_BITS < 64
data {-# CTYPE "HsInt64" #-} Int64 = I64# Int64#
instance Eq Int64 where (==) = eqInt64 (/=) = neInt64
eqInt64, neInt64 :: Int64 -> Int64 -> Bool
eqInt64 (I64# x) (I64# y) = isTrue# (x eqInt64#
y)
neInt64 (I64# x) (I64# y) = isTrue# (x neInt64#
y)
{-# INLINE [1] eqInt64 #-}
{-# INLINE [1] neInt64 #-}
instance Ord Int64 where (<) = 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)
instance Show Int64 where showsPrec p x = showsPrec p (toInteger x)
instance Num Int64 where
(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#)
abs x | x >= 0 = x
| otherwise = negate x
signum x | x > 0 = 1
signum 0 = 0
signum _ = -1
fromInteger i = I64# (integerToInt64 i)
instance Enum Int64 where succ x | x /= maxBound = x + 1 | otherwise = succError "Int64" pred x | x /= minBound = x - 1 | otherwise = predError "Int64" toEnum (I# i#) = I64# (intToInt64# i#) fromEnum x@(I64# x#) | x >= fromIntegral (minBound::Int) && x <= fromIntegral (maxBound::Int) = I# (int64ToInt# x#) | otherwise = fromEnumError "Int64" x enumFrom = integralEnumFrom enumFromThen = integralEnumFromThen enumFromTo = integralEnumFromTo enumFromThenTo = integralEnumFromThenTo
instance Integral Int64 where
quot x@(I64# x#) y@(I64# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = overflowError
| otherwise = I64# (x# quotInt64#
y#)
rem (I64# x#) y@(I64# y#)
| y == 0 = divZeroError
| y == (-1) = 0
| otherwise = I64# (x# `remInt64#` y#)
div x@(I64# x#) y@(I64# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = overflowError
| otherwise = I64# (x# `divInt64#` y#)
mod (I64# x#) y@(I64# y#)
| y == 0 = divZeroError
| y == (-1) = 0
| otherwise = I64# (x# `modInt64#` y#)
quotRem x@(I64# x#) y@(I64# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = (overflowError, 0)
| otherwise = (I64# (x# `quotInt64#` y#),
I64# (x# `remInt64#` y#))
divMod x@(I64# x#) y@(I64# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = (overflowError, 0)
| otherwise = (I64# (x# `divInt64#` y#),
I64# (x# `modInt64#` y#))
toInteger (I64# x) = int64ToInteger x
divInt64#, modInt64# :: Int64# -> Int64# -> Int64#
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)
= if isTrue# (r# neInt64#
zero) then r# plusInt64#
y# else zero
| otherwise = r#
where
!zero = intToInt64# 0#
!r# = x# remInt64#
y#
instance Read Int64 where readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
instance Bits Int64 where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-}
(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##)
bitSizeMaybe i = Just (finiteBitSize i)
bitSize i = finiteBitSize i
isSigned _ = True
popCount (I64# x#) =
I# (word2Int# (popCnt64# (int64ToWord64# x#)))
bit = bitDefault
testBit = testBitDefault
iShiftL64#, iShiftRA64# :: Int64# -> Int# -> Int64#
a iShiftL64#
b | isTrue# (b >=# 64#) = intToInt64# 0#
| otherwise = a uncheckedIShiftL64#
b
a iShiftRA64#
b | isTrue# (b >=# 64#) = if isTrue# (a ltInt64#
(intToInt64# 0#))
then intToInt64# (-1#)
else intToInt64# 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 #-}
#else
data {-# CTYPE "HsInt64" #-} Int64 = I64# Int#
instance Eq Int64 where (==) = eqInt64 (/=) = neInt64
eqInt64, neInt64 :: Int64 -> Int64 -> Bool eqInt64 (I64# x) (I64# y) = isTrue# (x ==# y) neInt64 (I64# x) (I64# y) = isTrue# (x /=# y) {-# INLINE [1] eqInt64 #-} {-# INLINE [1] neInt64 #-}
instance Ord Int64 where (<) = 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](GHC.Int.html#gtInt64)
(I64# y) = isTrue# (x ># y)
(I64# x) [geInt64](GHC.Int.html#geInt64)
(I64# y) = isTrue# (x >=# y)
(I64# x) [ltInt64](GHC.Int.html#ltInt64)
(I64# y) = isTrue# (x <# y)
(I64# x) [leInt64](GHC.Int.html#leInt64)
(I64# y) = isTrue# (x <=# y)
instance Show Int64 where showsPrec p x = showsPrec p (fromIntegral x :: Int)
instance Num Int64 where (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#) abs x | x >= 0 = x | otherwise = negate x signum x | x > 0 = 1 signum 0 = 0 signum _ = -1 fromInteger i = I64# (integerToInt i)
instance Enum Int64 where succ x | x /= maxBound = x + 1 | otherwise = succError "Int64" pred x | x /= minBound = x - 1 | otherwise = predError "Int64" toEnum (I# i#) = I64# i# fromEnum (I64# x#) = I# x# enumFrom = boundedEnumFrom enumFromThen = boundedEnumFromThen
instance Integral Int64 where
quot x@(I64# x#) y@(I64# y#)
| y == 0 = divZeroError
| y == (-1) && x == minBound = overflowError
| otherwise = I64# (x# quotInt#
y#)
rem (I64# x#) y@(I64# y#)
| y == 0 = divZeroError
| [y](#local-6989586621679089847) == (-1) = 0
| [otherwise](GHC.Base.html#otherwise) = [I64#](GHC.Int.html#I64%23) ([x#](#local-6989586621679089846) `remInt#` [y#](#local-6989586621679089848))
[div](GHC.Real.html#div) [x](#local-6989586621679089849)@([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089850)) [y](#local-6989586621679089851)@([I64#](GHC.Int.html#I64%23) [y#](#local-6989586621679089852))
| [y](#local-6989586621679089851) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679089851) == (-1) && [x](#local-6989586621679089849) == [minBound](GHC.Enum.html#minBound) = [overflowError](GHC.Real.html#overflowError)
| [otherwise](GHC.Base.html#otherwise) = [I64#](GHC.Int.html#I64%23) ([x#](#local-6989586621679089850) `divInt#` [y#](#local-6989586621679089852))
[mod](GHC.Real.html#mod) ([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089853)) [y](#local-6989586621679089854)@([I64#](GHC.Int.html#I64%23) [y#](#local-6989586621679089855))
| [y](#local-6989586621679089854) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679089854) == (-1) = 0
| [otherwise](GHC.Base.html#otherwise) = [I64#](GHC.Int.html#I64%23) ([x#](#local-6989586621679089853) `modInt#` [y#](#local-6989586621679089855))
[quotRem](GHC.Real.html#quotRem) [x](#local-6989586621679089856)@([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089857)) [y](#local-6989586621679089858)@([I64#](GHC.Int.html#I64%23) [y#](#local-6989586621679089859))
| [y](#local-6989586621679089858) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679089858) == (-1) && [x](#local-6989586621679089856) == [minBound](GHC.Enum.html#minBound) = ([overflowError](GHC.Real.html#overflowError), 0)
| [otherwise](GHC.Base.html#otherwise) = case [x#](#local-6989586621679089857) `quotRemInt#` [y#](#local-6989586621679089859) of
(# [q](#local-6989586621679089860), [r](#local-6989586621679089861) #) ->
([I64#](GHC.Int.html#I64%23) [q](#local-6989586621679089860), [I64#](GHC.Int.html#I64%23) [r](#local-6989586621679089861))
[divMod](GHC.Real.html#divMod) [x](#local-6989586621679089862)@([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089863)) [y](#local-6989586621679089864)@([I64#](GHC.Int.html#I64%23) [y#](#local-6989586621679089865))
| [y](#local-6989586621679089864) == 0 = [divZeroError](GHC.Real.html#divZeroError)
| [y](#local-6989586621679089864) == (-1) && [x](#local-6989586621679089862) == [minBound](GHC.Enum.html#minBound) = ([overflowError](GHC.Real.html#overflowError), 0)
| [otherwise](GHC.Base.html#otherwise) = case [x#](#local-6989586621679089863) `[divModInt#](GHC.Base.html#divModInt%23)` [y#](#local-6989586621679089865) of
(# [d](#local-6989586621679089866), [m](#local-6989586621679089867) #) ->
([I64#](GHC.Int.html#I64%23) [d](#local-6989586621679089866), [I64#](GHC.Int.html#I64%23) [m](#local-6989586621679089867))
[toInteger](GHC.Real.html#toInteger) ([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089868)) = smallInteger [x#](#local-6989586621679089868)
instance Read Int64 where readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
instance Bits Int64 where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-}
([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089814)) [.&.](Data.Bits.html#.%26.) ([I64#](GHC.Int.html#I64%23) [y#](#local-6989586621679089815)) = [I64#](GHC.Int.html#I64%23) (word2Int# (int2Word# [x#](#local-6989586621679089814) `and#` int2Word# [y#](#local-6989586621679089815)))
([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089816)) [.|.](Data.Bits.html#.%7C.) ([I64#](GHC.Int.html#I64%23) [y#](#local-6989586621679089817)) = [I64#](GHC.Int.html#I64%23) (word2Int# (int2Word# [x#](#local-6989586621679089816) `or#` int2Word# [y#](#local-6989586621679089817)))
([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089818)) `[xor](Data.Bits.html#xor)` ([I64#](GHC.Int.html#I64%23) [y#](#local-6989586621679089819)) = [I64#](GHC.Int.html#I64%23) (word2Int# (int2Word# [x#](#local-6989586621679089818) `xor#` int2Word# [y#](#local-6989586621679089819)))
[complement](Data.Bits.html#complement) ([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089820)) = [I64#](GHC.Int.html#I64%23) (word2Int# (int2Word# [x#](#local-6989586621679089820) `xor#` int2Word# (-1#)))
([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089821)) `[shift](Data.Bits.html#shift)` (I# [i#](#local-6989586621679089822))
| isTrue# ([i#](#local-6989586621679089822) >=# 0#) = [I64#](GHC.Int.html#I64%23) ([x#](#local-6989586621679089821) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679089822))
| [otherwise](GHC.Base.html#otherwise) = [I64#](GHC.Int.html#I64%23) ([x#](#local-6989586621679089821) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` negateInt# [i#](#local-6989586621679089822))
([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089823)) `[shiftL](Data.Bits.html#shiftL)` (I# [i#](#local-6989586621679089824)) = [I64#](GHC.Int.html#I64%23) ([x#](#local-6989586621679089823) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679089824))
([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089825)) `[unsafeShiftL](Data.Bits.html#unsafeShiftL)` (I# [i#](#local-6989586621679089826)) = [I64#](GHC.Int.html#I64%23) ([x#](#local-6989586621679089825) `uncheckedIShiftL#` [i#](#local-6989586621679089826))
([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089827)) `[shiftR](Data.Bits.html#shiftR)` (I# [i#](#local-6989586621679089828)) = [I64#](GHC.Int.html#I64%23) ([x#](#local-6989586621679089827) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` [i#](#local-6989586621679089828))
([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089829)) `[unsafeShiftR](Data.Bits.html#unsafeShiftR)` (I# [i#](#local-6989586621679089830)) = [I64#](GHC.Int.html#I64%23) ([x#](#local-6989586621679089829) `uncheckedIShiftRA#` [i#](#local-6989586621679089830))
([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089831)) `[rotate](Data.Bits.html#rotate)` (I# [i#](#local-6989586621679089832))
| isTrue# ([i'#](#local-6989586621679089834) ==# 0#)
= [I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089831)
| [otherwise](GHC.Base.html#otherwise)
= [I64#](GHC.Int.html#I64%23) (word2Int# (([x'#](#local-6989586621679089833) `uncheckedShiftL#` [i'#](#local-6989586621679089834)) `or#`
([x'#](#local-6989586621679089833) `uncheckedShiftRL#` (64# -# [i'#](#local-6989586621679089834)))))
where
![x'#](#local-6989586621679089833) = int2Word# [x#](#local-6989586621679089831)
![i'#](#local-6989586621679089834) = word2Int# (int2Word# [i#](#local-6989586621679089832) `and#` 63##)
[bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [i](#local-6989586621679089835) = [Just](GHC.Maybe.html#Just) ([finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679089835))
[bitSize](Data.Bits.html#bitSize) [i](#local-6989586621679089836) = [finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679089836)
[isSigned](Data.Bits.html#isSigned) _ = True
[popCount](Data.Bits.html#popCount) ([I64#](GHC.Int.html#I64%23) [x#](#local-6989586621679089837)) = I# (word2Int# (popCnt64# (int2Word# [x#](#local-6989586621679089837))))
[bit](Data.Bits.html#bit) = [bitDefault](Data.Bits.html#bitDefault)
[testBit](Data.Bits.html#testBit) = [testBitDefault](Data.Bits.html#testBitDefault)
{-# RULES "fromIntegral/a->Int64" fromIntegral = \x -> case fromIntegral x of I# x# -> I64# x# "fromIntegral/Int64->a" fromIntegral = (I64# x#) -> fromIntegral (I# x#) #-}
{-# RULES "properFraction/Float->(Int64,Float)" properFraction = \x -> case properFraction x of { (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 -> case properFraction x of { (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
instance FiniteBits Int64 where finiteBitSize _ = 64 #if WORD_SIZE_IN_BITS < 64 countLeadingZeros (I64# x#) = I# (word2Int# (clz64# (int64ToWord64# x#))) countTrailingZeros (I64# x#) = I# (word2Int# (ctz64# (int64ToWord64# x#))) #else countLeadingZeros (I64# x#) = I# (word2Int# (clz64# (int2Word# x#))) countTrailingZeros (I64# x#) = I# (word2Int# (ctz64# (int2Word# x#))) #endif
instance Real Int64 where toRational x = toInteger x % 1
instance Bounded Int64 where minBound = -0x8000000000000000 maxBound = 0x7FFFFFFFFFFFFFFF
instance Ix Int64 where range (m,n) = [m..n] unsafeIndex (m,_) i = fromIntegral i - fromIntegral m inRange (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
{-# RULES "fromIntegral/Natural->Int64" fromIntegral = (fromIntegral :: Int -> Int64) . naturalToInt "fromIntegral/Int64->Natural" fromIntegral = intToNatural . (fromIntegral :: Int64 -> Int) #-} #endif