{-# LANGUAGE Trustworthy #-}
module Relude.Numeric
(
module Data.Bits
, module Data.Int
, module Data.Word
, module GHC.Base
, module GHC.Float
, module GHC.Num
, module GHC.Real
, module Numeric.Natural
, integerToBounded
, integerToNatural
) where
import Data.Bits (toIntegralSized, xor)
import Data.Int (Int, Int16, Int32, Int64, Int8)
import Data.Word (Word, Word16, Word32, Word64, Word8, byteSwap16, byteSwap32, byteSwap64)
import GHC.Base (maxInt, minInt)
import GHC.Float (Double (..), Float (..), Floating (acos, acosh, asin, asinh, atan, atanh, cos, cosh, exp, logBase, pi, sin, sinh, sqrt, tan, tanh, (**)),
RealFloat (atan2, decodeFloat, encodeFloat, floatDigits, floatRadix, floatRange, isDenormalized, isIEEE, isInfinite, isNaN, isNegativeZero))
import GHC.Num (Integer, Num (..), subtract)
import GHC.Real (Fractional (..), Integral (..), Ratio, Rational, Real (..), RealFrac (..),
denominator, even, fromIntegral, gcd, lcm, numerator, odd, realToFrac, (^), (^^))
import Numeric.Natural (Natural)
import Relude.Base ((<), (>))
import Relude.Bool (otherwise)
import Relude.Enum (Bounded (..))
import Relude.Function (($))
import Relude.Monad (Maybe (..))
integerToBounded :: forall a. (Integral a, Bounded a) => Integer -> Maybe a
integerToBounded :: Integer -> Maybe a
integerToBounded Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< a -> Integer
forall a. Integral a => a -> Integer
toInteger (Bounded a => a
forall a. Bounded a => a
minBound @a) = Maybe a
forall a. Maybe a
Nothing
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> a -> Integer
forall a. Integral a => a -> Integer
toInteger (Bounded a => a
forall a. Bounded a => a
maxBound @a) = Maybe a
forall a. Maybe a
Nothing
| Bool
otherwise = a -> Maybe a
forall a. a -> Maybe a
Just (Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n)
{-# INLINE integerToBounded #-}
integerToNatural :: Integer -> Maybe Natural
integerToNatural :: Integer -> Maybe Natural
integerToNatural Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = Maybe Natural
forall a. Maybe a
Nothing
| Bool
otherwise = Natural -> Maybe Natural
forall a. a -> Maybe a
Just (Natural -> Maybe Natural) -> Natural -> Maybe Natural
forall a b. (a -> b) -> a -> b
$ Integer -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n
{-# INLINE integerToNatural #-}