module Integer.Positive.Unsafe
(
Positive (FromNatural),
toNatural,
fromNatural,
fromNaturalChecked,
toInteger,
fromInteger,
fromIntegerChecked,
toInt,
fromInt,
fromIntChecked,
subtract,
subtractChecked,
increase,
one,
addOne,
subtractOne,
subtractOneChecked,
)
where
import Control.DeepSeq qualified as DeepSeq
import Control.Exception qualified as Exception
import Control.Monad.Fail (fail)
import Data.Bits qualified as Bits
import Data.Hashable (Hashable)
import Data.List qualified as List
import Data.Maybe qualified as Maybe
import Data.Ord qualified as Ord
import Essentials
import Integer.BoundedBelow (BoundedBelow)
import Integer.BoundedBelow qualified as BoundedBelow
import Numeric.Natural (Natural)
import Text.Read qualified as Read
import Text.Show qualified as Show
import Prelude (Int, Integer, Integral, Num, Read, Real)
import Prelude qualified as Enum (Enum (..))
import Prelude qualified as Num
( Integral (..),
Num (..),
Real (..),
fromIntegral,
)
newtype Positive = FromNatural {Positive -> Natural
toNatural :: Natural}
deriving newtype (Positive -> Positive -> Bool
(Positive -> Positive -> Bool)
-> (Positive -> Positive -> Bool) -> Eq Positive
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Positive -> Positive -> Bool
== :: Positive -> Positive -> Bool
$c/= :: Positive -> Positive -> Bool
/= :: Positive -> Positive -> Bool
Eq, Eq Positive
Eq Positive =>
(Positive -> Positive -> Ordering)
-> (Positive -> Positive -> Bool)
-> (Positive -> Positive -> Bool)
-> (Positive -> Positive -> Bool)
-> (Positive -> Positive -> Bool)
-> (Positive -> Positive -> Positive)
-> (Positive -> Positive -> Positive)
-> Ord Positive
Positive -> Positive -> Bool
Positive -> Positive -> Ordering
Positive -> Positive -> Positive
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Positive -> Positive -> Ordering
compare :: Positive -> Positive -> Ordering
$c< :: Positive -> Positive -> Bool
< :: Positive -> Positive -> Bool
$c<= :: Positive -> Positive -> Bool
<= :: Positive -> Positive -> Bool
$c> :: Positive -> Positive -> Bool
> :: Positive -> Positive -> Bool
$c>= :: Positive -> Positive -> Bool
>= :: Positive -> Positive -> Bool
$cmax :: Positive -> Positive -> Positive
max :: Positive -> Positive -> Positive
$cmin :: Positive -> Positive -> Positive
min :: Positive -> Positive -> Positive
Ord, Eq Positive
Eq Positive =>
(Int -> Positive -> Int) -> (Positive -> Int) -> Hashable Positive
Int -> Positive -> Int
Positive -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Positive -> Int
hashWithSalt :: Int -> Positive -> Int
$chash :: Positive -> Int
hash :: Positive -> Int
Hashable)
instance DeepSeq.NFData Positive where rnf :: Positive -> ()
rnf (FromNatural Natural
x) = Natural -> ()
forall a. NFData a => a -> ()
DeepSeq.rnf Natural
x
fromNatural :: Natural -> Positive
fromNatural :: Natural -> Positive
fromNatural = Natural -> Positive
FromNatural
fromNaturalChecked :: Natural -> Positive
fromNaturalChecked :: Natural -> Positive
fromNaturalChecked Natural
x = case Natural
x of Natural
0 -> ArithException -> Positive
forall a e. Exception e => e -> a
Exception.throw ArithException
Exception.Underflow; Natural
_ -> Natural -> Positive
fromNatural Natural
x
toInteger :: Positive -> Integer
toInteger :: Positive -> Integer
toInteger = Natural -> Integer
forall a. Integral a => a -> Integer
Num.toInteger (Natural -> Integer)
-> (Positive -> Natural) -> Positive -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Natural
toNatural
fromInteger :: Integer -> Positive
fromInteger :: Integer -> Positive
fromInteger = Natural -> Positive
fromNatural (Natural -> Positive)
-> (Integer -> Natural) -> Integer -> Positive
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Integer -> Natural
forall a. Num a => Integer -> a
Num.fromInteger
fromIntegerChecked :: Integer -> Positive
fromIntegerChecked :: Integer -> Positive
fromIntegerChecked Integer
x = if Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
Ord.>= Integer
1 then Integer -> Positive
fromInteger Integer
x else ArithException -> Positive
forall a e. Exception e => e -> a
Exception.throw ArithException
Exception.Underflow
add :: Positive -> Positive -> Positive
add :: Positive -> Positive -> Positive
add Positive
a Positive
b = Natural -> Positive
fromNatural (Positive -> Natural
toNatural Positive
a Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Num.+ Positive -> Natural
toNatural Positive
b)
subtract :: Positive -> Positive -> Positive
subtract :: Positive -> Positive -> Positive
subtract Positive
a Positive
b = Natural -> Positive
fromNatural (Positive -> Natural
toNatural Positive
a Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Num.- Positive -> Natural
toNatural Positive
b)
subtractChecked :: Positive -> Positive -> Positive
subtractChecked :: Positive -> Positive -> Positive
subtractChecked Positive
a Positive
b = if Positive
a Positive -> Positive -> Bool
forall a. Ord a => a -> a -> Bool
Ord.> Positive
b then Positive -> Positive -> Positive
subtract Positive
a Positive
b else ArithException -> Positive
forall a e. Exception e => e -> a
Exception.throw ArithException
Exception.Underflow
multiply :: Positive -> Positive -> Positive
multiply :: Positive -> Positive -> Positive
multiply Positive
a Positive
b = Natural -> Positive
fromNatural (Positive -> Natural
toNatural Positive
a Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Num.* Positive -> Natural
toNatural Positive
b)
one :: Positive
one :: Positive
one = Natural -> Positive
fromNatural Natural
1
addOne :: Positive -> Positive
addOne :: Positive -> Positive
addOne = Natural -> Positive
fromNatural (Natural -> Positive)
-> (Positive -> Natural) -> Positive -> Positive
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Num.+ Natural
1) (Natural -> Natural)
-> (Positive -> Natural) -> Positive -> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Natural
toNatural
subtractOne :: Positive -> Positive
subtractOne :: Positive -> Positive
subtractOne = Natural -> Positive
fromNatural (Natural -> Positive)
-> (Positive -> Natural) -> Positive -> Positive
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Num.- Natural
1) (Natural -> Natural)
-> (Positive -> Natural) -> Positive -> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Natural
toNatural
subtractOneChecked :: Positive -> Positive
subtractOneChecked :: Positive -> Positive
subtractOneChecked Positive
x = case Positive
x of Positive
1 -> ArithException -> Positive
forall a e. Exception e => e -> a
Exception.throw ArithException
Exception.Underflow; Positive
_ -> Positive -> Positive
subtractOne Positive
x
increase :: Natural -> Positive -> Positive
increase :: Natural -> Positive -> Positive
increase Natural
n = Natural -> Positive
fromNatural (Natural -> Positive)
-> (Positive -> Natural) -> Positive -> Positive
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Num.+ Natural
n) (Natural -> Natural)
-> (Positive -> Natural) -> Positive -> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Natural
toNatural
toInt :: Positive -> Int
toInt :: Positive -> Int
toInt = Natural -> Int
forall a b. (Integral a, Num b) => a -> b
Num.fromIntegral (Natural -> Int) -> (Positive -> Natural) -> Positive -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Natural
toNatural
toIntChecked :: Positive -> Int
toIntChecked :: Positive -> Int
toIntChecked = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
Maybe.fromMaybe (ArithException -> Int
forall a e. Exception e => e -> a
Exception.throw ArithException
Exception.Overflow) (Maybe Int -> Int) -> (Positive -> Maybe Int) -> Positive -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Natural -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized (Natural -> Maybe Int)
-> (Positive -> Natural) -> Positive -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Natural
toNatural
fromInt :: Int -> Positive
fromInt :: Int -> Positive
fromInt = Natural -> Positive
fromNatural (Natural -> Positive) -> (Int -> Natural) -> Int -> Positive
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> Natural
forall a b. (Integral a, Num b) => a -> b
Num.fromIntegral
fromIntChecked :: Int -> Positive
fromIntChecked :: Int -> Positive
fromIntChecked Int
x = case Int -> Int
forall a. Num a => a -> a
Num.signum Int
x of Int
1 -> Int -> Positive
fromInt Int
x; Int
_ -> ArithException -> Positive
forall a e. Exception e => e -> a
Exception.throw ArithException
Exception.Underflow
enumFrom :: Positive -> [Positive]
enumFrom :: Positive -> [Positive]
enumFrom = (Natural -> Positive) -> [Natural] -> [Positive]
forall a b. (a -> b) -> [a] -> [b]
List.map Natural -> Positive
fromNatural ([Natural] -> [Positive])
-> (Positive -> [Natural]) -> Positive -> [Positive]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Natural -> [Natural]
forall a. Enum a => a -> [a]
Enum.enumFrom (Natural -> [Natural])
-> (Positive -> Natural) -> Positive -> [Natural]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Natural
toNatural
enumFromTo :: Positive -> Positive -> [Positive]
enumFromTo :: Positive -> Positive -> [Positive]
enumFromTo Positive
a Positive
b = (Natural -> Positive) -> [Natural] -> [Positive]
forall a b. (a -> b) -> [a] -> [b]
List.map Natural -> Positive
fromNatural ([Natural] -> [Positive]) -> [Natural] -> [Positive]
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> [Natural]
forall a. Enum a => a -> a -> [a]
Enum.enumFromTo (Positive -> Natural
toNatural Positive
a) (Positive -> Natural
toNatural Positive
b)
enumFromThen :: Positive -> Positive -> [Positive]
enumFromThen :: Positive -> Positive -> [Positive]
enumFromThen Positive
a Positive
b = if Positive
a Positive -> Positive -> Bool
forall a. Ord a => a -> a -> Bool
Ord.< Positive
b then [Positive]
ascending else [Positive]
descending
where
ascending :: [Positive]
ascending = (Natural -> Positive) -> [Natural] -> [Positive]
forall a b. (a -> b) -> [a] -> [b]
List.map Natural -> Positive
fromNatural ([Natural] -> [Positive]) -> [Natural] -> [Positive]
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> [Natural]
forall a. Enum a => a -> a -> [a]
Enum.enumFromThen (Positive -> Natural
toNatural Positive
a) (Positive -> Natural
toNatural Positive
b)
descending :: [Positive]
descending =
(Integer -> Positive) -> [Integer] -> [Positive]
forall a b. (a -> b) -> [a] -> [b]
List.map Integer -> Positive
fromInteger ([Integer] -> [Positive]) -> [Integer] -> [Positive]
forall a b. (a -> b) -> a -> b
$
(Integer -> Bool) -> [Integer] -> [Integer]
forall a. (a -> Bool) -> [a] -> [a]
List.takeWhile (Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
Ord.>= Integer
1) ([Integer] -> [Integer]) -> [Integer] -> [Integer]
forall a b. (a -> b) -> a -> b
$
Integer -> Integer -> [Integer]
forall a. Enum a => a -> a -> [a]
Enum.enumFromThen (Positive -> Integer
toInteger Positive
a) (Positive -> Integer
toInteger Positive
b)
enumFromThenTo :: Positive -> Positive -> Positive -> [Positive]
enumFromThenTo :: Positive -> Positive -> Positive -> [Positive]
enumFromThenTo Positive
a Positive
b Positive
c = if Positive
a Positive -> Positive -> Bool
forall a. Ord a => a -> a -> Bool
Ord.< Positive
b then [Positive]
ascending else [Positive]
descending
where
ascending :: [Positive]
ascending = (Natural -> Positive) -> [Natural] -> [Positive]
forall a b. (a -> b) -> [a] -> [b]
List.map Natural -> Positive
fromNatural ([Natural] -> [Positive]) -> [Natural] -> [Positive]
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> Natural -> [Natural]
forall a. Enum a => a -> a -> a -> [a]
Enum.enumFromThenTo (Positive -> Natural
toNatural Positive
a) (Positive -> Natural
toNatural Positive
b) (Positive -> Natural
toNatural Positive
c)
descending :: [Positive]
descending =
(Integer -> Positive) -> [Integer] -> [Positive]
forall a b. (a -> b) -> [a] -> [b]
List.map Integer -> Positive
fromInteger ([Integer] -> [Positive]) -> [Integer] -> [Positive]
forall a b. (a -> b) -> a -> b
$
(Integer -> Bool) -> [Integer] -> [Integer]
forall a. (a -> Bool) -> [a] -> [a]
List.takeWhile (Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
Ord.>= Integer
1) ([Integer] -> [Integer]) -> [Integer] -> [Integer]
forall a b. (a -> b) -> a -> b
$
Integer -> Integer -> Integer -> [Integer]
forall a. Enum a => a -> a -> a -> [a]
Enum.enumFromThenTo (Positive -> Integer
toInteger Positive
a) (Positive -> Integer
toInteger Positive
b) (Positive -> Integer
toInteger Positive
c)
type Div a = a -> a -> (a, a)
divisionOp :: Div Natural -> Div Positive
divisionOp :: Div Natural -> Div Positive
divisionOp Div Natural
o Positive
a Positive
b =
let (Natural
q, Natural
r) = Div Natural
o (Positive -> Natural
toNatural Positive
a) (Positive -> Natural
toNatural Positive
b)
in (Natural -> Positive
fromNaturalChecked Natural
q, Natural -> Positive
fromNaturalChecked Natural
r)
instance BoundedBelow Positive where
minBound :: Positive
minBound = Positive
1
instance Num Positive where
abs :: Positive -> Positive
abs = Positive -> Positive
forall a. a -> a
forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
negate :: Positive -> Positive
negate = \Positive
_ -> ArithException -> Positive
forall a e. Exception e => e -> a
Exception.throw ArithException
Exception.Underflow
signum :: Positive -> Positive
signum = \Positive
_ -> Natural -> Positive
fromNatural Natural
1
fromInteger :: Integer -> Positive
fromInteger = Integer -> Positive
fromIntegerChecked
+ :: Positive -> Positive -> Positive
(+) = Positive -> Positive -> Positive
add
* :: Positive -> Positive -> Positive
(*) = Positive -> Positive -> Positive
multiply
(-) = Positive -> Positive -> Positive
subtractChecked
instance Enum Positive where
succ :: Positive -> Positive
succ = Positive -> Positive
addOne
pred :: Positive -> Positive
pred = Positive -> Positive
subtractOneChecked
fromEnum :: Positive -> Int
fromEnum = Positive -> Int
toIntChecked
toEnum :: Int -> Positive
toEnum = Int -> Positive
fromIntChecked
enumFrom :: Positive -> [Positive]
enumFrom = Positive -> [Positive]
enumFrom
enumFromTo :: Positive -> Positive -> [Positive]
enumFromTo = Positive -> Positive -> [Positive]
enumFromTo
enumFromThen :: Positive -> Positive -> [Positive]
enumFromThen = Positive -> Positive -> [Positive]
enumFromThen
enumFromThenTo :: Positive -> Positive -> Positive -> [Positive]
enumFromThenTo = Positive -> Positive -> Positive -> [Positive]
enumFromThenTo
instance Real Positive where
toRational :: Positive -> Rational
toRational = Integer -> Rational
forall a. Real a => a -> Rational
Num.toRational (Integer -> Rational)
-> (Positive -> Integer) -> Positive -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Integer
toInteger
instance Integral Positive where
toInteger :: Positive -> Integer
toInteger = Positive -> Integer
toInteger
quotRem :: Div Positive
quotRem = Div Natural -> Div Positive
divisionOp Div Natural
forall a. Integral a => a -> a -> (a, a)
Num.quotRem
divMod :: Div Positive
divMod = Div Natural -> Div Positive
divisionOp Div Natural
forall a. Integral a => a -> a -> (a, a)
Num.divMod
instance Show Positive where
show :: Positive -> String
show = Natural -> String
forall a. Show a => a -> String
Show.show (Natural -> String) -> (Positive -> Natural) -> Positive -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Natural
toNatural
showsPrec :: Int -> Positive -> ShowS
showsPrec Int
i = Int -> Natural -> ShowS
forall a. Show a => Int -> a -> ShowS
Show.showsPrec Int
i (Natural -> ShowS) -> (Positive -> Natural) -> Positive -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Positive -> Natural
toNatural
instance Read Positive where
readsPrec :: Int -> ReadS Positive
readsPrec Int
i = do
[(Natural, String)]
xs <- forall a. Read a => Int -> ReadS a
Read.readsPrec @Natural Int
i
[(Positive, String)] -> ReadS Positive
forall a. a -> String -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(Positive, String)] -> ReadS Positive)
-> [(Positive, String)] -> ReadS Positive
forall a b. (a -> b) -> a -> b
$
[(Natural, String)]
xs [(Natural, String)]
-> ([(Natural, String)] -> [(Positive, String)])
-> [(Positive, String)]
forall a b. a -> (a -> b) -> b
& ((Natural, String) -> Maybe (Positive, String))
-> [(Natural, String)] -> [(Positive, String)]
forall a b. (a -> Maybe b) -> [a] -> [b]
Maybe.mapMaybe \case
(Natural
0, String
_) -> Maybe (Positive, String)
forall a. Maybe a
Nothing
(Natural
n, String
s) -> (Positive, String) -> Maybe (Positive, String)
forall a. a -> Maybe a
Just (Natural -> Positive
fromNatural Natural
n, String
s)
readPrec :: ReadPrec Positive
readPrec = do
Natural
n <- forall a. Read a => ReadPrec a
Read.readPrec @Natural
if Natural
n Natural -> Natural -> Bool
forall a. Eq a => a -> a -> Bool
== Natural
0 then String -> ReadPrec Positive
forall a. String -> ReadPrec a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"0" else Positive -> ReadPrec Positive
forall a. a -> ReadPrec a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Positive -> ReadPrec Positive) -> Positive -> ReadPrec Positive
forall a b. (a -> b) -> a -> b
$ Natural -> Positive
fromNatural Natural
n