-- |
-- Module:      Math.NumberTheory.Utils.FromIntegral
-- Copyright:   (c) 2017 Andrew Lelechenko
-- Licence:     MIT
-- Maintainer:  Andrew Lelechenko <andrew.lelechenko@gmail.com>
--
-- Monomorphic `fromIntegral`.
--

{-# LANGUAGE CPP #-}

module Math.NumberTheory.Utils.FromIntegral
  ( wordToInt
  , wordToInteger
  , intToWord
  , intToInt8
  , intToInt64
  , int8ToInt64
  , intToWord8
  , intToWord64
  , int8ToInt
  , int64ToInt
  , word8ToInt
  , word64ToInt
  , intToInteger
  , int16ToInteger
  , int64ToInteger
  , word64ToInteger
  , naturalToInteger
  , integerToNatural
  , integerToWord
  , integerToWord64
  , integerToInt
  , integerToInt64
  , intToNatural
  , naturalToInt
  , intToDouble
  , fromIntegral'
  ) where

import Data.Int
import Data.Word
import Numeric.Natural

wordToInt :: Word -> Int
wordToInt :: Word -> Int
wordToInt = Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE wordToInt #-}

wordToInteger :: Word -> Integer
wordToInteger :: Word -> Integer
wordToInteger = Word -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE wordToInteger #-}

intToWord :: Int -> Word
intToWord :: Int -> Word
intToWord = Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE intToWord #-}

intToInt8 :: Int -> Int8
intToInt8 :: Int -> Int8
intToInt8 = Int -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE intToInt8 #-}

intToInt64 :: Int -> Int64
intToInt64 :: Int -> Int64
intToInt64 = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE intToInt64 #-}

int8ToInt64 :: Int8 -> Int64
int8ToInt64 :: Int8 -> Int64
int8ToInt64 = Int8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE int8ToInt64 #-}

intToWord8 :: Int -> Word8
intToWord8 :: Int -> Word8
intToWord8 = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE intToWord8 #-}

intToWord64 :: Int -> Word64
intToWord64 :: Int -> Word64
intToWord64 = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE intToWord64 #-}

int8ToInt :: Int8 -> Int
int8ToInt :: Int8 -> Int
int8ToInt = Int8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE int8ToInt #-}

int64ToInt :: Int64 -> Int
int64ToInt :: Int64 -> Int
int64ToInt = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE int64ToInt #-}

word8ToInt :: Word8 -> Int
word8ToInt :: Word8 -> Int
word8ToInt = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE word8ToInt #-}

word64ToInt :: Word64 -> Int
word64ToInt :: Word64 -> Int
word64ToInt = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE word64ToInt #-}

intToInteger :: Int -> Integer
intToInteger :: Int -> Integer
intToInteger = Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE intToInteger #-}

int16ToInteger :: Int16 -> Integer
int16ToInteger :: Int16 -> Integer
int16ToInteger = Int16 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE int16ToInteger #-}

int64ToInteger :: Int64 -> Integer
int64ToInteger :: Int64 -> Integer
int64ToInteger = Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE int64ToInteger #-}

word64ToInteger :: Word64 -> Integer
word64ToInteger :: Word64 -> Integer
word64ToInteger = Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE word64ToInteger #-}

naturalToInteger :: Natural -> Integer
naturalToInteger :: Natural -> Integer
naturalToInteger = Natural -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE naturalToInteger #-}

integerToNatural :: Integer -> Natural
integerToNatural :: Integer -> Natural
integerToNatural = Integer -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral'
{-# INLINE integerToNatural #-}

integerToWord :: Integer -> Word
integerToWord :: Integer -> Word
integerToWord = Integer -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE integerToWord #-}

integerToWord64 :: Integer -> Word64
integerToWord64 :: Integer -> Word64
integerToWord64 = Integer -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE integerToWord64 #-}

integerToInt :: Integer -> Int
integerToInt :: Integer -> Int
integerToInt = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE integerToInt #-}

integerToInt64 :: Integer -> Int64
integerToInt64 :: Integer -> Int64
integerToInt64 = Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE integerToInt64 #-}

intToNatural :: Int -> Natural
intToNatural :: Int -> Natural
intToNatural = Int -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE intToNatural #-}

naturalToInt :: Natural -> Int
naturalToInt :: Natural -> Int
naturalToInt = Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE naturalToInt #-}

intToDouble :: Int -> Double
intToDouble :: Int -> Double
intToDouble = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE intToDouble #-}

fromIntegral' :: (Integral a, Num b) => a -> b
#if __GLASGOW_HASKELL__ == 900 && __GLASGOW_HASKELL_PATCHLEVEL1__ == 1
-- Cannot use fromIntegral because of https://gitlab.haskell.org/ghc/ghc/-/issues/19411
fromIntegral' = fromInteger . toInteger
#else
fromIntegral' :: a -> b
fromIntegral' = a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral
#endif
{-# INLINE fromIntegral' #-}