module NumHask.Algebra.Multiplicative
  ( Multiplicative (..),
    Product (..),
    product,
    accproduct,
    Divisive (..),
  )
where
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Traversable (mapAccumL)
import Data.Word (Word, Word16, Word32, Word64, Word8)
import GHC.Natural (Natural (..))
import Prelude (Double, Eq, Float, Int, Integer, Ord, Show, fromInteger, fromRational)
import qualified Prelude as P
class Multiplicative a where
  infixl 7 *
  (*) :: a -> a -> a
  one :: a
newtype Product a = Product
  { forall a. Product a -> a
getProduct :: a
  }
  deriving (Product a -> Product a -> Bool
forall a. Eq a => Product a -> Product a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Product a -> Product a -> Bool
$c/= :: forall a. Eq a => Product a -> Product a -> Bool
== :: Product a -> Product a -> Bool
$c== :: forall a. Eq a => Product a -> Product a -> Bool
Eq, Product a -> Product a -> Bool
Product a -> Product a -> Ordering
Product a -> Product a -> Product a
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
forall {a}. Ord a => Eq (Product a)
forall a. Ord a => Product a -> Product a -> Bool
forall a. Ord a => Product a -> Product a -> Ordering
forall a. Ord a => Product a -> Product a -> Product a
min :: Product a -> Product a -> Product a
$cmin :: forall a. Ord a => Product a -> Product a -> Product a
max :: Product a -> Product a -> Product a
$cmax :: forall a. Ord a => Product a -> Product a -> Product a
>= :: Product a -> Product a -> Bool
$c>= :: forall a. Ord a => Product a -> Product a -> Bool
> :: Product a -> Product a -> Bool
$c> :: forall a. Ord a => Product a -> Product a -> Bool
<= :: Product a -> Product a -> Bool
$c<= :: forall a. Ord a => Product a -> Product a -> Bool
< :: Product a -> Product a -> Bool
$c< :: forall a. Ord a => Product a -> Product a -> Bool
compare :: Product a -> Product a -> Ordering
$ccompare :: forall a. Ord a => Product a -> Product a -> Ordering
Ord, Int -> Product a -> ShowS
forall a. Show a => Int -> Product a -> ShowS
forall a. Show a => [Product a] -> ShowS
forall a. Show a => Product a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Product a] -> ShowS
$cshowList :: forall a. Show a => [Product a] -> ShowS
show :: Product a -> String
$cshow :: forall a. Show a => Product a -> String
showsPrec :: Int -> Product a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Product a -> ShowS
Show)
instance (Multiplicative a) => P.Semigroup (Product a) where
  Product a
a <> :: Product a -> Product a -> Product a
<> Product a
b = forall a. a -> Product a
Product (a
a forall a. Multiplicative a => a -> a -> a
* a
b)
instance (Multiplicative a) => P.Monoid (Product a) where
  mempty :: Product a
mempty = forall a. a -> Product a
Product forall a. Multiplicative a => a
one
product :: (Multiplicative a, P.Foldable f) => f a -> a
product :: forall a (f :: * -> *). (Multiplicative a, Foldable f) => f a -> a
product = forall a. Product a -> a
getProduct forall b c a. (b -> c) -> (a -> b) -> a -> c
P.. forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
P.foldMap forall a. a -> Product a
Product
accproduct :: (Multiplicative a, P.Traversable f) => f a -> f a
accproduct :: forall a (f :: * -> *).
(Multiplicative a, Traversable f) =>
f a -> f a
accproduct = forall a b. (a, b) -> b
P.snd forall b c a. (b -> c) -> (a -> b) -> a -> c
P.. forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumL (\a
a a
b -> (a
a forall a. Multiplicative a => a -> a -> a
* a
b, a
a forall a. Multiplicative a => a -> a -> a
* a
b)) forall a. Multiplicative a => a
one
class (Multiplicative a) => Divisive a where
  {-# MINIMAL (/) | recip #-}
  recip :: a -> a
  recip a
a = forall a. Multiplicative a => a
one forall a. Divisive a => a -> a -> a
/ a
a
  infixl 7 /
  (/) :: a -> a -> a
  (/) a
a a
b = a
a forall a. Multiplicative a => a -> a -> a
* forall a. Divisive a => a -> a
recip a
b
instance Multiplicative Double where
  * :: Double -> Double -> Double
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Double
one = Double
1.0
instance Divisive Double where
  recip :: Double -> Double
recip = forall a. Fractional a => a -> a
P.recip
instance Multiplicative Float where
  * :: Float -> Float -> Float
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Float
one = Float
1.0
instance Divisive Float where
  recip :: Float -> Float
recip = forall a. Fractional a => a -> a
P.recip
instance Multiplicative Int where
  * :: Int -> Int -> Int
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Int
one = Int
1
instance Multiplicative Integer where
  * :: Integer -> Integer -> Integer
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Integer
one = Integer
1
instance Multiplicative P.Bool where
  * :: Bool -> Bool -> Bool
(*) = Bool -> Bool -> Bool
(P.&&)
  one :: Bool
one = Bool
P.True
instance Multiplicative Natural where
  * :: Natural -> Natural -> Natural
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Natural
one = Natural
1
instance Multiplicative Int8 where
  * :: Int8 -> Int8 -> Int8
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Int8
one = Int8
1
instance Multiplicative Int16 where
  * :: Int16 -> Int16 -> Int16
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Int16
one = Int16
1
instance Multiplicative Int32 where
  * :: Int32 -> Int32 -> Int32
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Int32
one = Int32
1
instance Multiplicative Int64 where
  * :: Int64 -> Int64 -> Int64
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Int64
one = Int64
1
instance Multiplicative Word where
  * :: Word -> Word -> Word
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Word
one = Word
1
instance Multiplicative Word8 where
  * :: Word8 -> Word8 -> Word8
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Word8
one = Word8
1
instance Multiplicative Word16 where
  * :: Word16 -> Word16 -> Word16
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Word16
one = Word16
1
instance Multiplicative Word32 where
  * :: Word32 -> Word32 -> Word32
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Word32
one = Word32
1
instance Multiplicative Word64 where
  * :: Word64 -> Word64 -> Word64
(*) = forall a. Num a => a -> a -> a
(P.*)
  one :: Word64
one = Word64
1
instance (Multiplicative b) => Multiplicative (a -> b) where
  a -> b
f * :: (a -> b) -> (a -> b) -> a -> b
* a -> b
f' = \a
a -> a -> b
f a
a forall a. Multiplicative a => a -> a -> a
* a -> b
f' a
a
  one :: a -> b
one a
_ = forall a. Multiplicative a => a
one
instance (Divisive b) => Divisive (a -> b) where
  recip :: (a -> b) -> a -> b
recip a -> b
f = forall a. Divisive a => a -> a
recip forall b c a. (b -> c) -> (a -> b) -> a -> c
P.. a -> b
f