{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Math.Extras.Int (
saturatedFromInteger
, saturatedAdd
, saturatedSubtract
, saturatedMultiply
, saturatedPow
, toBinaryString
) where
import Data.Bits (Bits(..), FiniteBits(..))
import Data.List.NonEmpty (NonEmpty, nonEmpty)
import Data.Maybe (fromMaybe)
saturatedFromInteger :: forall a. (Integral a, Bounded a) => Integer -> a
saturatedFromInteger x
| x > toInteger (maxBound @a) = maxBound
| x < toInteger (minBound @a) = minBound
| otherwise = fromInteger x
saturatedAdd :: (Integral a, Bounded a) => a -> a -> a
saturatedAdd x y = saturatedFromInteger (toInteger x + toInteger y)
saturatedSubtract :: (Integral a, Bounded a) => a -> a -> a
saturatedSubtract x y = saturatedFromInteger (toInteger x - toInteger y)
saturatedMultiply :: (Integral a, Bounded a) => a -> a -> a
saturatedMultiply x y = saturatedFromInteger (toInteger x * toInteger y)
saturatedPow :: Int -> Int -> Int
saturatedPow _ b | b < 0 = error "Negative exponent"
saturatedPow 0 0 = 1
saturatedPow 0 _ = 0
saturatedPow 1 _ = 1
saturatedPow (-1) b = if even b then 1 else -1
saturatedPow 2 b
| b >= finiteBitSize (0 :: Int) - 1 = maxBound
| otherwise = unsafeShiftL 1 b
saturatedPow (-2) b
| b >= finiteBitSize (0 :: Int) = if even b then maxBound else minBound
| otherwise = unsafeShiftL (if even b then 1 else -1) b
saturatedPow a b = go a b 1
where
bound = if a < 0 && odd b then minBound else maxBound
sqrtMaxBound = floor . sqrt @Double . fromIntegral $ maxBound @Int
go a b acc
| b == 0 = acc
| b == 1 = saturatedMultiply acc a
| a > sqrtMaxBound || a < -sqrtMaxBound = bound
| otherwise =
let acc' = if even b then acc else saturatedMultiply acc a
in go (a * a) (b `div` 2) acc'
toBinaryString :: FiniteBits b => b -> NonEmpty Char
toBinaryString b = f <$> fromMaybe (pure 0) (nonEmpty [len-1, len-2 .. 0])
where
len = finiteBitSize b - countLeadingZeros b
f i = if testBit b i then '1' else '0'