{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NoImplicitPrelude #-}
#if !MIN_VERSION_base(4,8,0)
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
#endif
module Data.Int.Int24 (
Int24(..)
, narrow24Int#
) where
import Data.Bits
import Data.Data
import Data.Maybe
import Data.Word.Word24
import Foreign.Storable
import GHC.Arr
import GHC.Base
import GHC.Enum
import GHC.Int.Compat
import GHC.Integer (smallInteger, integerToInt)
import GHC.Num hiding (integerToInt)
import GHC.Ptr
import GHC.Read
import GHC.Real
import GHC.Show
import GHC.Word.Compat
import Control.DeepSeq
#if !MIN_VERSION_base(4,8,0)
import Data.Typeable
#endif
data Int24 = I24# Int# deriving (Int24 -> Int24 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Int24 -> Int24 -> Bool
$c/= :: Int24 -> Int24 -> Bool
== :: Int24 -> Int24 -> Bool
$c== :: Int24 -> Int24 -> Bool
Eq, Eq Int24
Int24 -> Int24 -> Bool
Int24 -> Int24 -> Ordering
Int24 -> Int24 -> Int24
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Int24 -> Int24 -> Int24
$cmin :: Int24 -> Int24 -> Int24
max :: Int24 -> Int24 -> Int24
$cmax :: Int24 -> Int24 -> Int24
>= :: Int24 -> Int24 -> Bool
$c>= :: Int24 -> Int24 -> Bool
> :: Int24 -> Int24 -> Bool
$c> :: Int24 -> Int24 -> Bool
<= :: Int24 -> Int24 -> Bool
$c<= :: Int24 -> Int24 -> Bool
< :: Int24 -> Int24 -> Bool
$c< :: Int24 -> Int24 -> Bool
compare :: Int24 -> Int24 -> Ordering
$ccompare :: Int24 -> Int24 -> Ordering
Ord)
#if !MIN_VERSION_base(4,8,0)
deriving instance Typeable Int24
#endif
instance NFData Int24 where rnf :: Int24 -> ()
rnf !Int24
_ = ()
int24Type :: DataType
int24Type :: DataType
int24Type = String -> DataType
mkIntType String
"Data.Word.Int24.Int24"
instance Data Int24 where
toConstr :: Int24 -> Constr
toConstr Int24
x = forall a. (Integral a, Show a) => DataType -> a -> Constr
mkIntegralConstr DataType
int24Type Int24
x
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Int24
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
z Constr
c = case Constr -> ConstrRep
constrRep Constr
c of
(IntConstr Integer
x) -> forall r. r -> c r
z (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x)
ConstrRep
_ -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Data.Data.gunfold: Constructor " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Constr
c
forall a. [a] -> [a] -> [a]
++ String
" is not of type Int24."
dataTypeOf :: Int24 -> DataType
dataTypeOf Int24
_ = DataType
int24Type
narrow24Int# :: Int# -> Int#
narrow24Int# :: Int# -> Int#
narrow24Int# Int#
x# = if Int# -> Bool
isTrue# ((Word#
x'# Word# -> Word# -> Word#
`and#` Word#
mask#) Word# -> Word# -> Int#
`eqWord#` Word#
mask#)
then Word# -> Int#
word2Int# (Word#
x'# Word# -> Word# -> Word#
`or#` Int# -> Word#
int2Word# Int#
m1#)
else Word# -> Int#
word2Int# (Word#
x'# Word# -> Word# -> Word#
`and#` Int# -> Word#
int2Word# Int#
m2#)
where
!x'# :: Word#
x'# = Int# -> Word#
int2Word# Int#
x#
!mask# :: Word#
mask# = Int# -> Word#
int2Word# Int#
0x00800000#
!(I# Int#
m1#) = -Int
8388608
!(I# Int#
m2#) = Int
16777215
instance Show Int24 where
showsPrec :: Int -> Int24 -> ShowS
showsPrec Int
p Int24
x = forall a. Show a => Int -> a -> ShowS
showsPrec Int
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int24
x :: Int)
instance Num Int24 where
(I24# Int#
x#) + :: Int24 -> Int24 -> Int24
+ (I24# Int#
y#) = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
+# Int#
y#))
(I24# Int#
x#) - :: Int24 -> Int24 -> Int24
- (I24# Int#
y#) = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
-# Int#
y#))
(I24# Int#
x#) * :: Int24 -> Int24 -> Int24
* (I24# Int#
y#) = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
*# Int#
y#))
negate :: Int24 -> Int24
negate (I24# Int#
x#) = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int# -> Int#
negateInt# Int#
x#))
abs :: Int24 -> Int24
abs Int24
x | Int24
x forall a. Ord a => a -> a -> Bool
>= Int24
0 = Int24
x
| Bool
otherwise = forall a. Num a => a -> a
negate Int24
x
signum :: Int24 -> Int24
signum Int24
x | Int24
x forall a. Ord a => a -> a -> Bool
> Int24
0 = Int24
1
signum Int24
0 = Int24
0
signum Int24
_ = -Int24
1
fromInteger :: Integer -> Int24
fromInteger Integer
i = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Integer -> Int#
integerToInt Integer
i))
instance Real Int24 where
toRational :: Int24 -> Rational
toRational Int24
x = forall a. Integral a => a -> Integer
toInteger Int24
x forall a. Integral a => a -> a -> Ratio a
% Integer
1
instance Enum Int24 where
succ :: Int24 -> Int24
succ Int24
x
| Int24
x forall a. Eq a => a -> a -> Bool
/= forall a. Bounded a => a
maxBound = Int24
x forall a. Num a => a -> a -> a
+ Int24
1
| Bool
otherwise = forall a. String -> a
succError String
"Int24"
pred :: Int24 -> Int24
pred Int24
x
| Int24
x forall a. Eq a => a -> a -> Bool
/= forall a. Bounded a => a
minBound = Int24
x forall a. Num a => a -> a -> a
- Int24
1
| Bool
otherwise = forall a. String -> a
predError String
"Int24"
toEnum :: Int -> Int24
toEnum i :: Int
i@(I# Int#
i#)
| Int
i forall a. Ord a => a -> a -> Bool
>= forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bounded a => a
minBound::Int24) Bool -> Bool -> Bool
&& Int
i forall a. Ord a => a -> a -> Bool
<= forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bounded a => a
maxBound::Int24)
= Int# -> Int24
I24# Int#
i#
| Bool
otherwise = forall a b. Show a => String -> Int -> (a, a) -> b
toEnumError String
"Int24" Int
i (forall a. Bounded a => a
minBound::Int24, forall a. Bounded a => a
maxBound::Int24)
fromEnum :: Int24 -> Int
fromEnum (I24# Int#
x#) = Int# -> Int
I# Int#
x#
enumFrom :: Int24 -> [Int24]
enumFrom = forall a. (Enum a, Bounded a) => a -> [a]
boundedEnumFrom
enumFromThen :: Int24 -> Int24 -> [Int24]
enumFromThen = forall a. (Enum a, Bounded a) => a -> a -> [a]
boundedEnumFromThen
instance Integral Int24 where
quot :: Int24 -> Int24 -> Int24
quot x :: Int24
x@(I24# Int#
x#) y :: Int24
y@(I24# Int#
y#)
| Int24
y forall a. Eq a => a -> a -> Bool
== Int24
0 = forall a. a
divZeroError
| Int24
x forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
minBound Bool -> Bool -> Bool
&& Int24
y forall a. Eq a => a -> a -> Bool
== (-Int24
1) = forall a. a
overflowError
| Bool
otherwise = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`quotInt#` Int#
y#))
rem :: Int24 -> Int24 -> Int24
rem x :: Int24
x@(I24# Int#
x#) y :: Int24
y@(I24# Int#
y#)
| Int24
y forall a. Eq a => a -> a -> Bool
== Int24
0 = forall a. a
divZeroError
| Int24
x forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
minBound Bool -> Bool -> Bool
&& Int24
y forall a. Eq a => a -> a -> Bool
== (-Int24
1) = forall a. a
overflowError
| Bool
otherwise = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`remInt#` Int#
y#))
div :: Int24 -> Int24 -> Int24
div x :: Int24
x@(I24# Int#
x#) y :: Int24
y@(I24# Int#
y#)
| Int24
y forall a. Eq a => a -> a -> Bool
== Int24
0 = forall a. a
divZeroError
| Int24
x forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
minBound Bool -> Bool -> Bool
&& Int24
y forall a. Eq a => a -> a -> Bool
== (-Int24
1) = forall a. a
overflowError
| Bool
otherwise = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`divInt#` Int#
y#))
mod :: Int24 -> Int24 -> Int24
mod x :: Int24
x@(I24# Int#
x#) y :: Int24
y@(I24# Int#
y#)
| Int24
y forall a. Eq a => a -> a -> Bool
== Int24
0 = forall a. a
divZeroError
| Int24
x forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
minBound Bool -> Bool -> Bool
&& Int24
y forall a. Eq a => a -> a -> Bool
== (-Int24
1) = forall a. a
overflowError
| Bool
otherwise = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`modInt#` Int#
y#))
quotRem :: Int24 -> Int24 -> (Int24, Int24)
quotRem x :: Int24
x@(I24# Int#
x#) y :: Int24
y@(I24# Int#
y#)
| Int24
y forall a. Eq a => a -> a -> Bool
== Int24
0 = forall a. a
divZeroError
| Int24
x forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
minBound Bool -> Bool -> Bool
&& Int24
y forall a. Eq a => a -> a -> Bool
== (-Int24
1) = forall a. a
overflowError
| Bool
otherwise = (Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`quotInt#` Int#
y#)),
Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`remInt#` Int#
y#)))
divMod :: Int24 -> Int24 -> (Int24, Int24)
divMod x :: Int24
x@(I24# Int#
x#) y :: Int24
y@(I24# Int#
y#)
| Int24
y forall a. Eq a => a -> a -> Bool
== Int24
0 = forall a. a
divZeroError
| Int24
x forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
minBound Bool -> Bool -> Bool
&& Int24
y forall a. Eq a => a -> a -> Bool
== (-Int24
1) = forall a. a
overflowError
| Bool
otherwise = (Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`divInt#` Int#
y#)),
Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`modInt#` Int#
y#)))
toInteger :: Int24 -> Integer
toInteger (I24# Int#
x#) = Int# -> Integer
smallInteger Int#
x#
instance Bounded Int24 where
minBound :: Int24
minBound = -Int24
0x800000
maxBound :: Int24
maxBound = Int24
0x7FFFFF
instance Ix Int24 where
range :: (Int24, Int24) -> [Int24]
range (Int24
m,Int24
n) = [Int24
m..Int24
n]
unsafeIndex :: (Int24, Int24) -> Int24 -> Int
unsafeIndex (Int24
m,Int24
_) Int24
i = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int24
i forall a. Num a => a -> a -> a
- forall a b. (Integral a, Num b) => a -> b
fromIntegral Int24
m
inRange :: (Int24, Int24) -> Int24 -> Bool
inRange (Int24
m,Int24
n) Int24
i = Int24
m forall a. Ord a => a -> a -> Bool
<= Int24
i Bool -> Bool -> Bool
&& Int24
i forall a. Ord a => a -> a -> Bool
<= Int24
n
instance Read Int24 where
readsPrec :: Int -> ReadS Int24
readsPrec Int
p String
s = [(forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
x::Int), String
r) | (Int
x, String
r) <- forall a. Read a => Int -> ReadS a
readsPrec Int
p String
s]
instance Bits Int24 where
{-# INLINE shift #-}
{-# INLINE bit #-}
{-# INLINE testBit #-}
(I24# Int#
x#) .&. :: Int24 -> Int24 -> Int24
.&. (I24# Int#
y#) = Int# -> Int24
I24# (Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
x# Word# -> Word# -> Word#
`and#` Int# -> Word#
int2Word# Int#
y#))
(I24# Int#
x#) .|. :: Int24 -> Int24 -> Int24
.|. (I24# Int#
y#) = Int# -> Int24
I24# (Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
x# Word# -> Word# -> Word#
`or#` Int# -> Word#
int2Word# Int#
y#))
(I24# Int#
x#) xor :: Int24 -> Int24 -> Int24
`xor` (I24# Int#
y#) = Int# -> Int24
I24# (Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
x# Word# -> Word# -> Word#
`xor#` Int# -> Word#
int2Word# Int#
y#))
complement :: Int24 -> Int24
complement (I24# Int#
x#) = Int# -> Int24
I24# (Word# -> Int#
word2Int# (Word# -> Word#
not# (Int# -> Word#
int2Word# Int#
x#)))
(I24# Int#
x#) shift :: Int24 -> Int -> Int24
`shift` (I# Int#
i#)
| Int# -> Bool
isTrue# (Int#
i# Int# -> Int# -> Int#
>=# Int#
0#) = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`iShiftL#` Int#
i#))
| Bool
otherwise = Int# -> Int24
I24# (Int#
x# Int# -> Int# -> Int#
`iShiftRA#` Int# -> Int#
negateInt# Int#
i#)
(I24# Int#
x#) shiftL :: Int24 -> Int -> Int24
`shiftL` (I# Int#
i#) = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`iShiftL#` Int#
i#))
(I24# Int#
x#) unsafeShiftL :: Int24 -> Int -> Int24
`unsafeShiftL` (I# Int#
i#) = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Int#
x# Int# -> Int# -> Int#
`uncheckedIShiftL#` Int#
i#))
(I24# Int#
x#) shiftR :: Int24 -> Int -> Int24
`shiftR` (I# Int#
i#) = Int# -> Int24
I24# (Int#
x# Int# -> Int# -> Int#
`iShiftRA#` Int#
i#)
(I24# Int#
x#) unsafeShiftR :: Int24 -> Int -> Int24
`unsafeShiftR` (I# Int#
i#) = Int# -> Int24
I24# (Int#
x# Int# -> Int# -> Int#
`uncheckedIShiftRA#` Int#
i#)
(I24# Int#
x#) rotate :: Int24 -> Int -> Int24
`rotate` Int
i
| Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# Int#
0#) = Int# -> Int24
I24# Int#
x#
| Bool
otherwise = Int# -> Int24
I24# (Int# -> Int#
narrow24Int# (Word# -> Int#
word2Int# ((Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
(Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftRL#` (Int#
24# Int# -> Int# -> Int#
-# Int#
i'#)))))
where
!x'# :: Word#
x'# = Word# -> Word#
narrow24Word# (Int# -> Word#
int2Word# Int#
x#)
!(I# Int#
i'#) = Int
i forall a. Integral a => a -> a -> a
`mod` Int
24
bitSizeMaybe :: Int24 -> Maybe Int
bitSizeMaybe Int24
i = forall a. a -> Maybe a
Just (forall b. FiniteBits b => b -> Int
finiteBitSize Int24
i)
bitSize :: Int24 -> Int
bitSize = forall b. FiniteBits b => b -> Int
finiteBitSize
isSigned :: Int24 -> Bool
isSigned Int24
_ = Bool
True
popCount :: Int24 -> Int
popCount (I24# Int#
x#) = Int# -> Int
I# (Word# -> Int#
word2Int# (Word# -> Word#
popCnt24# (Int# -> Word#
int2Word# Int#
x#)))
bit :: Int -> Int24
bit = forall a. (Bits a, Num a) => Int -> a
bitDefault
testBit :: Int24 -> Int -> Bool
testBit = forall a. (Bits a, Num a) => a -> Int -> Bool
testBitDefault
instance FiniteBits Int24 where
finiteBitSize :: Int24 -> Int
finiteBitSize Int24
_ = Int
24
#if MIN_VERSION_base(4,8,0)
countLeadingZeros :: Int24 -> Int
countLeadingZeros (I24# Int#
x#) = Int# -> Int
I# (Word# -> Int#
word2Int# (Word# -> Word#
clz24# (Int# -> Word#
int2Word# Int#
x#)))
countTrailingZeros :: Int24 -> Int
countTrailingZeros (I24# Int#
x#) = Int# -> Int
I# (Word# -> Int#
word2Int# (Word# -> Word#
ctz24# (Int# -> Word#
int2Word# Int#
x#)))
#endif
{-# RULES
"fromIntegral/Word8->Int24" fromIntegral = \(W8# x#) -> I24# (word2Int# x#)
"fromIntegral/Word16->Int24" fromIntegral = \(W16# x#) -> I24# (word2Int# x#)
"fromIntegral/Int8->Int24" fromIntegral = \(I8# x#) -> I24# x#
"fromIntegral/Int16->Int24" fromIntegral = \(I16# x#) -> I24# x#
"fromIntegral/Int24->Int24" fromIntegral = id :: Int24 -> Int24
"fromIntegral/a->Int24" fromIntegral = \x -> case fromIntegral x of I# x# -> I24# (narrow24Int# x#)
"fromIntegral/Int24->a" fromIntegral = \(I24# x#) -> fromIntegral (I# x#)
#-}
{-# RULES
"properFraction/Float->(Int24,Float)"
properFraction = \x ->
case properFraction x of {
(n, y) -> ((fromIntegral :: Int -> Int24) n, y :: Float) }
"truncate/Float->Int24"
truncate = (fromIntegral :: Int -> Int24) . (truncate :: Float -> Int)
"floor/Float->Int24"
floor = (fromIntegral :: Int -> Int24) . (floor :: Float -> Int)
"ceiling/Float->Int24"
ceiling = (fromIntegral :: Int -> Int24) . (ceiling :: Float -> Int)
"round/Float->Int24"
round = (fromIntegral :: Int -> Int24) . (round :: Float -> Int)
#-}
{-# RULES
"properFraction/Double->(Int24,Double)"
properFraction = \x ->
case properFraction x of {
(n, y) -> ((fromIntegral :: Int -> Int24) n, y :: Double) }
"truncate/Double->Int24"
truncate = (fromIntegral :: Int -> Int24) . (truncate :: Double -> Int)
"floor/Double->Int24"
floor = (fromIntegral :: Int -> Int24) . (floor :: Double -> Int)
"ceiling/Double->Int24"
ceiling = (fromIntegral :: Int -> Int24) . (ceiling :: Double -> Int)
"round/Double->Int24"
round = (fromIntegral :: Int -> Int24) . (round :: Double -> Int)
#-}
instance Storable Int24 where
sizeOf :: Int24 -> Int
sizeOf Int24
_ = Int
3
alignment :: Int24 -> Int
alignment Int24
_ = Int
3
peek :: Ptr Int24 -> IO Int24
peek Ptr Int24
p = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek ((forall a b. Ptr a -> Ptr b
castPtr Ptr Int24
p) :: Ptr Word24)
poke :: Ptr Int24 -> Int24 -> IO ()
poke Ptr Int24
p Int24
v = forall a. Storable a => Ptr a -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr Ptr Int24
p :: Ptr Word24) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int24
v)