{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Safe.Numeric
(
NumExpand(..)
, NumConvert(..)
, Word29_
, Int29_
, (+@)
, (+%)
, (+:)
, (+!)
, (-@)
, (-%)
, (-:)
, (-!)
, (*@)
, (*%)
, (*:)
, (*!)
, (^@)
, (^%)
, (^:)
, (^!)
, DivResult
, divE
, divX
, modE
, modX
, divModE
, divModX
, quotE
, quotX
, remE
, remX
, quotRemE
, quotRemX
) where
import Control.Exception (ArithException (..))
import Data.Int
import Data.WideWord
import Data.Word
import Safe.Partial (Partial)
class NumExpand b a where
ex :: b -> a
default ex :: (Num a, Integral b) => b -> a
ex = b -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE ex #-}
checkE
:: forall a . (Integral a, Bounded a) => Integer -> Either ArithException a
checkE :: Integer -> Either ArithException a
checkE Integer
v | Integer
v Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
minBound :: a) = ArithException -> Either ArithException a
forall a b. a -> Either a b
Left ArithException
Underflow
| Integer
v Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
maxBound :: a) = ArithException -> Either ArithException a
forall a b. a -> Either a b
Left ArithException
Overflow
| Bool
otherwise = a -> Either ArithException a
forall a b. b -> Either a b
Right (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
v)
{-# INLINE checkE #-}
checkS :: forall a . (Integral a, Bounded a) => Integer -> a
checkS :: Integer -> a
checkS Integer
v | Integer
v Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
minBound :: a) = a
forall a. Bounded a => a
minBound
| Integer
v Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
maxBound :: a) = a
forall a. Bounded a => a
maxBound
| Bool
otherwise = Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
v
{-# INLINE checkS #-}
checkX :: forall a . (Integral a, Bounded a) => Partial => Integer -> a
checkX :: Integer -> a
checkX Integer
v | Integer
v Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
minBound :: a) = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"Underflow"
| Integer
v Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
maxBound :: a) = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"Overflow"
| Bool
otherwise = Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
v
{-# INLINE checkX #-}
class NumConvert b a where
ctW :: b -> a
default ctW :: (Num a, Integral b) => b -> a
ctW b
b = b -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral b
b
{-# INLINE ctW #-}
ctE :: b -> Either ArithException a
default ctE :: (Integral a, Bounded a, Integral b) => b -> Either ArithException a
ctE = Integer -> Either ArithException a
forall a.
(Integral a, Bounded a) =>
Integer -> Either ArithException a
checkE (Integer -> Either ArithException a)
-> (b -> Integer) -> b -> Either ArithException a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Integer
forall a. Integral a => a -> Integer
toInteger
{-# INLINE ctE #-}
ctS :: b -> a
default ctS :: (Integral a, Bounded a, Integral b) => b -> a
ctS = Integer -> a
forall a. (Integral a, Bounded a) => Integer -> a
checkS (Integer -> a) -> (b -> Integer) -> b -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Integer
forall a. Integral a => a -> Integer
toInteger
{-# INLINE ctS #-}
ctX :: Partial => b -> a
default ctX :: (Integral a, Bounded a, Integral b) => Partial => b -> a
ctX = Integer -> a
forall a. (Integral a, Bounded a, HasCallStack) => Integer -> a
checkX (Integer -> a) -> (b -> Integer) -> b -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Integer
forall a. Integral a => a -> Integer
toInteger
{-# INLINE ctX #-}
type Word29_ = Word
type Int29_ = Int
instance NumExpand Word8 Word8
instance NumExpand Word8 Word16
instance NumExpand Word8 Word29_
instance NumExpand Word8 Word32
instance NumExpand Word8 Word64
instance NumExpand Word8 Word128
instance NumExpand Word8 Word256
instance NumConvert Word8 Int8
instance NumExpand Word8 Int16
instance NumExpand Word8 Int29_
instance NumExpand Word8 Int32
instance NumExpand Word8 Int64
instance NumExpand Word8 Int128
instance NumExpand Word8 Integer
instance NumConvert Word16 Word8
instance NumExpand Word16 Word16
instance NumExpand Word16 Word29_
instance NumExpand Word16 Word32
instance NumExpand Word16 Word64
instance NumExpand Word16 Word128
instance NumExpand Word16 Word256
instance NumConvert Word16 Int8
instance NumConvert Word16 Int16
instance NumExpand Word16 Int29_
instance NumExpand Word16 Int32
instance NumExpand Word16 Int64
instance NumExpand Word16 Int128
instance NumExpand Word16 Integer
instance NumConvert Word29_ Word8
instance NumConvert Word29_ Word16
instance NumExpand Word29_ Word29_
instance NumConvert Word29_ Word32
instance NumConvert Word29_ Word64
instance NumConvert Word29_ Word128
instance NumConvert Word29_ Word256
instance NumConvert Word29_ Int8
instance NumConvert Word29_ Int16
instance NumConvert Word29_ Int29_
instance NumConvert Word29_ Int32
instance NumConvert Word29_ Int64
instance NumConvert Word29_ Int128
instance NumExpand Word29_ Integer
instance NumConvert Word32 Word8
instance NumConvert Word32 Word16
instance NumConvert Word32 Word29_
instance NumExpand Word32 Word32
instance NumExpand Word32 Word64
instance NumExpand Word32 Word128
instance NumExpand Word32 Word256
instance NumConvert Word32 Int8
instance NumConvert Word32 Int16
instance NumConvert Word32 Int29_
instance NumConvert Word32 Int32
instance NumExpand Word32 Int64
instance NumExpand Word32 Int128
instance NumExpand Word32 Integer
instance NumConvert Word64 Word8
instance NumConvert Word64 Word16
instance NumConvert Word64 Word29_
instance NumConvert Word64 Word32
instance NumExpand Word64 Word64
instance NumExpand Word64 Word128
instance NumExpand Word64 Word256
instance NumConvert Word64 Int8
instance NumConvert Word64 Int16
instance NumConvert Word64 Int29_
instance NumConvert Word64 Int32
instance NumConvert Word64 Int64
instance NumExpand Word64 Int128
instance NumExpand Word64 Integer
instance NumConvert Word128 Word8
instance NumConvert Word128 Word16
instance NumConvert Word128 Word29_
instance NumConvert Word128 Word32
instance NumConvert Word128 Word64
instance NumExpand Word128 Word128
instance NumExpand Word128 Word256
instance NumConvert Word128 Int8
instance NumConvert Word128 Int16
instance NumConvert Word128 Int29_
instance NumConvert Word128 Int32
instance NumConvert Word128 Int64
instance NumConvert Word128 Int128
instance NumExpand Word128 Integer
instance NumConvert Word256 Word8
instance NumConvert Word256 Word16
instance NumConvert Word256 Word29_
instance NumConvert Word256 Word32
instance NumConvert Word256 Word64
instance NumConvert Word256 Word128
instance NumExpand Word256 Word256
instance NumConvert Word256 Int8
instance NumConvert Word256 Int16
instance NumConvert Word256 Int29_
instance NumConvert Word256 Int32
instance NumConvert Word256 Int64
instance NumConvert Word256 Int128
instance NumExpand Word256 Integer
instance NumConvert Int8 Word8
instance NumConvert Int8 Word16
instance NumConvert Int8 Word29_
instance NumConvert Int8 Word32
instance NumConvert Int8 Word64
instance NumConvert Int8 Word128
instance NumConvert Int8 Word256
instance NumExpand Int8 Int8
instance NumExpand Int8 Int16
instance NumExpand Int8 Int29_
instance NumExpand Int8 Int32
instance NumExpand Int8 Int64
instance NumExpand Int8 Int128
instance NumExpand Int8 Integer
instance NumConvert Int16 Word8
instance NumConvert Int16 Word16
instance NumConvert Int16 Word29_
instance NumConvert Int16 Word32
instance NumConvert Int16 Word64
instance NumConvert Int16 Word128
instance NumConvert Int16 Word256
instance NumConvert Int16 Int8
instance NumExpand Int16 Int16
instance NumExpand Int16 Int29_
instance NumExpand Int16 Int32
instance NumExpand Int16 Int64
instance NumExpand Int16 Int128
instance NumExpand Int16 Integer
instance NumConvert Int29_ Word8
instance NumConvert Int29_ Word16
instance NumConvert Int29_ Word29_
instance NumConvert Int29_ Word32
instance NumConvert Int29_ Word64
instance NumConvert Int29_ Word128
instance NumConvert Int29_ Word256
instance NumConvert Int29_ Int8
instance NumConvert Int29_ Int16
instance NumExpand Int29_ Int29_
instance NumConvert Int29_ Int32
instance NumConvert Int29_ Int64
instance NumConvert Int29_ Int128
instance NumExpand Int29_ Integer
instance NumConvert Int32 Word8
instance NumConvert Int32 Word16
instance NumConvert Int32 Word29_
instance NumConvert Int32 Word32
instance NumConvert Int32 Word64
instance NumConvert Int32 Word128
instance NumConvert Int32 Word256
instance NumConvert Int32 Int8
instance NumConvert Int32 Int16
instance NumConvert Int32 Int29_
instance NumExpand Int32 Int32
instance NumExpand Int32 Int64
instance NumExpand Int32 Int128
instance NumExpand Int32 Integer
instance NumConvert Int64 Word8
instance NumConvert Int64 Word16
instance NumConvert Int64 Word29_
instance NumConvert Int64 Word32
instance NumConvert Int64 Word64
instance NumConvert Int64 Word128
instance NumConvert Int64 Word256
instance NumConvert Int64 Int8
instance NumConvert Int64 Int16
instance NumConvert Int64 Int29_
instance NumConvert Int64 Int32
instance NumExpand Int64 Int64
instance NumExpand Int64 Int128
instance NumExpand Int64 Integer
instance NumConvert Int128 Word8
instance NumConvert Int128 Word16
instance NumConvert Int128 Word29_
instance NumConvert Int128 Word32
instance NumConvert Int128 Word64
instance NumConvert Int128 Word128
instance NumConvert Int128 Word256
instance NumConvert Int128 Int8
instance NumConvert Int128 Int16
instance NumConvert Int128 Int29_
instance NumConvert Int128 Int32
instance NumConvert Int128 Int64
instance NumExpand Int128 Int128
instance NumExpand Int128 Integer
instance NumConvert Integer Word8
instance NumConvert Integer Word16
instance NumConvert Integer Word29_
instance NumConvert Integer Word32
instance NumConvert Integer Word64
instance NumConvert Integer Word128
instance NumConvert Integer Word256
instance NumConvert Integer Int8
instance NumConvert Integer Int16
instance NumConvert Integer Int29_
instance NumConvert Integer Int32
instance NumConvert Integer Int64
instance NumConvert Integer Int128
instance NumExpand Integer Integer
(+@) :: Num a => a -> a -> a
+@ :: a -> a -> a
(+@) = a -> a -> a
forall a. Num a => a -> a -> a
(+)
infixl 6 +@
{-# INLINE (+@) #-}
(+%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a
+% :: a -> a -> Either ArithException a
(+%) a
a a
b = Integer -> Either ArithException a
forall a.
(Integral a, Bounded a) =>
Integer -> Either ArithException a
checkE (Integer -> Either ArithException a)
-> Integer -> Either ArithException a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixl 6 +%
{-# INLINE (+%) #-}
(+:) :: (Integral a, Bounded a) => a -> a -> a
+: :: a -> a -> a
(+:) a
a a
b = Integer -> a
forall a. (Integral a, Bounded a) => Integer -> a
checkS (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixl 6 +:
{-# INLINE (+:) #-}
(+!) :: (Integral a, Bounded a) => Partial => a -> a -> a
+! :: a -> a -> a
(+!) a
a a
b = Integer -> a
forall a. (Integral a, Bounded a, HasCallStack) => Integer -> a
checkX (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixl 6 +!
{-# INLINE (+!) #-}
(-@) :: Num a => a -> a -> a
-@ :: a -> a -> a
(-@) = (-)
infixl 6 -@
{-# INLINE (-@) #-}
(-%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a
-% :: a -> a -> Either ArithException a
(-%) a
a a
b = Integer -> Either ArithException a
forall a.
(Integral a, Bounded a) =>
Integer -> Either ArithException a
checkE (Integer -> Either ArithException a)
-> Integer -> Either ArithException a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixl 6 -%
{-# INLINE (-%) #-}
(-:) :: (Integral a, Bounded a) => a -> a -> a
-: :: a -> a -> a
(-:) a
a a
b = Integer -> a
forall a. (Integral a, Bounded a) => Integer -> a
checkS (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixl 6 -:
{-# INLINE (-:) #-}
(-!) :: (Integral a, Bounded a) => Partial => a -> a -> a
-! :: a -> a -> a
(-!) a
a a
b = Integer -> a
forall a. (Integral a, Bounded a, HasCallStack) => Integer -> a
checkX (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixl 6 -!
{-# INLINE (-!) #-}
(*@) :: Num a => a -> a -> a
*@ :: a -> a -> a
(*@) = a -> a -> a
forall a. Num a => a -> a -> a
(*)
infixl 7 *@
{-# INLINE (*@) #-}
(*%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a
*% :: a -> a -> Either ArithException a
(*%) a
a a
b = Integer -> Either ArithException a
forall a.
(Integral a, Bounded a) =>
Integer -> Either ArithException a
checkE (Integer -> Either ArithException a)
-> Integer -> Either ArithException a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixl 7 *%
{-# INLINE (*%) #-}
(*:) :: (Integral a, Bounded a) => a -> a -> a
*: :: a -> a -> a
(*:) a
a a
b = Integer -> a
forall a. (Integral a, Bounded a) => Integer -> a
checkS (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixl 7 *:
{-# INLINE (*:) #-}
(*!) :: (Integral a, Bounded a) => Partial => a -> a -> a
*! :: a -> a -> a
(*!) a
a a
b = Integer -> a
forall a. (Integral a, Bounded a, HasCallStack) => Integer -> a
checkX (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixl 7 *!
{-# INLINE (*!) #-}
(^@) :: Integral a => a -> a -> a
^@ :: a -> a -> a
(^@) = a -> a -> a
forall a b. (Num a, Integral b) => a -> b -> a
(^)
infixr 8 ^@
{-# INLINE (^@) #-}
(^%) :: (Integral a, Bounded a) => a -> a -> Either ArithException a
^% :: a -> a -> Either ArithException a
(^%) a
a a
b = Integer -> Either ArithException a
forall a.
(Integral a, Bounded a) =>
Integer -> Either ArithException a
checkE (Integer -> Either ArithException a)
-> Integer -> Either ArithException a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixr 8 ^%
{-# INLINE (^%) #-}
(^:) :: (Integral a, Bounded a) => a -> a -> a
^: :: a -> a -> a
(^:) a
a a
b = Integer -> a
forall a. (Integral a, Bounded a) => Integer -> a
checkS (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixr 8 ^:
{-# INLINE (^:) #-}
(^!) :: (Integral a, Bounded a) => Partial => a -> a -> a
^! :: a -> a -> a
(^!) a
a a
b = Integer -> a
forall a. (Integral a, Bounded a, HasCallStack) => Integer -> a
checkX (Integer -> a) -> Integer -> a
forall a b. (a -> b) -> a -> b
$ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
a Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ a -> Integer
forall a. Integral a => a -> Integer
toInteger a
b
infixr 8 ^!
{-# INLINE (^!) #-}
type DivResult a = Either Ordering a
explicitDiv :: (Eq a, Ord a, Num a) => (a -> a -> b) -> a -> a -> DivResult b
explicitDiv :: (a -> a -> b) -> a -> a -> DivResult b
explicitDiv a -> a -> b
op a
x a
y = if a
y a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 then Ordering -> DivResult b
forall a b. a -> Either a b
Left (Ordering -> DivResult b) -> Ordering -> DivResult b
forall a b. (a -> b) -> a -> b
$ a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
0 else b -> DivResult b
forall a b. b -> Either a b
Right (b -> DivResult b) -> b -> DivResult b
forall a b. (a -> b) -> a -> b
$ a
x a -> a -> b
`op` a
y
{-# INLINE explicitDiv #-}
divE :: Integral a => a -> a -> DivResult a
divE :: a -> a -> DivResult a
divE = (a -> a -> a) -> a -> a -> DivResult a
forall a b.
(Eq a, Ord a, Num a) =>
(a -> a -> b) -> a -> a -> DivResult b
explicitDiv a -> a -> a
forall a. Integral a => a -> a -> a
div
{-# INLINE divE #-}
divX :: Integral a => a -> a -> a
divX :: a -> a -> a
divX = a -> a -> a
forall a. Integral a => a -> a -> a
div
{-# INLINE divX #-}
modE :: Integral a => a -> a -> DivResult a
modE :: a -> a -> DivResult a
modE = (a -> a -> a) -> a -> a -> DivResult a
forall a b.
(Eq a, Ord a, Num a) =>
(a -> a -> b) -> a -> a -> DivResult b
explicitDiv a -> a -> a
forall a. Integral a => a -> a -> a
mod
{-# INLINE modE #-}
modX :: Integral a => a -> a -> a
modX :: a -> a -> a
modX = a -> a -> a
forall a. Integral a => a -> a -> a
mod
{-# INLINE modX #-}
divModE :: Integral a => a -> a -> DivResult (a, a)
divModE :: a -> a -> DivResult (a, a)
divModE = (a -> a -> (a, a)) -> a -> a -> DivResult (a, a)
forall a b.
(Eq a, Ord a, Num a) =>
(a -> a -> b) -> a -> a -> DivResult b
explicitDiv a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
divMod
{-# INLINE divModE #-}
divModX :: Integral a => a -> a -> (a, a)
divModX :: a -> a -> (a, a)
divModX = a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
divMod
{-# INLINE divModX #-}
quotE :: Integral a => a -> a -> DivResult a
quotE :: a -> a -> DivResult a
quotE = (a -> a -> a) -> a -> a -> DivResult a
forall a b.
(Eq a, Ord a, Num a) =>
(a -> a -> b) -> a -> a -> DivResult b
explicitDiv a -> a -> a
forall a. Integral a => a -> a -> a
quot
{-# INLINE quotE #-}
quotX :: Integral a => a -> a -> a
quotX :: a -> a -> a
quotX = a -> a -> a
forall a. Integral a => a -> a -> a
quot
{-# INLINE quotX #-}
remE :: Integral a => a -> a -> DivResult a
remE :: a -> a -> DivResult a
remE = (a -> a -> a) -> a -> a -> DivResult a
forall a b.
(Eq a, Ord a, Num a) =>
(a -> a -> b) -> a -> a -> DivResult b
explicitDiv a -> a -> a
forall a. Integral a => a -> a -> a
rem
{-# INLINE remE #-}
remX :: Integral a => a -> a -> a
remX :: a -> a -> a
remX = a -> a -> a
forall a. Integral a => a -> a -> a
rem
{-# INLINE remX #-}
quotRemE :: Integral a => a -> a -> DivResult (a, a)
quotRemE :: a -> a -> DivResult (a, a)
quotRemE = (a -> a -> (a, a)) -> a -> a -> DivResult (a, a)
forall a b.
(Eq a, Ord a, Num a) =>
(a -> a -> b) -> a -> a -> DivResult b
explicitDiv a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
quotRem
{-# INLINE quotRemE #-}
quotRemX :: Integral a => a -> a -> (a, a)
quotRemX :: a -> a -> (a, a)
quotRemX = a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
quotRem
{-# INLINE quotRemX #-}