{-# language Trustworthy #-} module NatOptics.Positive.Math ( minus, plus, absoluteDifference, ) where import Data.Ord ( Ord, (<), compare, Ordering (..) ) import Prelude ( Num, (+), (-) ) import NatOptics.Positive.Unsafe ( Positive (..) ) import NatOptics.Signed ( Signed ) import qualified NatOptics.Signed as Signed import NatOptics.NonNegative.Unsafe ( NonNegative (..) ) plus :: Num n => Positive n -> Positive n -> Positive n plus :: forall n. Num n => Positive n -> Positive n -> Positive n plus (PositiveUnsafe n a) (PositiveUnsafe n b) = n -> Positive n forall number. number -> Positive number PositiveUnsafe (n a n -> n -> n forall a. Num a => a -> a -> a + n b) minus :: (Num n, Ord n) => Positive n -> Positive n -> Signed n minus :: forall n. (Num n, Ord n) => Positive n -> Positive n -> Signed n minus (PositiveUnsafe n a) (PositiveUnsafe n b) = case n -> n -> Ordering forall a. Ord a => a -> a -> Ordering compare n a n b of Ordering EQ -> Signed n forall n. Signed n Signed.Zero Ordering GT -> Positive n -> Signed n forall n. Positive n -> Signed n Signed.Plus (n -> Positive n forall number. number -> Positive number PositiveUnsafe (n a n -> n -> n forall a. Num a => a -> a -> a - n b)) Ordering LT -> Positive n -> Signed n forall n. Positive n -> Signed n Signed.Minus (n -> Positive n forall number. number -> Positive number PositiveUnsafe (n b n -> n -> n forall a. Num a => a -> a -> a - n a)) absoluteDifference :: (Num n, Ord n) => Positive n -> Positive n -> NonNegative n absoluteDifference :: forall n. (Num n, Ord n) => Positive n -> Positive n -> NonNegative n absoluteDifference (PositiveUnsafe n a) (PositiveUnsafe n b) = n -> NonNegative n forall number. number -> NonNegative number NonNegativeUnsafe (if n a n -> n -> Bool forall a. Ord a => a -> a -> Bool < n b then n b n -> n -> n forall a. Num a => a -> a -> a - n a else n a n -> n -> n forall a. Num a => a -> a -> a - n b)