{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE NegativeLiterals #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE Trustworthy #-} {-# LANGUAGE UnboxedTuples #-} {-# OPTIONS_HADDOCK not-home #-} #include "MachDeps.h" module GHC.Internal.Int ( Int(..), Int8(..), Int16(..), Int32(..), Int64(..), uncheckedIShiftL64#, uncheckedIShiftRA64#, shiftRLInt8#, shiftRLInt16#, shiftRLInt32#, eqInt, 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 ) where import GHC.Internal.Data.Bits import GHC.Internal.Data.Maybe import GHC.Prim import GHC.Internal.Base import GHC.Internal.Enum import GHC.Internal.Num import GHC.Internal.Real import GHC.Internal.Read import GHC.Internal.Arr import GHC.Internal.Show data {-# CTYPE "HsInt8" #-} Int8 = I8# Int8# instance Eq Int8 where == :: Int8 -> Int8 -> Bool (==) = Int8 -> Int8 -> Bool eqInt8 /= :: Int8 -> Int8 -> Bool (/=) = Int8 -> Int8 -> Bool neInt8 eqInt8, neInt8 :: Int8 -> Int8 -> Bool eqInt8 :: Int8 -> Int8 -> Bool eqInt8 (I8# Int8# x) (I8# Int8# y) = Int# -> Bool isTrue# ((Int8# -> Int# int8ToInt# Int8# x) Int# -> Int# -> Int# ==# (Int8# -> Int# int8ToInt# Int8# y)) neInt8 :: Int8 -> Int8 -> Bool neInt8 (I8# Int8# x) (I8# Int8# y) = Int# -> Bool isTrue# ((Int8# -> Int# int8ToInt# Int8# x) Int# -> Int# -> Int# /=# (Int8# -> Int# int8ToInt# Int8# y)) {-# INLINE [1] eqInt8 #-} {-# INLINE [1] neInt8 #-} instance Ord Int8 where < :: Int8 -> Int8 -> Bool (<) = Int8 -> Int8 -> Bool ltInt8 <= :: Int8 -> Int8 -> Bool (<=) = Int8 -> Int8 -> Bool leInt8 >= :: Int8 -> Int8 -> Bool (>=) = Int8 -> Int8 -> Bool geInt8 > :: Int8 -> Int8 -> Bool (>) = Int8 -> Int8 -> Bool gtInt8 {-# INLINE [1] gtInt8 #-} {-# INLINE [1] geInt8 #-} {-# INLINE [1] ltInt8 #-} {-# INLINE [1] leInt8 #-} gtInt8, geInt8, ltInt8, leInt8 :: Int8 -> Int8 -> Bool (I8# Int8# x) gtInt8 :: Int8 -> Int8 -> Bool `gtInt8` (I8# Int8# y) = Int# -> Bool isTrue# (Int8# x Int8# -> Int8# -> Int# `gtInt8#` Int8# y) (I8# Int8# x) geInt8 :: Int8 -> Int8 -> Bool `geInt8` (I8# Int8# y) = Int# -> Bool isTrue# (Int8# x Int8# -> Int8# -> Int# `geInt8#` Int8# y) (I8# Int8# x) ltInt8 :: Int8 -> Int8 -> Bool `ltInt8` (I8# Int8# y) = Int# -> Bool isTrue# (Int8# x Int8# -> Int8# -> Int# `ltInt8#` Int8# y) (I8# Int8# x) leInt8 :: Int8 -> Int8 -> Bool `leInt8` (I8# Int8# y) = Int# -> Bool isTrue# (Int8# x Int8# -> Int8# -> Int# `leInt8#` Int8# y) instance Show Int8 where showsPrec :: Int -> Int8 -> ShowS showsPrec Int p Int8 x = Int -> Int -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p (Int8 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int8 x :: Int) instance Num Int8 where (I8# Int8# x#) + :: Int8 -> Int8 -> Int8 + (I8# Int8# y#) = Int8# -> Int8 I8# (Int8# x# Int8# -> Int8# -> Int8# `plusInt8#` Int8# y#) (I8# Int8# x#) - :: Int8 -> Int8 -> Int8 - (I8# Int8# y#) = Int8# -> Int8 I8# (Int8# x# Int8# -> Int8# -> Int8# `subInt8#` Int8# y#) (I8# Int8# x#) * :: Int8 -> Int8 -> Int8 * (I8# Int8# y#) = Int8# -> Int8 I8# (Int8# x# Int8# -> Int8# -> Int8# `timesInt8#` Int8# y#) negate :: Int8 -> Int8 negate (I8# Int8# x#) = Int8# -> Int8 I8# (Int8# -> Int8# negateInt8# Int8# x#) abs :: Int8 -> Int8 abs Int8 x | Int8 x Int8 -> Int8 -> Bool forall a. Ord a => a -> a -> Bool >= Int8 0 = Int8 x | Bool otherwise = Int8 -> Int8 forall a. Num a => a -> a negate Int8 x signum :: Int8 -> Int8 signum Int8 x | Int8 x Int8 -> Int8 -> Bool forall a. Ord a => a -> a -> Bool > Int8 0 = Int8 1 signum Int8 0 = Int8 0 signum Int8 _ = Int8 -1 fromInteger :: Integer -> Int8 fromInteger Integer i = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# (Integer -> Int# integerToInt# Integer i)) instance Real Int8 where toRational :: Int8 -> Rational toRational Int8 x = Int8 -> Integer forall a. Integral a => a -> Integer toInteger Int8 x Integer -> Integer -> Rational forall a. Integral a => a -> a -> Ratio a % Integer 1 instance Enum Int8 where succ :: Int8 -> Int8 succ Int8 x | Int8 x Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool /= Int8 forall a. Bounded a => a maxBound = Int8 x Int8 -> Int8 -> Int8 forall a. Num a => a -> a -> a + Int8 1 | Bool otherwise = String -> Int8 forall a. String -> a succError String "Int8" pred :: Int8 -> Int8 pred Int8 x | Int8 x Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool /= Int8 forall a. Bounded a => a minBound = Int8 x Int8 -> Int8 -> Int8 forall a. Num a => a -> a -> a - Int8 1 | Bool otherwise = String -> Int8 forall a. String -> a predError String "Int8" toEnum :: Int -> Int8 toEnum i :: Int i@(I# Int# i#) | Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int8 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int8 forall a. Bounded a => a minBound::Int8) Bool -> Bool -> Bool && Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Int8 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int8 forall a. Bounded a => a maxBound::Int8) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# Int# i#) | Bool otherwise = String -> Int -> (Int8, Int8) -> Int8 forall a b. Show a => String -> Int -> (a, a) -> b toEnumError String "Int8" Int i (Int8 forall a. Bounded a => a minBound::Int8, Int8 forall a. Bounded a => a maxBound::Int8) fromEnum :: Int8 -> Int fromEnum (I8# Int8# x#) = Int# -> Int I# (Int8# -> Int# int8ToInt# Int8# x#) {-# INLINE enumFrom #-} enumFrom :: Int8 -> [Int8] enumFrom = Int8 -> [Int8] forall a. (Enum a, Bounded a) => a -> [a] boundedEnumFrom {-# INLINE enumFromThen #-} enumFromThen :: Int8 -> Int8 -> [Int8] enumFromThen = Int8 -> Int8 -> [Int8] forall a. (Enum a, Bounded a) => a -> a -> [a] boundedEnumFromThen instance Integral Int8 where quot :: Int8 -> Int8 -> Int8 quot x :: Int8 x@(I8# Int8# x#) y :: Int8 y@(I8# Int8# y#) | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 0 = Int8 forall a. a divZeroError | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == (Int8 -1) Bool -> Bool -> Bool && Int8 x Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 forall a. Bounded a => a minBound = Int8 forall a. a overflowError | Bool otherwise = Int8# -> Int8 I8# (Int8# x# Int8# -> Int8# -> Int8# `quotInt8#` Int8# y#) rem :: Int8 -> Int8 -> Int8 rem (I8# Int8# x#) y :: Int8 y@(I8# Int8# y#) | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 0 = Int8 forall a. a divZeroError | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == (Int8 -1) = Int8 0 | Bool otherwise = Int8# -> Int8 I8# (Int8# x# Int8# -> Int8# -> Int8# `remInt8#` Int8# y#) div :: Int8 -> Int8 -> Int8 div x :: Int8 x@(I8# Int8# x#) y :: Int8 y@(I8# Int8# y#) | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 0 = Int8 forall a. a divZeroError | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == (Int8 -1) Bool -> Bool -> Bool && Int8 x Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 forall a. Bounded a => a minBound = Int8 forall a. a overflowError | Bool otherwise = Int8# -> Int8 I8# (Int8# x# Int8# -> Int8# -> Int8# `divInt8#` Int8# y#) mod :: Int8 -> Int8 -> Int8 mod (I8# Int8# x#) y :: Int8 y@(I8# Int8# y#) | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 0 = Int8 forall a. a divZeroError | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == (Int8 -1) = Int8 0 | Bool otherwise = Int8# -> Int8 I8# (Int8# x# Int8# -> Int8# -> Int8# `modInt8#` Int8# y#) quotRem :: Int8 -> Int8 -> (Int8, Int8) quotRem x :: Int8 x@(I8# Int8# x#) y :: Int8 y@(I8# Int8# y#) | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 0 = (Int8, Int8) forall a. a divZeroError | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == (Int8 -1) Bool -> Bool -> Bool && Int8 x Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 forall a. Bounded a => a minBound = (Int8 forall a. a overflowError, Int8 0) | Bool otherwise = case Int8# x# Int8# -> Int8# -> (# Int8#, Int8# #) `quotRemInt8#` Int8# y# of (# Int8# q, Int8# r #) -> (Int8# -> Int8 I8# Int8# q, Int8# -> Int8 I8# Int8# r) divMod :: Int8 -> Int8 -> (Int8, Int8) divMod x :: Int8 x@(I8# Int8# x#) y :: Int8 y@(I8# Int8# y#) | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 0 = (Int8, Int8) forall a. a divZeroError | Int8 y Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == (Int8 -1) Bool -> Bool -> Bool && Int8 x Int8 -> Int8 -> Bool forall a. Eq a => a -> a -> Bool == Int8 forall a. Bounded a => a minBound = (Int8 forall a. a overflowError, Int8 0) | Bool otherwise = case Int8# x# Int8# -> Int8# -> (# Int8#, Int8# #) `divModInt8#` Int8# y# of (# Int8# d, Int8# m #) -> (Int8# -> Int8 I8# Int8# d, Int8# -> Int8 I8# Int8# m) toInteger :: Int8 -> Integer toInteger (I8# Int8# x#) = Int# -> Integer IS (Int8# -> Int# int8ToInt# Int8# x#) instance Bounded Int8 where minBound :: Int8 minBound = Int8 -0x80 maxBound :: Int8 maxBound = Int8 0x7F instance Ix Int8 where range :: (Int8, Int8) -> [Int8] range (Int8 m,Int8 n) = [Int8 m..Int8 n] unsafeIndex :: (Int8, Int8) -> Int8 -> Int unsafeIndex (Int8 m,Int8 _) Int8 i = Int8 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int8 i Int -> Int -> Int forall a. Num a => a -> a -> a - Int8 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int8 m inRange :: (Int8, Int8) -> Int8 -> Bool inRange (Int8 m,Int8 n) Int8 i = Int8 m Int8 -> Int8 -> Bool forall a. Ord a => a -> a -> Bool <= Int8 i Bool -> Bool -> Bool && Int8 i Int8 -> Int8 -> Bool forall a. Ord a => a -> a -> Bool <= Int8 n instance Read Int8 where readsPrec :: Int -> ReadS Int8 readsPrec Int p String s = [(Int -> Int8 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int x::Int), String r) | (Int x, String r) <- Int -> ReadS Int forall a. Read a => Int -> ReadS a readsPrec Int p String s] instance Bits Int8 where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-} {-# INLINE popCount #-} (I8# Int8# x#) .&. :: Int8 -> Int8 -> Int8 .&. (I8# Int8# y#) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# ((Int8# -> Int# int8ToInt# Int8# x#) Int# -> Int# -> Int# `andI#` (Int8# -> Int# int8ToInt# Int8# y#))) (I8# Int8# x#) .|. :: Int8 -> Int8 -> Int8 .|. (I8# Int8# y#) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# ((Int8# -> Int# int8ToInt# Int8# x#) Int# -> Int# -> Int# `orI#` (Int8# -> Int# int8ToInt# Int8# y#))) (I8# Int8# x#) xor :: Int8 -> Int8 -> Int8 `xor` (I8# Int8# y#) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# ((Int8# -> Int# int8ToInt# Int8# x#) Int# -> Int# -> Int# `xorI#` (Int8# -> Int# int8ToInt# Int8# y#))) complement :: Int8 -> Int8 complement (I8# Int8# x#) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# (Int# -> Int# notI# (Int8# -> Int# int8ToInt# Int8# x#))) (I8# Int8# x#) shift :: Int8 -> Int -> Int8 `shift` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# ((Int8# -> Int# int8ToInt# Int8# x#) Int# -> Int# -> Int# `iShiftL#` Int# i#)) | Bool otherwise = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# ((Int8# -> Int# int8ToInt# Int8# x#) Int# -> Int# -> Int# `iShiftRA#` Int# -> Int# negateInt# Int# i#)) (I8# Int8# x#) shiftL :: Int8 -> Int -> Int8 `shiftL` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# ((Int8# -> Int# int8ToInt# Int8# x#) Int# -> Int# -> Int# `iShiftL#` Int# i#)) | Bool otherwise = Int8 forall a. a overflowError (I8# Int8# x#) unsafeShiftL :: Int8 -> Int -> Int8 `unsafeShiftL` (I# Int# i#) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# ((Int8# -> Int# int8ToInt# Int8# x#) Int# -> Int# -> Int# `uncheckedIShiftL#` Int# i#)) (I8# Int8# x#) shiftR :: Int8 -> Int -> Int8 `shiftR` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# ((Int8# -> Int# int8ToInt# Int8# x#) Int# -> Int# -> Int# `iShiftRA#` Int# i#)) | Bool otherwise = Int8 forall a. a overflowError (I8# Int8# x#) unsafeShiftR :: Int8 -> Int -> Int8 `unsafeShiftR` (I# Int# i#) = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# ((Int8# -> Int# int8ToInt# Int8# x#) Int# -> Int# -> Int# `uncheckedIShiftRA#` Int# i#)) (I8# Int8# x#) rotate :: Int8 -> Int -> Int8 `rotate` (I# Int# i#) | Int# -> Bool isTrue# (Int# i'# Int# -> Int# -> Int# ==# Int# 0#) = Int8# -> Int8 I8# Int8# x# | Bool otherwise = Int8# -> Int8 I8# (Int# -> Int8# intToInt8# (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# (Int8# -> Int# int8ToInt# Int8# x#)) !i'# :: Int# i'# = Word# -> Int# word2Int# (Int# -> Word# int2Word# Int# i# Word# -> Word# -> Word# `and#` Word# 7##) bitSizeMaybe :: Int8 -> Maybe Int bitSizeMaybe Int8 i = Int -> Maybe Int forall a. a -> Maybe a Just (Int8 -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int8 i) bitSize :: Int8 -> Int bitSize Int8 i = Int8 -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int8 i isSigned :: Int8 -> Bool isSigned Int8 _ = Bool True popCount :: Int8 -> Int popCount (I8# Int8# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# popCnt8# (Int# -> Word# int2Word# (Int8# -> Int# int8ToInt# Int8# x#)))) bit :: Int -> Int8 bit Int i = Int -> Int8 forall a. (Bits a, Num a) => Int -> a bitDefault Int i testBit :: Int8 -> Int -> Bool testBit Int8 a Int i = Int8 -> Int -> Bool forall a. (Bits a, Num a) => a -> Int -> Bool testBitDefault Int8 a Int i instance FiniteBits Int8 where {-# INLINE countLeadingZeros #-} {-# INLINE countTrailingZeros #-} finiteBitSize :: Int8 -> Int finiteBitSize Int8 _ = Int 8 countLeadingZeros :: Int8 -> Int countLeadingZeros (I8# Int8# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# clz8# (Int# -> Word# int2Word# (Int8# -> Int# int8ToInt# Int8# x#)))) countTrailingZeros :: Int8 -> Int countTrailingZeros (I8# Int8# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# ctz8# (Int# -> Word# int2Word# (Int8# -> Int# int8ToInt# Int8# 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# Int16# instance Eq Int16 where == :: Int16 -> Int16 -> Bool (==) = Int16 -> Int16 -> Bool eqInt16 /= :: Int16 -> Int16 -> Bool (/=) = Int16 -> Int16 -> Bool neInt16 eqInt16, neInt16 :: Int16 -> Int16 -> Bool eqInt16 :: Int16 -> Int16 -> Bool eqInt16 (I16# Int16# x) (I16# Int16# y) = Int# -> Bool isTrue# ((Int16# -> Int# int16ToInt# Int16# x) Int# -> Int# -> Int# ==# (Int16# -> Int# int16ToInt# Int16# y)) neInt16 :: Int16 -> Int16 -> Bool neInt16 (I16# Int16# x) (I16# Int16# y) = Int# -> Bool isTrue# ((Int16# -> Int# int16ToInt# Int16# x) Int# -> Int# -> Int# /=# (Int16# -> Int# int16ToInt# Int16# y)) {-# INLINE [1] eqInt16 #-} {-# INLINE [1] neInt16 #-} instance Ord Int16 where < :: Int16 -> Int16 -> Bool (<) = Int16 -> Int16 -> Bool ltInt16 <= :: Int16 -> Int16 -> Bool (<=) = Int16 -> Int16 -> Bool leInt16 >= :: Int16 -> Int16 -> Bool (>=) = Int16 -> Int16 -> Bool geInt16 > :: Int16 -> Int16 -> Bool (>) = Int16 -> Int16 -> Bool gtInt16 {-# INLINE [1] gtInt16 #-} {-# INLINE [1] geInt16 #-} {-# INLINE [1] ltInt16 #-} {-# INLINE [1] leInt16 #-} gtInt16, geInt16, ltInt16, leInt16 :: Int16 -> Int16 -> Bool (I16# Int16# x) gtInt16 :: Int16 -> Int16 -> Bool `gtInt16` (I16# Int16# y) = Int# -> Bool isTrue# (Int16# x Int16# -> Int16# -> Int# `gtInt16#` Int16# y) (I16# Int16# x) geInt16 :: Int16 -> Int16 -> Bool `geInt16` (I16# Int16# y) = Int# -> Bool isTrue# (Int16# x Int16# -> Int16# -> Int# `geInt16#` Int16# y) (I16# Int16# x) ltInt16 :: Int16 -> Int16 -> Bool `ltInt16` (I16# Int16# y) = Int# -> Bool isTrue# (Int16# x Int16# -> Int16# -> Int# `ltInt16#` Int16# y) (I16# Int16# x) leInt16 :: Int16 -> Int16 -> Bool `leInt16` (I16# Int16# y) = Int# -> Bool isTrue# (Int16# x Int16# -> Int16# -> Int# `leInt16#` Int16# y) instance Show Int16 where showsPrec :: Int -> Int16 -> ShowS showsPrec Int p Int16 x = Int -> Int -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p (Int16 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int16 x :: Int) instance Num Int16 where (I16# Int16# x#) + :: Int16 -> Int16 -> Int16 + (I16# Int16# y#) = Int16# -> Int16 I16# (Int16# x# Int16# -> Int16# -> Int16# `plusInt16#` Int16# y#) (I16# Int16# x#) - :: Int16 -> Int16 -> Int16 - (I16# Int16# y#) = Int16# -> Int16 I16# (Int16# x# Int16# -> Int16# -> Int16# `subInt16#` Int16# y#) (I16# Int16# x#) * :: Int16 -> Int16 -> Int16 * (I16# Int16# y#) = Int16# -> Int16 I16# (Int16# x# Int16# -> Int16# -> Int16# `timesInt16#` Int16# y#) negate :: Int16 -> Int16 negate (I16# Int16# x#) = Int16# -> Int16 I16# (Int16# -> Int16# negateInt16# Int16# x#) abs :: Int16 -> Int16 abs Int16 x | Int16 x Int16 -> Int16 -> Bool forall a. Ord a => a -> a -> Bool >= Int16 0 = Int16 x | Bool otherwise = Int16 -> Int16 forall a. Num a => a -> a negate Int16 x signum :: Int16 -> Int16 signum Int16 x | Int16 x Int16 -> Int16 -> Bool forall a. Ord a => a -> a -> Bool > Int16 0 = Int16 1 signum Int16 0 = Int16 0 signum Int16 _ = Int16 -1 fromInteger :: Integer -> Int16 fromInteger Integer i = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# (Integer -> Int# integerToInt# Integer i)) instance Real Int16 where toRational :: Int16 -> Rational toRational Int16 x = Int16 -> Integer forall a. Integral a => a -> Integer toInteger Int16 x Integer -> Integer -> Rational forall a. Integral a => a -> a -> Ratio a % Integer 1 instance Enum Int16 where succ :: Int16 -> Int16 succ Int16 x | Int16 x Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool /= Int16 forall a. Bounded a => a maxBound = Int16 x Int16 -> Int16 -> Int16 forall a. Num a => a -> a -> a + Int16 1 | Bool otherwise = String -> Int16 forall a. String -> a succError String "Int16" pred :: Int16 -> Int16 pred Int16 x | Int16 x Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool /= Int16 forall a. Bounded a => a minBound = Int16 x Int16 -> Int16 -> Int16 forall a. Num a => a -> a -> a - Int16 1 | Bool otherwise = String -> Int16 forall a. String -> a predError String "Int16" toEnum :: Int -> Int16 toEnum i :: Int i@(I# Int# i#) | Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int16 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int16 forall a. Bounded a => a minBound::Int16) Bool -> Bool -> Bool && Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Int16 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int16 forall a. Bounded a => a maxBound::Int16) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# Int# i#) | Bool otherwise = String -> Int -> (Int16, Int16) -> Int16 forall a b. Show a => String -> Int -> (a, a) -> b toEnumError String "Int16" Int i (Int16 forall a. Bounded a => a minBound::Int16, Int16 forall a. Bounded a => a maxBound::Int16) fromEnum :: Int16 -> Int fromEnum (I16# Int16# x#) = Int# -> Int I# (Int16# -> Int# int16ToInt# Int16# x#) {-# INLINE enumFrom #-} enumFrom :: Int16 -> [Int16] enumFrom = Int16 -> [Int16] forall a. (Enum a, Bounded a) => a -> [a] boundedEnumFrom {-# INLINE enumFromThen #-} enumFromThen :: Int16 -> Int16 -> [Int16] enumFromThen = Int16 -> Int16 -> [Int16] forall a. (Enum a, Bounded a) => a -> a -> [a] boundedEnumFromThen instance Integral Int16 where quot :: Int16 -> Int16 -> Int16 quot x :: Int16 x@(I16# Int16# x#) y :: Int16 y@(I16# Int16# y#) | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 0 = Int16 forall a. a divZeroError | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == (Int16 -1) Bool -> Bool -> Bool && Int16 x Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 forall a. Bounded a => a minBound = Int16 forall a. a overflowError | Bool otherwise = Int16# -> Int16 I16# (Int16# x# Int16# -> Int16# -> Int16# `quotInt16#` Int16# y#) rem :: Int16 -> Int16 -> Int16 rem (I16# Int16# x#) y :: Int16 y@(I16# Int16# y#) | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 0 = Int16 forall a. a divZeroError | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == (Int16 -1) = Int16 0 | Bool otherwise = Int16# -> Int16 I16# (Int16# x# Int16# -> Int16# -> Int16# `remInt16#` Int16# y#) div :: Int16 -> Int16 -> Int16 div x :: Int16 x@(I16# Int16# x#) y :: Int16 y@(I16# Int16# y#) | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 0 = Int16 forall a. a divZeroError | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == (Int16 -1) Bool -> Bool -> Bool && Int16 x Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 forall a. Bounded a => a minBound = Int16 forall a. a overflowError | Bool otherwise = Int16# -> Int16 I16# (Int16# x# Int16# -> Int16# -> Int16# `divInt16#` Int16# y#) mod :: Int16 -> Int16 -> Int16 mod (I16# Int16# x#) y :: Int16 y@(I16# Int16# y#) | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 0 = Int16 forall a. a divZeroError | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == (Int16 -1) = Int16 0 | Bool otherwise = Int16# -> Int16 I16# (Int16# x# Int16# -> Int16# -> Int16# `modInt16#` Int16# y#) quotRem :: Int16 -> Int16 -> (Int16, Int16) quotRem x :: Int16 x@(I16# Int16# x#) y :: Int16 y@(I16# Int16# y#) | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 0 = (Int16, Int16) forall a. a divZeroError | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == (Int16 -1) Bool -> Bool -> Bool && Int16 x Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 forall a. Bounded a => a minBound = (Int16 forall a. a overflowError, Int16 0) | Bool otherwise = case Int16# x# Int16# -> Int16# -> (# Int16#, Int16# #) `quotRemInt16#` Int16# y# of (# Int16# q, Int16# r #) -> (Int16# -> Int16 I16# Int16# q, Int16# -> Int16 I16# Int16# r) divMod :: Int16 -> Int16 -> (Int16, Int16) divMod x :: Int16 x@(I16# Int16# x#) y :: Int16 y@(I16# Int16# y#) | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 0 = (Int16, Int16) forall a. a divZeroError | Int16 y Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == (Int16 -1) Bool -> Bool -> Bool && Int16 x Int16 -> Int16 -> Bool forall a. Eq a => a -> a -> Bool == Int16 forall a. Bounded a => a minBound = (Int16 forall a. a overflowError, Int16 0) | Bool otherwise = case Int16# x# Int16# -> Int16# -> (# Int16#, Int16# #) `divModInt16#` Int16# y# of (# Int16# d, Int16# m #) -> (Int16# -> Int16 I16# Int16# d, Int16# -> Int16 I16# Int16# m) toInteger :: Int16 -> Integer toInteger (I16# Int16# x#) = Int# -> Integer IS (Int16# -> Int# int16ToInt# Int16# x#) instance Bounded Int16 where minBound :: Int16 minBound = Int16 -0x8000 maxBound :: Int16 maxBound = Int16 0x7FFF instance Ix Int16 where range :: (Int16, Int16) -> [Int16] range (Int16 m,Int16 n) = [Int16 m..Int16 n] unsafeIndex :: (Int16, Int16) -> Int16 -> Int unsafeIndex (Int16 m,Int16 _) Int16 i = Int16 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int16 i Int -> Int -> Int forall a. Num a => a -> a -> a - Int16 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int16 m inRange :: (Int16, Int16) -> Int16 -> Bool inRange (Int16 m,Int16 n) Int16 i = Int16 m Int16 -> Int16 -> Bool forall a. Ord a => a -> a -> Bool <= Int16 i Bool -> Bool -> Bool && Int16 i Int16 -> Int16 -> Bool forall a. Ord a => a -> a -> Bool <= Int16 n instance Read Int16 where readsPrec :: Int -> ReadS Int16 readsPrec Int p String s = [(Int -> Int16 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int x::Int), String r) | (Int x, String r) <- Int -> ReadS Int forall a. Read a => Int -> ReadS a readsPrec Int p String s] instance Bits Int16 where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-} {-# INLINE popCount #-} (I16# Int16# x#) .&. :: Int16 -> Int16 -> Int16 .&. (I16# Int16# y#) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# ((Int16# -> Int# int16ToInt# Int16# x#) Int# -> Int# -> Int# `andI#` (Int16# -> Int# int16ToInt# Int16# y#))) (I16# Int16# x#) .|. :: Int16 -> Int16 -> Int16 .|. (I16# Int16# y#) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# ((Int16# -> Int# int16ToInt# Int16# x#) Int# -> Int# -> Int# `orI#` (Int16# -> Int# int16ToInt# Int16# y#))) (I16# Int16# x#) xor :: Int16 -> Int16 -> Int16 `xor` (I16# Int16# y#) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# ((Int16# -> Int# int16ToInt# Int16# x#) Int# -> Int# -> Int# `xorI#` (Int16# -> Int# int16ToInt# Int16# y#))) complement :: Int16 -> Int16 complement (I16# Int16# x#) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# (Int# -> Int# notI# (Int16# -> Int# int16ToInt# Int16# x#))) (I16# Int16# x#) shift :: Int16 -> Int -> Int16 `shift` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# ((Int16# -> Int# int16ToInt# Int16# x#) Int# -> Int# -> Int# `iShiftL#` Int# i#)) | Bool otherwise = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# ((Int16# -> Int# int16ToInt# Int16# x#) Int# -> Int# -> Int# `iShiftRA#` Int# -> Int# negateInt# Int# i#)) (I16# Int16# x#) shiftL :: Int16 -> Int -> Int16 `shiftL` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# ((Int16# -> Int# int16ToInt# Int16# x#) Int# -> Int# -> Int# `iShiftL#` Int# i#)) | Bool otherwise = Int16 forall a. a overflowError (I16# Int16# x#) unsafeShiftL :: Int16 -> Int -> Int16 `unsafeShiftL` (I# Int# i#) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# ((Int16# -> Int# int16ToInt# Int16# x#) Int# -> Int# -> Int# `uncheckedIShiftL#` Int# i#)) (I16# Int16# x#) shiftR :: Int16 -> Int -> Int16 `shiftR` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# ((Int16# -> Int# int16ToInt# Int16# x#) Int# -> Int# -> Int# `iShiftRA#` Int# i#)) | Bool otherwise = Int16 forall a. a overflowError (I16# Int16# x#) unsafeShiftR :: Int16 -> Int -> Int16 `unsafeShiftR` (I# Int# i#) = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# ((Int16# -> Int# int16ToInt# Int16# x#) Int# -> Int# -> Int# `uncheckedIShiftRA#` Int# i#)) (I16# Int16# x#) rotate :: Int16 -> Int -> Int16 `rotate` (I# Int# i#) | Int# -> Bool isTrue# (Int# i'# Int# -> Int# -> Int# ==# Int# 0#) = Int16# -> Int16 I16# Int16# x# | Bool otherwise = Int16# -> Int16 I16# (Int# -> Int16# intToInt16# (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# (Int16# -> Int# int16ToInt# Int16# x#)) !i'# :: Int# i'# = Word# -> Int# word2Int# (Int# -> Word# int2Word# Int# i# Word# -> Word# -> Word# `and#` Word# 15##) bitSizeMaybe :: Int16 -> Maybe Int bitSizeMaybe Int16 i = Int -> Maybe Int forall a. a -> Maybe a Just (Int16 -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int16 i) bitSize :: Int16 -> Int bitSize Int16 i = Int16 -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int16 i isSigned :: Int16 -> Bool isSigned Int16 _ = Bool True popCount :: Int16 -> Int popCount (I16# Int16# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# popCnt16# (Int# -> Word# int2Word# (Int16# -> Int# int16ToInt# Int16# x#)))) bit :: Int -> Int16 bit Int i = Int -> Int16 forall a. (Bits a, Num a) => Int -> a bitDefault Int i testBit :: Int16 -> Int -> Bool testBit Int16 a Int i = Int16 -> Int -> Bool forall a. (Bits a, Num a) => a -> Int -> Bool testBitDefault Int16 a Int i instance FiniteBits Int16 where {-# INLINE countLeadingZeros #-} {-# INLINE countTrailingZeros #-} finiteBitSize :: Int16 -> Int finiteBitSize Int16 _ = Int 16 countLeadingZeros :: Int16 -> Int countLeadingZeros (I16# Int16# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# clz16# (Int# -> Word# int2Word# (Int16# -> Int# int16ToInt# Int16# x#)))) countTrailingZeros :: Int16 -> Int countTrailingZeros (I16# Int16# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# ctz16# (Int# -> Word# int2Word# (Int16# -> Int# int16ToInt# Int16# 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) #-} data {-# CTYPE "HsInt32" #-} Int32 = I32# Int32# instance Eq Int32 where == :: Int32 -> Int32 -> Bool (==) = Int32 -> Int32 -> Bool eqInt32 /= :: Int32 -> Int32 -> Bool (/=) = Int32 -> Int32 -> Bool neInt32 eqInt32, neInt32 :: Int32 -> Int32 -> Bool eqInt32 :: Int32 -> Int32 -> Bool eqInt32 (I32# Int32# x) (I32# Int32# y) = Int# -> Bool isTrue# ((Int32# -> Int# int32ToInt# Int32# x) Int# -> Int# -> Int# ==# (Int32# -> Int# int32ToInt# Int32# y)) neInt32 :: Int32 -> Int32 -> Bool neInt32 (I32# Int32# x) (I32# Int32# y) = Int# -> Bool isTrue# ((Int32# -> Int# int32ToInt# Int32# x) Int# -> Int# -> Int# /=# (Int32# -> Int# int32ToInt# Int32# y)) {-# INLINE [1] eqInt32 #-} {-# INLINE [1] neInt32 #-} instance Ord Int32 where < :: Int32 -> Int32 -> Bool (<) = Int32 -> Int32 -> Bool ltInt32 <= :: Int32 -> Int32 -> Bool (<=) = Int32 -> Int32 -> Bool leInt32 >= :: Int32 -> Int32 -> Bool (>=) = Int32 -> Int32 -> Bool geInt32 > :: Int32 -> Int32 -> Bool (>) = Int32 -> Int32 -> Bool gtInt32 {-# INLINE [1] gtInt32 #-} {-# INLINE [1] geInt32 #-} {-# INLINE [1] ltInt32 #-} {-# INLINE [1] leInt32 #-} gtInt32, geInt32, ltInt32, leInt32 :: Int32 -> Int32 -> Bool (I32# Int32# x) gtInt32 :: Int32 -> Int32 -> Bool `gtInt32` (I32# Int32# y) = Int# -> Bool isTrue# (Int32# x Int32# -> Int32# -> Int# `gtInt32#` Int32# y) (I32# Int32# x) geInt32 :: Int32 -> Int32 -> Bool `geInt32` (I32# Int32# y) = Int# -> Bool isTrue# (Int32# x Int32# -> Int32# -> Int# `geInt32#` Int32# y) (I32# Int32# x) ltInt32 :: Int32 -> Int32 -> Bool `ltInt32` (I32# Int32# y) = Int# -> Bool isTrue# (Int32# x Int32# -> Int32# -> Int# `ltInt32#` Int32# y) (I32# Int32# x) leInt32 :: Int32 -> Int32 -> Bool `leInt32` (I32# Int32# y) = Int# -> Bool isTrue# (Int32# x Int32# -> Int32# -> Int# `leInt32#` Int32# y) instance Show Int32 where showsPrec :: Int -> Int32 -> ShowS showsPrec Int p Int32 x = Int -> Int -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p (Int32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int32 x :: Int) instance Num Int32 where (I32# Int32# x#) + :: Int32 -> Int32 -> Int32 + (I32# Int32# y#) = Int32# -> Int32 I32# (Int32# x# Int32# -> Int32# -> Int32# `plusInt32#` Int32# y#) (I32# Int32# x#) - :: Int32 -> Int32 -> Int32 - (I32# Int32# y#) = Int32# -> Int32 I32# (Int32# x# Int32# -> Int32# -> Int32# `subInt32#` Int32# y#) (I32# Int32# x#) * :: Int32 -> Int32 -> Int32 * (I32# Int32# y#) = Int32# -> Int32 I32# (Int32# x# Int32# -> Int32# -> Int32# `timesInt32#` Int32# y#) negate :: Int32 -> Int32 negate (I32# Int32# x#) = Int32# -> Int32 I32# (Int32# -> Int32# negateInt32# Int32# x#) abs :: Int32 -> Int32 abs Int32 x | Int32 x Int32 -> Int32 -> Bool forall a. Ord a => a -> a -> Bool >= Int32 0 = Int32 x | Bool otherwise = Int32 -> Int32 forall a. Num a => a -> a negate Int32 x signum :: Int32 -> Int32 signum Int32 x | Int32 x Int32 -> Int32 -> Bool forall a. Ord a => a -> a -> Bool > Int32 0 = Int32 1 signum Int32 0 = Int32 0 signum Int32 _ = Int32 -1 fromInteger :: Integer -> Int32 fromInteger Integer i = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# (Integer -> Int# integerToInt# Integer i)) instance Enum Int32 where succ :: Int32 -> Int32 succ Int32 x | Int32 x Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool /= Int32 forall a. Bounded a => a maxBound = Int32 x Int32 -> Int32 -> Int32 forall a. Num a => a -> a -> a + Int32 1 | Bool otherwise = String -> Int32 forall a. String -> a succError String "Int32" pred :: Int32 -> Int32 pred Int32 x | Int32 x Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool /= Int32 forall a. Bounded a => a minBound = Int32 x Int32 -> Int32 -> Int32 forall a. Num a => a -> a -> a - Int32 1 | Bool otherwise = String -> Int32 forall a. String -> a predError String "Int32" #if WORD_SIZE_IN_BITS == 32 toEnum (I# i#) = I32# (intToInt32# i#) #else toEnum :: Int -> Int32 toEnum i :: Int i@(I# Int# i#) | Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int32 forall a. Bounded a => a minBound::Int32) Bool -> Bool -> Bool && Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Int32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (Int32 forall a. Bounded a => a maxBound::Int32) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# Int# i#) | Bool otherwise = String -> Int -> (Int32, Int32) -> Int32 forall a b. Show a => String -> Int -> (a, a) -> b toEnumError String "Int32" Int i (Int32 forall a. Bounded a => a minBound::Int32, Int32 forall a. Bounded a => a maxBound::Int32) #endif fromEnum :: Int32 -> Int fromEnum (I32# Int32# x#) = Int# -> Int I# (Int32# -> Int# int32ToInt# Int32# x#) {-# INLINE enumFrom #-} enumFrom :: Int32 -> [Int32] enumFrom = Int32 -> [Int32] forall a. (Enum a, Bounded a) => a -> [a] boundedEnumFrom {-# INLINE enumFromThen #-} enumFromThen :: Int32 -> Int32 -> [Int32] enumFromThen = Int32 -> Int32 -> [Int32] forall a. (Enum a, Bounded a) => a -> a -> [a] boundedEnumFromThen instance Integral Int32 where quot :: Int32 -> Int32 -> Int32 quot x :: Int32 x@(I32# Int32# x#) y :: Int32 y@(I32# Int32# y#) | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 0 = Int32 forall a. a divZeroError | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == (Int32 -1) Bool -> Bool -> Bool && Int32 x Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 forall a. Bounded a => a minBound = Int32 forall a. a overflowError | Bool otherwise = Int32# -> Int32 I32# (Int32# x# Int32# -> Int32# -> Int32# `quotInt32#` Int32# y#) rem :: Int32 -> Int32 -> Int32 rem (I32# Int32# x#) y :: Int32 y@(I32# Int32# y#) | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 0 = Int32 forall a. a divZeroError | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == (Int32 -1) = Int32 0 | Bool otherwise = Int32# -> Int32 I32# (Int32# x# Int32# -> Int32# -> Int32# `remInt32#` Int32# y#) div :: Int32 -> Int32 -> Int32 div x :: Int32 x@(I32# Int32# x#) y :: Int32 y@(I32# Int32# y#) | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 0 = Int32 forall a. a divZeroError | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == (Int32 -1) Bool -> Bool -> Bool && Int32 x Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 forall a. Bounded a => a minBound = Int32 forall a. a overflowError | Bool otherwise = Int32# -> Int32 I32# (Int32# x# Int32# -> Int32# -> Int32# `divInt32#` Int32# y#) mod :: Int32 -> Int32 -> Int32 mod (I32# Int32# x#) y :: Int32 y@(I32# Int32# y#) | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 0 = Int32 forall a. a divZeroError | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == (Int32 -1) = Int32 0 | Bool otherwise = Int32# -> Int32 I32# (Int32# x# Int32# -> Int32# -> Int32# `modInt32#` Int32# y#) quotRem :: Int32 -> Int32 -> (Int32, Int32) quotRem x :: Int32 x@(I32# Int32# x#) y :: Int32 y@(I32# Int32# y#) | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 0 = (Int32, Int32) forall a. a divZeroError | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == (Int32 -1) Bool -> Bool -> Bool && Int32 x Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 forall a. Bounded a => a minBound = (Int32 forall a. a overflowError, Int32 0) | Bool otherwise = case Int32# x# Int32# -> Int32# -> (# Int32#, Int32# #) `quotRemInt32#` Int32# y# of (# Int32# q, Int32# r #) -> (Int32# -> Int32 I32# Int32# q, Int32# -> Int32 I32# Int32# r) divMod :: Int32 -> Int32 -> (Int32, Int32) divMod x :: Int32 x@(I32# Int32# x#) y :: Int32 y@(I32# Int32# y#) | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 0 = (Int32, Int32) forall a. a divZeroError | Int32 y Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == (Int32 -1) Bool -> Bool -> Bool && Int32 x Int32 -> Int32 -> Bool forall a. Eq a => a -> a -> Bool == Int32 forall a. Bounded a => a minBound = (Int32 forall a. a overflowError, Int32 0) | Bool otherwise = case Int32# x# Int32# -> Int32# -> (# Int32#, Int32# #) `divModInt32#` Int32# y# of (# Int32# d, Int32# m #) -> (Int32# -> Int32 I32# Int32# d, Int32# -> Int32 I32# Int32# m) toInteger :: Int32 -> Integer toInteger (I32# Int32# x#) = Int# -> Integer IS (Int32# -> Int# int32ToInt# Int32# x#) instance Read Int32 where readsPrec :: Int -> ReadS Int32 readsPrec Int p String s = [(Int -> Int32 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int x::Int), String r) | (Int x, String r) <- Int -> ReadS Int forall a. Read a => Int -> ReadS a readsPrec Int p String s] instance Bits Int32 where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-} {-# INLINE popCount #-} (I32# Int32# x#) .&. :: Int32 -> Int32 -> Int32 .&. (I32# Int32# y#) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# ((Int32# -> Int# int32ToInt# Int32# x#) Int# -> Int# -> Int# `andI#` (Int32# -> Int# int32ToInt# Int32# y#))) (I32# Int32# x#) .|. :: Int32 -> Int32 -> Int32 .|. (I32# Int32# y#) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# ((Int32# -> Int# int32ToInt# Int32# x#) Int# -> Int# -> Int# `orI#` (Int32# -> Int# int32ToInt# Int32# y#))) (I32# Int32# x#) xor :: Int32 -> Int32 -> Int32 `xor` (I32# Int32# y#) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# ((Int32# -> Int# int32ToInt# Int32# x#) Int# -> Int# -> Int# `xorI#` (Int32# -> Int# int32ToInt# Int32# y#))) complement :: Int32 -> Int32 complement (I32# Int32# x#) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# (Int# -> Int# notI# (Int32# -> Int# int32ToInt# Int32# x#))) (I32# Int32# x#) shift :: Int32 -> Int -> Int32 `shift` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# ((Int32# -> Int# int32ToInt# Int32# x#) Int# -> Int# -> Int# `iShiftL#` Int# i#)) | Bool otherwise = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# ((Int32# -> Int# int32ToInt# Int32# x#) Int# -> Int# -> Int# `iShiftRA#` Int# -> Int# negateInt# Int# i#)) (I32# Int32# x#) shiftL :: Int32 -> Int -> Int32 `shiftL` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# ((Int32# -> Int# int32ToInt# Int32# x#) Int# -> Int# -> Int# `iShiftL#` Int# i#)) | Bool otherwise = Int32 forall a. a overflowError (I32# Int32# x#) unsafeShiftL :: Int32 -> Int -> Int32 `unsafeShiftL` (I# Int# i#) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# ((Int32# -> Int# int32ToInt# Int32# x#) Int# -> Int# -> Int# `uncheckedIShiftL#` Int# i#)) (I32# Int32# x#) shiftR :: Int32 -> Int -> Int32 `shiftR` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# ((Int32# -> Int# int32ToInt# Int32# x#) Int# -> Int# -> Int# `iShiftRA#` Int# i#)) | Bool otherwise = Int32 forall a. a overflowError (I32# Int32# x#) unsafeShiftR :: Int32 -> Int -> Int32 `unsafeShiftR` (I# Int# i#) = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# ((Int32# -> Int# int32ToInt# Int32# x#) Int# -> Int# -> Int# `uncheckedIShiftRA#` Int# i#)) (I32# Int32# x#) rotate :: Int32 -> Int -> Int32 `rotate` (I# Int# i#) | Int# -> Bool isTrue# (Int# i'# Int# -> Int# -> Int# ==# Int# 0#) = Int32# -> Int32 I32# Int32# x# | Bool otherwise = Int32# -> Int32 I32# (Int# -> Int32# intToInt32# (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# (Int32# -> Int# int32ToInt# Int32# x#)) !i'# :: Int# i'# = Word# -> Int# word2Int# (Int# -> Word# int2Word# Int# i# Word# -> Word# -> Word# `and#` Word# 31##) bitSizeMaybe :: Int32 -> Maybe Int bitSizeMaybe Int32 i = Int -> Maybe Int forall a. a -> Maybe a Just (Int32 -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int32 i) bitSize :: Int32 -> Int bitSize Int32 i = Int32 -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int32 i isSigned :: Int32 -> Bool isSigned Int32 _ = Bool True popCount :: Int32 -> Int popCount (I32# Int32# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# popCnt32# (Int# -> Word# int2Word# (Int32# -> Int# int32ToInt# Int32# x#)))) bit :: Int -> Int32 bit Int i = Int -> Int32 forall a. (Bits a, Num a) => Int -> a bitDefault Int i testBit :: Int32 -> Int -> Bool testBit Int32 a Int i = Int32 -> Int -> Bool forall a. (Bits a, Num a) => a -> Int -> Bool testBitDefault Int32 a Int i instance FiniteBits Int32 where {-# INLINE countLeadingZeros #-} {-# INLINE countTrailingZeros #-} finiteBitSize :: Int32 -> Int finiteBitSize Int32 _ = Int 32 countLeadingZeros :: Int32 -> Int countLeadingZeros (I32# Int32# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# clz32# (Int# -> Word# int2Word# (Int32# -> Int# int32ToInt# Int32# x#)))) countTrailingZeros :: Int32 -> Int countTrailingZeros (I32# Int32# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# ctz32# (Int# -> Word# int2Word# (Int32# -> Int# int32ToInt# Int32# 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 :: Int32 -> Rational toRational Int32 x = Int32 -> Integer forall a. Integral a => a -> Integer toInteger Int32 x Integer -> Integer -> Rational forall a. Integral a => a -> a -> Ratio a % Integer 1 instance Bounded Int32 where minBound :: Int32 minBound = Int32 -0x80000000 maxBound :: Int32 maxBound = Int32 0x7FFFFFFF instance Ix Int32 where range :: (Int32, Int32) -> [Int32] range (Int32 m,Int32 n) = [Int32 m..Int32 n] unsafeIndex :: (Int32, Int32) -> Int32 -> Int unsafeIndex (Int32 m,Int32 _) Int32 i = Int32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int32 i Int -> Int -> Int forall a. Num a => a -> a -> a - Int32 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int32 m inRange :: (Int32, Int32) -> Int32 -> Bool inRange (Int32 m,Int32 n) Int32 i = Int32 m Int32 -> Int32 -> Bool forall a. Ord a => a -> a -> Bool <= Int32 i Bool -> Bool -> Bool && Int32 i Int32 -> Int32 -> Bool forall a. Ord a => a -> a -> Bool <= Int32 n data {-# CTYPE "HsInt64" #-} Int64 = I64# Int64# instance Eq Int64 where == :: Int64 -> Int64 -> Bool (==) = Int64 -> Int64 -> Bool eqInt64 /= :: Int64 -> Int64 -> Bool (/=) = Int64 -> Int64 -> Bool neInt64 eqInt64, neInt64 :: Int64 -> Int64 -> Bool eqInt64 :: Int64 -> Int64 -> Bool eqInt64 (I64# Int64# x) (I64# Int64# y) = Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `eqInt64#` Int64# y) neInt64 :: Int64 -> Int64 -> Bool neInt64 (I64# Int64# x) (I64# Int64# y) = Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `neInt64#` Int64# y) {-# INLINE [1] eqInt64 #-} {-# INLINE [1] neInt64 #-} instance Ord Int64 where < :: Int64 -> Int64 -> Bool (<) = Int64 -> Int64 -> Bool ltInt64 <= :: Int64 -> Int64 -> Bool (<=) = Int64 -> Int64 -> Bool leInt64 >= :: Int64 -> Int64 -> Bool (>=) = Int64 -> Int64 -> Bool geInt64 > :: Int64 -> Int64 -> Bool (>) = Int64 -> Int64 -> Bool gtInt64 {-# INLINE [1] gtInt64 #-} {-# INLINE [1] geInt64 #-} {-# INLINE [1] ltInt64 #-} {-# INLINE [1] leInt64 #-} gtInt64, geInt64, ltInt64, leInt64 :: Int64 -> Int64 -> Bool (I64# Int64# x) gtInt64 :: Int64 -> Int64 -> Bool `gtInt64` (I64# Int64# y) = Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `gtInt64#` Int64# y) (I64# Int64# x) geInt64 :: Int64 -> Int64 -> Bool `geInt64` (I64# Int64# y) = Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `geInt64#` Int64# y) (I64# Int64# x) ltInt64 :: Int64 -> Int64 -> Bool `ltInt64` (I64# Int64# y) = Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `ltInt64#` Int64# y) (I64# Int64# x) leInt64 :: Int64 -> Int64 -> Bool `leInt64` (I64# Int64# y) = Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `leInt64#` Int64# y) instance Show Int64 where showsPrec :: Int -> Int64 -> ShowS showsPrec Int p Int64 x = Int -> Integer -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p (Int64 -> Integer forall a. Integral a => a -> Integer toInteger Int64 x) instance Num Int64 where (I64# Int64# x#) + :: Int64 -> Int64 -> Int64 + (I64# Int64# y#) = Int64# -> Int64 I64# (Int64# x# Int64# -> Int64# -> Int64# `plusInt64#` Int64# y#) (I64# Int64# x#) - :: Int64 -> Int64 -> Int64 - (I64# Int64# y#) = Int64# -> Int64 I64# (Int64# x# Int64# -> Int64# -> Int64# `subInt64#` Int64# y#) (I64# Int64# x#) * :: Int64 -> Int64 -> Int64 * (I64# Int64# y#) = Int64# -> Int64 I64# (Int64# x# Int64# -> Int64# -> Int64# `timesInt64#` Int64# y#) negate :: Int64 -> Int64 negate (I64# Int64# x#) = Int64# -> Int64 I64# (Int64# -> Int64# negateInt64# Int64# x#) abs :: Int64 -> Int64 abs Int64 x | Int64 x Int64 -> Int64 -> Bool forall a. Ord a => a -> a -> Bool >= Int64 0 = Int64 x | Bool otherwise = Int64 -> Int64 forall a. Num a => a -> a negate Int64 x signum :: Int64 -> Int64 signum Int64 x | Int64 x Int64 -> Int64 -> Bool forall a. Ord a => a -> a -> Bool > Int64 0 = Int64 1 signum Int64 0 = Int64 0 signum Int64 _ = Int64 -1 fromInteger :: Integer -> Int64 fromInteger Integer i = Int64# -> Int64 I64# (Integer -> Int64# integerToInt64# Integer i) instance Enum Int64 where succ :: Int64 -> Int64 succ Int64 x | Int64 x Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool /= Int64 forall a. Bounded a => a maxBound = Int64 x Int64 -> Int64 -> Int64 forall a. Num a => a -> a -> a + Int64 1 | Bool otherwise = String -> Int64 forall a. String -> a succError String "Int64" pred :: Int64 -> Int64 pred Int64 x | Int64 x Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool /= Int64 forall a. Bounded a => a minBound = Int64 x Int64 -> Int64 -> Int64 forall a. Num a => a -> a -> a - Int64 1 | Bool otherwise = String -> Int64 forall a. String -> a predError String "Int64" toEnum :: Int -> Int64 toEnum (I# Int# i#) = Int64# -> Int64 I64# (Int# -> Int64# intToInt64# Int# i#) fromEnum :: Int64 -> Int fromEnum x :: Int64 x@(I64# Int64# x#) | Int64 x Int64 -> Int64 -> Bool forall a. Ord a => a -> a -> Bool >= Int -> Int64 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int forall a. Bounded a => a minBound::Int) Bool -> Bool -> Bool && Int64 x Int64 -> Int64 -> Bool forall a. Ord a => a -> a -> Bool <= Int -> Int64 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int forall a. Bounded a => a maxBound::Int) = Int# -> Int I# (Int64# -> Int# int64ToInt# Int64# x#) | Bool otherwise = String -> Int64 -> Int forall a b. Show a => String -> a -> b fromEnumError String "Int64" Int64 x {-# INLINE enumFrom #-} enumFrom :: Int64 -> [Int64] enumFrom (I64# Int64# x) = Int64# -> Int64# -> [Int64] eftInt64 Int64# x Int64# maxInt64# where !(I64# Int64# maxInt64#) = Int64 forall a. Bounded a => a maxBound {-# INLINE enumFromTo #-} enumFromTo :: Int64 -> Int64 -> [Int64] enumFromTo (I64# Int64# x) (I64# Int64# y) = Int64# -> Int64# -> [Int64] eftInt64 Int64# x Int64# y {-# INLINE enumFromThen #-} enumFromThen :: Int64 -> Int64 -> [Int64] enumFromThen (I64# Int64# x1) (I64# Int64# x2) = Int64# -> Int64# -> [Int64] efdInt64 Int64# x1 Int64# x2 {-# INLINE enumFromThenTo #-} enumFromThenTo :: Int64 -> Int64 -> Int64 -> [Int64] enumFromThenTo (I64# Int64# x1) (I64# Int64# x2) (I64# Int64# y) = Int64# -> Int64# -> Int64# -> [Int64] efdtInt64 Int64# x1 Int64# x2 Int64# y {-# RULES "eftInt64" [~1] forall x y. eftInt64 x y = build (\ c n -> eftInt64FB c n x y) "eftInt64List" [1] eftInt64FB (:) [] = eftInt64 #-} {-# NOINLINE [1] eftInt64 #-} eftInt64 :: Int64# -> Int64# -> [Int64] eftInt64 :: Int64# -> Int64# -> [Int64] eftInt64 Int64# x0 Int64# y | Int# -> Bool isTrue# (Int64# x0 Int64# -> Int64# -> Int# `gtInt64#` Int64# y) = [] | Bool otherwise = Int64# -> [Int64] go Int64# x0 where go :: Int64# -> [Int64] go Int64# x = Int64# -> Int64 I64# Int64# x Int64 -> [Int64] -> [Int64] forall a. a -> [a] -> [a] : if Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `eqInt64#` Int64# y) then [] else Int64# -> [Int64] go (Int64# x Int64# -> Int64# -> Int64# `plusInt64#` (Int# -> Int64# intToInt64# Int# 1#)) {-# INLINE [0] eftInt64FB #-} eftInt64FB :: (Int64 -> r -> r) -> r -> Int64# -> Int64# -> r eftInt64FB :: forall r. (Int64 -> r -> r) -> r -> Int64# -> Int64# -> r eftInt64FB Int64 -> r -> r c r n Int64# x0 Int64# y | Int# -> Bool isTrue# (Int64# x0 Int64# -> Int64# -> Int# `gtInt64#` Int64# y) = r n | Bool otherwise = Int64# -> r go Int64# x0 where go :: Int64# -> r go Int64# x = Int64# -> Int64 I64# Int64# x Int64 -> r -> r `c` if Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `eqInt64#` Int64# y) then r n else Int64# -> r go (Int64# x Int64# -> Int64# -> Int64# `plusInt64#` (Int# -> Int64# intToInt64# Int# 1#)) {-# RULES "efdtInt64" [~1] forall x1 x2 y. efdtInt64 x1 x2 y = build (\ c n -> efdtInt64FB c n x1 x2 y) "efdtInt64UpList" [1] efdtInt64FB (:) [] = efdtInt64 #-} efdInt64 :: Int64# -> Int64# -> [Int64] efdInt64 :: Int64# -> Int64# -> [Int64] efdInt64 Int64# x1 Int64# x2 | Int# -> Bool isTrue# (Int64# x2 Int64# -> Int64# -> Int# `geInt64#` Int64# x1) = case Int64 forall a. Bounded a => a maxBound of I64# Int64# y -> Int64# -> Int64# -> Int64# -> [Int64] efdtInt64Up Int64# x1 Int64# x2 Int64# y | Bool otherwise = case Int64 forall a. Bounded a => a minBound of I64# Int64# y -> Int64# -> Int64# -> Int64# -> [Int64] efdtInt64Dn Int64# x1 Int64# x2 Int64# y {-# NOINLINE [1] efdtInt64 #-} efdtInt64 :: Int64# -> Int64# -> Int64# -> [Int64] efdtInt64 :: Int64# -> Int64# -> Int64# -> [Int64] efdtInt64 Int64# x1 Int64# x2 Int64# y | Int# -> Bool isTrue# (Int64# x2 Int64# -> Int64# -> Int# `geInt64#` Int64# x1) = Int64# -> Int64# -> Int64# -> [Int64] efdtInt64Up Int64# x1 Int64# x2 Int64# y | Bool otherwise = Int64# -> Int64# -> Int64# -> [Int64] efdtInt64Dn Int64# x1 Int64# x2 Int64# y {-# INLINE [0] efdtInt64FB #-} efdtInt64FB :: (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r efdtInt64FB :: forall r. (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r efdtInt64FB Int64 -> r -> r c r n Int64# x1 Int64# x2 Int64# y | Int# -> Bool isTrue# (Int64# x2 Int64# -> Int64# -> Int# `geInt64#` Int64# x1) = (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r forall r. (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r efdtInt64UpFB Int64 -> r -> r c r n Int64# x1 Int64# x2 Int64# y | Bool otherwise = (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r forall r. (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r efdtInt64DnFB Int64 -> r -> r c r n Int64# x1 Int64# x2 Int64# y efdtInt64Up :: Int64# -> Int64# -> Int64# -> [Int64] efdtInt64Up :: Int64# -> Int64# -> Int64# -> [Int64] efdtInt64Up Int64# x1 Int64# x2 Int64# y | Int# -> Bool isTrue# (Int64# y Int64# -> Int64# -> Int# `ltInt64#` Int64# x2) = if Int# -> Bool isTrue# (Int64# y Int64# -> Int64# -> Int# `ltInt64#` Int64# x1) then [] else [Int64# -> Int64 I64# Int64# x1] | Bool otherwise = let !delta :: Int64# delta = Int64# x2 Int64# -> Int64# -> Int64# `subInt64#` Int64# x1 !y' :: Int64# y' = Int64# y Int64# -> Int64# -> Int64# `subInt64#` Int64# delta go_up :: Int64# -> [Int64] go_up Int64# x | Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `gtInt64#` Int64# y') = [Int64# -> Int64 I64# Int64# x] | Bool otherwise = Int64# -> Int64 I64# Int64# x Int64 -> [Int64] -> [Int64] forall a. a -> [a] -> [a] : Int64# -> [Int64] go_up (Int64# x Int64# -> Int64# -> Int64# `plusInt64#` Int64# delta) in Int64# -> Int64 I64# Int64# x1 Int64 -> [Int64] -> [Int64] forall a. a -> [a] -> [a] : Int64# -> [Int64] go_up Int64# x2 {-# INLINE [0] efdtInt64UpFB #-} efdtInt64UpFB :: (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r efdtInt64UpFB :: forall r. (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r efdtInt64UpFB Int64 -> r -> r c r n Int64# x1 Int64# x2 Int64# y | Int# -> Bool isTrue# (Int64# y Int64# -> Int64# -> Int# `ltInt64#` Int64# x2) = if Int# -> Bool isTrue# (Int64# y Int64# -> Int64# -> Int# `ltInt64#` Int64# x1) then r n else Int64# -> Int64 I64# Int64# x1 Int64 -> r -> r `c` r n | Bool otherwise = let !delta :: Int64# delta = Int64# x2 Int64# -> Int64# -> Int64# `subInt64#` Int64# x1 !y' :: Int64# y' = Int64# y Int64# -> Int64# -> Int64# `subInt64#` Int64# delta go_up :: Int64# -> r go_up Int64# x | Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `gtInt64#` Int64# y') = Int64# -> Int64 I64# Int64# x Int64 -> r -> r `c` r n | Bool otherwise = Int64# -> Int64 I64# Int64# x Int64 -> r -> r `c` Int64# -> r go_up (Int64# x Int64# -> Int64# -> Int64# `plusInt64#` Int64# delta) in Int64# -> Int64 I64# Int64# x1 Int64 -> r -> r `c` Int64# -> r go_up Int64# x2 efdtInt64Dn :: Int64# -> Int64# -> Int64# -> [Int64] efdtInt64Dn :: Int64# -> Int64# -> Int64# -> [Int64] efdtInt64Dn Int64# x1 Int64# x2 Int64# y | Int# -> Bool isTrue# (Int64# y Int64# -> Int64# -> Int# `gtInt64#` Int64# x2) = if Int# -> Bool isTrue# (Int64# y Int64# -> Int64# -> Int# `gtInt64#` Int64# x1) then [] else [Int64# -> Int64 I64# Int64# x1] | Bool otherwise = let !delta :: Int64# delta = Int64# x2 Int64# -> Int64# -> Int64# `subInt64#` Int64# x1 !y' :: Int64# y' = Int64# y Int64# -> Int64# -> Int64# `subInt64#` Int64# delta go_dn :: Int64# -> [Int64] go_dn Int64# x | Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `ltInt64#` Int64# y') = [Int64# -> Int64 I64# Int64# x] | Bool otherwise = Int64# -> Int64 I64# Int64# x Int64 -> [Int64] -> [Int64] forall a. a -> [a] -> [a] : Int64# -> [Int64] go_dn (Int64# x Int64# -> Int64# -> Int64# `plusInt64#` Int64# delta) in Int64# -> Int64 I64# Int64# x1 Int64 -> [Int64] -> [Int64] forall a. a -> [a] -> [a] : Int64# -> [Int64] go_dn Int64# x2 {-# INLINE [0] efdtInt64DnFB #-} efdtInt64DnFB :: (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r efdtInt64DnFB :: forall r. (Int64 -> r -> r) -> r -> Int64# -> Int64# -> Int64# -> r efdtInt64DnFB Int64 -> r -> r c r n Int64# x1 Int64# x2 Int64# y | Int# -> Bool isTrue# (Int64# y Int64# -> Int64# -> Int# `gtInt64#` Int64# x2) = if Int# -> Bool isTrue# (Int64# y Int64# -> Int64# -> Int# `gtInt64#` Int64# x1) then r n else Int64# -> Int64 I64# Int64# x1 Int64 -> r -> r `c` r n | Bool otherwise = let !delta :: Int64# delta = Int64# x2 Int64# -> Int64# -> Int64# `subInt64#` Int64# x1 !y' :: Int64# y' = Int64# y Int64# -> Int64# -> Int64# `subInt64#` Int64# delta go_dn :: Int64# -> r go_dn Int64# x | Int# -> Bool isTrue# (Int64# x Int64# -> Int64# -> Int# `ltInt64#` Int64# y') = Int64# -> Int64 I64# Int64# x Int64 -> r -> r `c` r n | Bool otherwise = Int64# -> Int64 I64# Int64# x Int64 -> r -> r `c` Int64# -> r go_dn (Int64# x Int64# -> Int64# -> Int64# `plusInt64#` Int64# delta) in Int64# -> Int64 I64# Int64# x1 Int64 -> r -> r `c` Int64# -> r go_dn Int64# x2 instance Integral Int64 where quot :: Int64 -> Int64 -> Int64 quot x :: Int64 x@(I64# Int64# x#) y :: Int64 y@(I64# Int64# y#) | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 0 = Int64 forall a. a divZeroError | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == (Int64 -1) Bool -> Bool -> Bool && Int64 x Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 forall a. Bounded a => a minBound = Int64 forall a. a overflowError | Bool otherwise = Int64# -> Int64 I64# (Int64# x# Int64# -> Int64# -> Int64# `quotInt64#` Int64# y#) rem :: Int64 -> Int64 -> Int64 rem (I64# Int64# x#) y :: Int64 y@(I64# Int64# y#) | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 0 = Int64 forall a. a divZeroError | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == (Int64 -1) = Int64 0 | Bool otherwise = Int64# -> Int64 I64# (Int64# x# Int64# -> Int64# -> Int64# `remInt64#` Int64# y#) div :: Int64 -> Int64 -> Int64 div x :: Int64 x@(I64# Int64# x#) y :: Int64 y@(I64# Int64# y#) | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 0 = Int64 forall a. a divZeroError | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == (Int64 -1) Bool -> Bool -> Bool && Int64 x Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 forall a. Bounded a => a minBound = Int64 forall a. a overflowError | Bool otherwise = Int64# -> Int64 I64# (Int64# x# Int64# -> Int64# -> Int64# `divInt64#` Int64# y#) mod :: Int64 -> Int64 -> Int64 mod (I64# Int64# x#) y :: Int64 y@(I64# Int64# y#) | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 0 = Int64 forall a. a divZeroError | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == (Int64 -1) = Int64 0 | Bool otherwise = Int64# -> Int64 I64# (Int64# x# Int64# -> Int64# -> Int64# `modInt64#` Int64# y#) quotRem :: Int64 -> Int64 -> (Int64, Int64) quotRem x :: Int64 x@(I64# Int64# x#) y :: Int64 y@(I64# Int64# y#) | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 0 = (Int64, Int64) forall a. a divZeroError | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == (Int64 -1) Bool -> Bool -> Bool && Int64 x Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 forall a. Bounded a => a minBound = (Int64 forall a. a overflowError, Int64 0) #if WORD_SIZE_IN_BITS < 64 | otherwise = (I64# (x# `quotInt64#` y#), I64# (x# `remInt64#` y#)) #else | Bool otherwise = case Int# -> Int# -> (# Int#, Int# #) quotRemInt# (Int64# -> Int# int64ToInt# Int64# x#) (Int64# -> Int# int64ToInt# Int64# y#) of (# Int# q, Int# r #) -> (Int64# -> Int64 I64# (Int# -> Int64# intToInt64# Int# q), Int64# -> Int64 I64# (Int# -> Int64# intToInt64# Int# r)) #endif divMod :: Int64 -> Int64 -> (Int64, Int64) divMod x :: Int64 x@(I64# Int64# x#) y :: Int64 y@(I64# Int64# y#) | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 0 = (Int64, Int64) forall a. a divZeroError | Int64 y Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == (Int64 -1) Bool -> Bool -> Bool && Int64 x Int64 -> Int64 -> Bool forall a. Eq a => a -> a -> Bool == Int64 forall a. Bounded a => a minBound = (Int64 forall a. a overflowError, Int64 0) #if WORD_SIZE_IN_BITS < 64 | otherwise = (I64# (x# `divInt64#` y#), I64# (x# `modInt64#` y#)) #else | Bool otherwise = case Int# -> Int# -> (# Int#, Int# #) divModInt# (Int64# -> Int# int64ToInt# Int64# x#) (Int64# -> Int# int64ToInt# Int64# y#) of (# Int# q, Int# r #) -> (Int64# -> Int64 I64# (Int# -> Int64# intToInt64# Int# q), Int64# -> Int64 I64# (Int# -> Int64# intToInt64# Int# r)) #endif toInteger :: Int64 -> Integer toInteger (I64# Int64# x) = Int64# -> Integer integerFromInt64# Int64# x divInt64#, modInt64# :: Int64# -> Int64# -> Int64# Int64# x# divInt64# :: Int64# -> Int64# -> Int64# `divInt64#` Int64# y# | Int# -> Bool isTrue# (Int64# x# Int64# -> Int64# -> Int# `gtInt64#` Int64# zero) Bool -> Bool -> Bool && Int# -> Bool isTrue# (Int64# y# Int64# -> Int64# -> Int# `ltInt64#` Int64# zero) = ((Int64# x# Int64# -> Int64# -> Int64# `subInt64#` Int64# one) Int64# -> Int64# -> Int64# `quotInt64#` Int64# y#) Int64# -> Int64# -> Int64# `subInt64#` Int64# one | Int# -> Bool isTrue# (Int64# x# Int64# -> Int64# -> Int# `ltInt64#` Int64# zero) Bool -> Bool -> Bool && Int# -> Bool isTrue# (Int64# y# Int64# -> Int64# -> Int# `gtInt64#` Int64# zero) = ((Int64# x# Int64# -> Int64# -> Int64# `plusInt64#` Int64# one) Int64# -> Int64# -> Int64# `quotInt64#` Int64# y#) Int64# -> Int64# -> Int64# `subInt64#` Int64# one | Bool otherwise = Int64# x# Int64# -> Int64# -> Int64# `quotInt64#` Int64# y# where !zero :: Int64# zero = Int# -> Int64# intToInt64# Int# 0# !one :: Int64# one = Int# -> Int64# intToInt64# Int# 1# Int64# x# modInt64# :: Int64# -> Int64# -> Int64# `modInt64#` Int64# y# | Int# -> Bool isTrue# (Int64# x# Int64# -> Int64# -> Int# `gtInt64#` Int64# zero) Bool -> Bool -> Bool && Int# -> Bool isTrue# (Int64# y# Int64# -> Int64# -> Int# `ltInt64#` Int64# zero) Bool -> Bool -> Bool || Int# -> Bool isTrue# (Int64# x# Int64# -> Int64# -> Int# `ltInt64#` Int64# zero) Bool -> Bool -> Bool && Int# -> Bool isTrue# (Int64# y# Int64# -> Int64# -> Int# `gtInt64#` Int64# zero) = if Int# -> Bool isTrue# (Int64# r# Int64# -> Int64# -> Int# `neInt64#` Int64# zero) then Int64# r# Int64# -> Int64# -> Int64# `plusInt64#` Int64# y# else Int64# zero | Bool otherwise = Int64# r# where !zero :: Int64# zero = Int# -> Int64# intToInt64# Int# 0# !r# :: Int64# r# = Int64# x# Int64# -> Int64# -> Int64# `remInt64#` Int64# y# instance Read Int64 where readsPrec :: Int -> ReadS Int64 readsPrec Int p String s = [(Integer -> Int64 forall a. Num a => Integer -> a fromInteger Integer x, String r) | (Integer x, String r) <- Int -> ReadS Integer forall a. Read a => Int -> ReadS a readsPrec Int p String s] instance Bits Int64 where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-} {-# INLINE popCount #-} (I64# Int64# x#) .&. :: Int64 -> Int64 -> Int64 .&. (I64# Int64# y#) = Int64# -> Int64 I64# (Word64# -> Int64# word64ToInt64# (Int64# -> Word64# int64ToWord64# Int64# x# Word64# -> Word64# -> Word64# `and64#` Int64# -> Word64# int64ToWord64# Int64# y#)) (I64# Int64# x#) .|. :: Int64 -> Int64 -> Int64 .|. (I64# Int64# y#) = Int64# -> Int64 I64# (Word64# -> Int64# word64ToInt64# (Int64# -> Word64# int64ToWord64# Int64# x# Word64# -> Word64# -> Word64# `or64#` Int64# -> Word64# int64ToWord64# Int64# y#)) (I64# Int64# x#) xor :: Int64 -> Int64 -> Int64 `xor` (I64# Int64# y#) = Int64# -> Int64 I64# (Word64# -> Int64# word64ToInt64# (Int64# -> Word64# int64ToWord64# Int64# x# Word64# -> Word64# -> Word64# `xor64#` Int64# -> Word64# int64ToWord64# Int64# y#)) complement :: Int64 -> Int64 complement (I64# Int64# x#) = Int64# -> Int64 I64# (Word64# -> Int64# word64ToInt64# (Word64# -> Word64# not64# (Int64# -> Word64# int64ToWord64# Int64# x#))) (I64# Int64# x#) shift :: Int64 -> Int -> Int64 `shift` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int64# -> Int64 I64# (Int64# x# Int64# -> Int# -> Int64# `shiftLInt64#` Int# i#) | Bool otherwise = Int64# -> Int64 I64# (Int64# x# Int64# -> Int# -> Int64# `shiftRAInt64#` Int# -> Int# negateInt# Int# i#) (I64# Int64# x#) shiftL :: Int64 -> Int -> Int64 `shiftL` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int64# -> Int64 I64# (Int64# x# Int64# -> Int# -> Int64# `shiftLInt64#` Int# i#) | Bool otherwise = Int64 forall a. a overflowError (I64# Int64# x#) unsafeShiftL :: Int64 -> Int -> Int64 `unsafeShiftL` (I# Int# i#) = Int64# -> Int64 I64# (Int64# x# Int64# -> Int# -> Int64# `uncheckedIShiftL64#` Int# i#) (I64# Int64# x#) shiftR :: Int64 -> Int -> Int64 `shiftR` (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int64# -> Int64 I64# (Int64# x# Int64# -> Int# -> Int64# `shiftRAInt64#` Int# i#) | Bool otherwise = Int64 forall a. a overflowError (I64# Int64# x#) unsafeShiftR :: Int64 -> Int -> Int64 `unsafeShiftR` (I# Int# i#) = Int64# -> Int64 I64# (Int64# x# Int64# -> Int# -> Int64# `uncheckedIShiftRA64#` Int# i#) (I64# Int64# x#) rotate :: Int64 -> Int -> Int64 `rotate` (I# Int# i#) | Int# -> Bool isTrue# (Int# i'# Int# -> Int# -> Int# ==# Int# 0#) = Int64# -> Int64 I64# Int64# x# | Bool otherwise = Int64# -> Int64 I64# (Word64# -> Int64# word64ToInt64# ((Word64# x'# Word64# -> Int# -> Word64# `uncheckedShiftL64#` Int# i'#) Word64# -> Word64# -> Word64# `or64#` (Word64# x'# Word64# -> Int# -> Word64# `uncheckedShiftRL64#` (Int# 64# Int# -> Int# -> Int# -# Int# i'#)))) where !x'# :: Word64# x'# = Int64# -> Word64# int64ToWord64# Int64# x# !i'# :: Int# i'# = Word# -> Int# word2Int# (Int# -> Word# int2Word# Int# i# Word# -> Word# -> Word# `and#` Word# 63##) bitSizeMaybe :: Int64 -> Maybe Int bitSizeMaybe Int64 i = Int -> Maybe Int forall a. a -> Maybe a Just (Int64 -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int64 i) bitSize :: Int64 -> Int bitSize Int64 i = Int64 -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int64 i isSigned :: Int64 -> Bool isSigned Int64 _ = Bool True popCount :: Int64 -> Int popCount (I64# Int64# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word64# -> Word# popCnt64# (Int64# -> Word64# int64ToWord64# Int64# x#))) bit :: Int -> Int64 bit Int i = Int -> Int64 forall a. (Bits a, Num a) => Int -> a bitDefault Int i testBit :: Int64 -> Int -> Bool testBit Int64 a Int i = Int64 -> Int -> Bool forall a. (Bits a, Num a) => a -> Int -> Bool testBitDefault Int64 a Int i #if WORD_SIZE_IN_BITS == 64 {-# 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) #-} #endif instance FiniteBits Int64 where {-# INLINE countLeadingZeros #-} {-# INLINE countTrailingZeros #-} finiteBitSize :: Int64 -> Int finiteBitSize Int64 _ = Int 64 countLeadingZeros :: Int64 -> Int countLeadingZeros (I64# Int64# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word64# -> Word# clz64# (Int64# -> Word64# int64ToWord64# Int64# x#))) countTrailingZeros :: Int64 -> Int countTrailingZeros (I64# Int64# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word64# -> Word# ctz64# (Int64# -> Word64# int64ToWord64# Int64# x#))) instance Real Int64 where toRational :: Int64 -> Rational toRational Int64 x = Int64 -> Integer forall a. Integral a => a -> Integer toInteger Int64 x Integer -> Integer -> Rational forall a. Integral a => a -> a -> Ratio a % Integer 1 instance Bounded Int64 where minBound :: Int64 minBound = Int64 -0x8000000000000000 maxBound :: Int64 maxBound = Int64 0x7FFFFFFFFFFFFFFF instance Ix Int64 where range :: (Int64, Int64) -> [Int64] range (Int64 m,Int64 n) = [Int64 m..Int64 n] unsafeIndex :: (Int64, Int64) -> Int64 -> Int unsafeIndex (Int64 m,Int64 _) Int64 i = Int64 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int64 i Int -> Int -> Int forall a. Num a => a -> a -> a - Int64 -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int64 m inRange :: (Int64, Int64) -> Int64 -> Bool inRange (Int64 m,Int64 n) Int64 i = Int64 m Int64 -> Int64 -> Bool forall a. Ord a => a -> a -> Bool <= Int64 i Bool -> Bool -> Bool && Int64 i Int64 -> Int64 -> Bool forall a. Ord a => a -> a -> Bool <= Int64 n shiftRLInt8# :: Int8# -> Int# -> Int8# Int8# a shiftRLInt8# :: Int8# -> Int# -> Int8# `shiftRLInt8#` Int# b = Int8# -> Int# -> Int8# uncheckedShiftRLInt8# Int8# a Int# b Int8# -> Int8# -> Int8# `andInt8#` Int# -> Int8# intToInt8# (Int# -> Int# -> Int# shift_mask Int# 8# Int# b) shiftRLInt16# :: Int16# -> Int# -> Int16# Int16# a shiftRLInt16# :: Int16# -> Int# -> Int16# `shiftRLInt16#` Int# b = Int16# -> Int# -> Int16# uncheckedShiftRLInt16# Int16# a Int# b Int16# -> Int16# -> Int16# `andInt16#` Int# -> Int16# intToInt16# (Int# -> Int# -> Int# shift_mask Int# 16# Int# b) shiftRLInt32# :: Int32# -> Int# -> Int32# Int32# a shiftRLInt32# :: Int32# -> Int# -> Int32# `shiftRLInt32#` Int# b = Int32# -> Int# -> Int32# uncheckedShiftRLInt32# Int32# a Int# b Int32# -> Int32# -> Int32# `andInt32#` Int# -> Int32# intToInt32# (Int# -> Int# -> Int# shift_mask Int# 32# Int# b) shiftLInt64# :: Int64# -> Int# -> Int64# Int64# a shiftLInt64# :: Int64# -> Int# -> Int64# `shiftLInt64#` Int# b = Int64# -> Int# -> Int64# uncheckedIShiftL64# Int64# a Int# b Int64# -> Int64# -> Int64# `andInt64#` Int# -> Int64# intToInt64# (Int# -> Int# -> Int# shift_mask Int# 64# Int# b) shiftRAInt64# :: Int64# -> Int# -> Int64# Int64# a shiftRAInt64# :: Int64# -> Int# -> Int64# `shiftRAInt64#` Int# b | Int# -> Bool isTrue# (Int# b Int# -> Int# -> Int# >=# Int# 64#) = Int# -> Int64# intToInt64# (Int# -> Int# negateInt# (Int64# a Int64# -> Int64# -> Int# `ltInt64#` (Int# -> Int64# intToInt64# Int# 0#))) | Bool otherwise = Int64# a Int64# -> Int# -> Int64# `uncheckedIShiftRA64#` Int# b andInt8# :: Int8# -> Int8# -> Int8# Int8# x andInt8# :: Int8# -> Int8# -> Int8# `andInt8#` Int8# y = Word8# -> Int8# word8ToInt8# (Int8# -> Word8# int8ToWord8# Int8# x Word8# -> Word8# -> Word8# `andWord8#` Int8# -> Word8# int8ToWord8# Int8# y) andInt16# :: Int16# -> Int16# -> Int16# Int16# x andInt16# :: Int16# -> Int16# -> Int16# `andInt16#` Int16# y = Word16# -> Int16# word16ToInt16# (Int16# -> Word16# int16ToWord16# Int16# x Word16# -> Word16# -> Word16# `andWord16#` Int16# -> Word16# int16ToWord16# Int16# y) andInt32# :: Int32# -> Int32# -> Int32# Int32# x andInt32# :: Int32# -> Int32# -> Int32# `andInt32#` Int32# y = Word32# -> Int32# word32ToInt32# (Int32# -> Word32# int32ToWord32# Int32# x Word32# -> Word32# -> Word32# `andWord32#` Int32# -> Word32# int32ToWord32# Int32# y) andInt64# :: Int64# -> Int64# -> Int64# Int64# x andInt64# :: Int64# -> Int64# -> Int64# `andInt64#` Int64# y = Word64# -> Int64# word64ToInt64# (Int64# -> Word64# int64ToWord64# Int64# x Word64# -> Word64# -> Word64# `and64#` Int64# -> Word64# int64ToWord64# Int64# y)
RetroSearch is an open source project built by @garambo | Open a GitHub Issue
Search and Browse the WWW like it's 1997 | Search results from DuckDuckGo
HTML:
3.2
| Encoding:
UTF-8
| Version:
0.7.4