module Integer.Natural
(
Natural,
toPositive,
fromPositive,
toInteger,
fromInteger,
toSigned,
fromSigned,
toInt,
fromInt,
toWord,
fromWord,
subtract,
strictlyIncrease,
one,
addOne,
subtractOne,
length,
)
where
import Data.Int (Int)
import Data.List qualified as List
import Data.Ord qualified as Ord
import Data.Word (Word)
import Essentials
import Integer.Positive qualified as Positive
import Integer.Positive.Unsafe (Positive)
import Integer.Positive.Unsafe qualified as Positive.Unsafe
import Integer.Signed (Signed (..))
import Integer.Signed qualified as Signed
import Numeric.Natural (Natural)
import Prelude (Integer)
import Prelude qualified as Bounded (Bounded (..))
import Prelude qualified as Num (Integral (..), Num (..))
toPositive :: Natural -> Maybe Positive
toPositive :: Natural -> Maybe Positive
toPositive = Natural -> Maybe Positive
Positive.fromNatural
fromPositive :: Positive -> Natural
fromPositive :: Positive -> Natural
fromPositive = Positive -> Natural
Positive.toNatural
fromInteger :: Integer -> Maybe Natural
fromInteger :: Integer -> Maybe Natural
fromInteger Integer
x = if Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
Ord.>= Integer
0 then Natural -> Maybe Natural
forall a. a -> Maybe a
Just (Integer -> Natural
forall a. Num a => Integer -> a
Num.fromInteger Integer
x) else Maybe Natural
forall a. Maybe a
Nothing
toInteger :: Natural -> Integer
toInteger :: Natural -> Integer
toInteger = Natural -> Integer
forall a. Integral a => a -> Integer
Num.toInteger
toSigned :: Natural -> Signed
toSigned :: Natural -> Signed
toSigned = Natural -> Signed
Signed.fromNatural
fromSigned :: Signed -> Maybe Natural
fromSigned :: Signed -> Maybe Natural
fromSigned = Signed -> Maybe Natural
Signed.toNatural
toInt :: Natural -> Maybe Int
toInt :: Natural -> Maybe Int
toInt Natural
x = if Bool
ok then Int -> Maybe Int
forall a. a -> Maybe a
Just (Integer -> Int
forall a. Num a => Integer -> a
Num.fromInteger Integer
x') else Maybe Int
forall a. Maybe a
Nothing
where
ok :: Bool
ok = Integer
x' Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
Ord.<= Int -> Integer
forall a. Integral a => a -> Integer
Num.toInteger (Int
forall a. Bounded a => a
Bounded.maxBound :: Int)
x' :: Integer
x' = Natural -> Integer
forall a. Integral a => a -> Integer
Num.toInteger Natural
x
fromInt :: Int -> Maybe Natural
fromInt :: Int -> Maybe Natural
fromInt Int
x = if Bool
ok then Natural -> Maybe Natural
forall a. a -> Maybe a
Just (Integer -> Natural
forall a. Num a => Integer -> a
Num.fromInteger Integer
x') else Maybe Natural
forall a. Maybe a
Nothing
where
ok :: Bool
ok = Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
Ord.>= Int
0
x' :: Integer
x' = Int -> Integer
forall a. Integral a => a -> Integer
Num.toInteger Int
x
toWord :: Natural -> Maybe Word
toWord :: Natural -> Maybe Word
toWord Natural
x = if Bool
ok then Word -> Maybe Word
forall a. a -> Maybe a
Just (Integer -> Word
forall a. Num a => Integer -> a
Num.fromInteger Integer
x') else Maybe Word
forall a. Maybe a
Nothing
where
ok :: Bool
ok = Integer
x' Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
Ord.<= Word -> Integer
forall a. Integral a => a -> Integer
Num.toInteger (Word
forall a. Bounded a => a
Bounded.maxBound :: Word)
x' :: Integer
x' = Natural -> Integer
forall a. Integral a => a -> Integer
Num.toInteger Natural
x
fromWord :: Word -> Natural
fromWord :: Word -> Natural
fromWord Word
x = Integer -> Natural
forall a. Num a => Integer -> a
Num.fromInteger (Word -> Integer
forall a. Integral a => a -> Integer
Num.toInteger Word
x)
subtract :: Natural -> Natural -> Signed
subtract :: Natural -> Natural -> Signed
subtract Natural
a Natural
b = case Natural -> Natural -> Ordering
forall a. Ord a => a -> a -> Ordering
Ord.compare Natural
a Natural
b of
Ordering
Ord.EQ -> Signed
Zero
Ordering
Ord.GT -> Positive -> Signed
Plus (Positive -> Signed) -> Positive -> Signed
forall a b. (a -> b) -> a -> b
$ Natural -> Positive
Positive.Unsafe.fromNatural (Natural -> Positive) -> Natural -> Positive
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
(Num.-) Natural
a Natural
b
Ordering
Ord.LT -> Positive -> Signed
Minus (Positive -> Signed) -> Positive -> Signed
forall a b. (a -> b) -> a -> b
$ Natural -> Positive
Positive.Unsafe.fromNatural (Natural -> Positive) -> Natural -> Positive
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
(Num.-) Natural
b Natural
a
one :: Natural
one :: Natural
one = Natural
1
addOne :: Natural -> Positive
addOne :: Natural -> Positive
addOne Natural
x = Natural -> Positive
Positive.Unsafe.fromNatural (Natural
x Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Num.+ Natural
1)
subtractOne :: Natural -> Maybe Signed
subtractOne :: Natural -> Maybe Signed
subtractOne Natural
x = case Natural
x of
Natural
0 -> Maybe Signed
forall a. Maybe a
Nothing
Natural
p -> Signed -> Maybe Signed
forall a. a -> Maybe a
Just (Natural -> Natural -> Signed
subtract Natural
p Natural
1)
length :: [a] -> Natural
length :: forall a. [a] -> Natural
length = (Natural -> a -> Natural) -> Natural -> [a] -> Natural
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' (\Natural
x a
_ -> Natural
x Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Num.+ Natural
1) Natural
0
strictlyIncrease :: Positive -> Natural -> Natural
strictlyIncrease :: Positive -> Natural -> Natural
strictlyIncrease Positive
p Natural
n = Positive -> Natural
Positive.toNatural Positive
p Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Num.+ Natural
n