{-# Language ConstrainedClassMethods #-}
{-# Language DefaultSignatures #-}
{-# Language DeriveFunctor #-}
{-# Language DeriveGeneric #-}
module Data.Semiring where
import Control.Applicative
import Control.Monad
import Data.Complex
import Data.Foldable hiding (product)
import Data.Functor.Apply
import Data.Functor.Classes
import Data.Functor.Contravariant (Predicate(..), Equivalence(..), Op(..))
import Data.Functor.Identity (Identity(..))
import Data.Group
import Data.List (unfoldr)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Semigroup
import Data.Semigroup.Foldable
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import GHC.Generics (Generic, Generic1)
import GHC.Real (even, quot)
import Numeric.Natural
import Prelude hiding ((^), replicate, sum, product)
import qualified Data.Map as Map
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import qualified Data.IntMap as IntMap
infixr 7 ><
class Semigroup r => Semiring r where
(><) :: r -> r -> r
fromBoolean :: Monoid r => Bool -> r
fromBoolean _ = mempty
sunit :: (Monoid r, Semiring r) => r
sunit = fromBoolean True
fromBooleanDef :: (Monoid r, Semiring r) => r -> Bool -> r
fromBooleanDef _ False = mempty
fromBooleanDef o True = o
product :: Foldable t => Monoid r => Semiring r => (a -> r) -> t a -> r
product f = foldr' ((><) . f) sunit
product1 :: Foldable1 t => Semiring r => (a -> r) -> t a -> r
product1 f = getProd . foldMap1 (Prod . f)
cross :: Foldable f => Applicative f => Monoid r => Semiring r => f r -> f r -> r
cross a b = fold $ liftA2 (><) a b
cross1 :: Foldable1 f => Apply f => Semiring r => f r -> f r -> r
cross1 a b = fold1 $ liftF2 (><) a b
replicate :: Monoid r => Natural -> r -> r
replicate y0 x0
| y0 == 0 = mempty
| otherwise = f x0 y0
where
f x y
| even y = f (x <> x) (y `quot` 2)
| y == 1 = x
| otherwise = g (x <> x) ((y - 1) `quot` 2) x
g x y z
| even y = g (x <> x) (y `quot` 2) z
| y == 1 = x <> z
| otherwise = g (x <> x) ((y - 1) `quot` 2) (x <> z)
{-# INLINE replicate #-}
replicate' :: Monoid r => Semiring r => Natural -> r -> r
replicate' n r = getProd $ replicate n (Prod r)
infixr 8 ^
(^) :: Monoid r => Semiring r => r -> Natural -> r
(^) = flip replicate'
powers :: Monoid r => Semiring r => Natural -> r -> r
powers n a = foldr' (<>) sunit . flip unfoldr n $ \m ->
if m == 0 then Nothing else Just (a^m,m-1)
class Semiring a => Kleene a where
{-# MINIMAL star | plus #-}
star :: a -> a
default star :: Monoid a => a -> a
star a = sunit <> plus a
plus :: a -> a
plus a = a >< star a
instance Kleene () where
star _ = ()
plus _ = ()
{-# INLINE star #-}
{-# INLINE plus #-}
instance (Monoid b, Kleene b) => Kleene (a -> b) where
plus = fmap plus
{-# INLINE plus #-}
star = fmap star
{-# INLINE star #-}
instance Semigroup a => Semiring (First a) where
(><) = liftA2 (<>)
{-# INLINE (><) #-}
instance Semigroup a => Semiring (Last a) where
(><) = liftA2 (<>)
{-# INLINE (><) #-}
instance Ord a => Semiring (Max a) where
(><) = min
{-# INLINE (><) #-}
instance Ord a => Semiring (Min a) where
(><) = max
{-# INLINE (><) #-}
instance Semigroup a => Semiring (Either e a) where
(><) = liftA2 (<>)
{-# INLINE (><) #-}
instance Semigroup a => Semiring (NonEmpty a) where
(><) = liftA2 (<>)
{-# INLINE (><) #-}
instance Semiring () where
(><) _ _ = ()
fromBoolean _ = ()
instance Semiring Ordering where
LT >< LT = LT
LT >< GT = LT
_ >< EQ = EQ
EQ >< _ = EQ
GT >< x = x
fromBoolean = fromBooleanDef GT
instance (Monoid b, Semiring b) => Semiring (a -> b) where
(><) = liftA2 (><)
{-# INLINE (><) #-}
fromBoolean = const . fromBoolean
instance (Monoid a, Semiring a) => Semiring (Op a b) where
Op f >< Op g = Op $ \x -> f x >< g x
{-# INLINE (><) #-}
fromBoolean = fromBooleanDef $ Op (const sunit)
instance (Monoid a, Monoid b, Semiring a, Semiring b) => Semiring (a, b) where
(a, b) >< (c, d) = (a><c, b><d)
{-# INLINE (><) #-}
fromBoolean = liftA2 (,) fromBoolean fromBoolean
instance (Semigroup (Complex a), Group a, Semiring a) => Semiring (Complex a) where
(x :+ y) >< (x' :+ y') = (x >< x' << y >< y') :+ (x >< y' <> y >< x')
{-# INLINE (><) #-}
fromBoolean False = mempty
fromBoolean True = fromBoolean True :+ mempty
{-# INLINE fromBoolean #-}
instance Monoid a => Semiring [a] where
(><) = liftA2 (<>)
{-# INLINE (><) #-}
fromBoolean = fromBooleanDef $ pure mempty
instance (Monoid a, Semiring a) => Semiring (Maybe a) where
(><) = liftA2 (><)
{-# INLINE (><) #-}
fromBoolean = fromBooleanDef $ pure mempty
instance (Monoid a, Semiring a) => Semiring (Dual a) where
(><) = liftA2 $ flip (><)
{-# INLINE (><) #-}
fromBoolean = Dual . fromBoolean
{-# INLINE fromBoolean #-}
instance (Monoid a, Semiring a) => Semiring (Const a b) where
(Const x) >< (Const y) = Const (x >< y)
{-# INLINE (><) #-}
fromBoolean = Const . fromBoolean
{-# INLINE fromBoolean #-}
instance (Monoid a, Semiring a) => Semiring (Identity a) where
(><) = liftA2 (><)
{-# INLINE (><) #-}
fromBoolean = fromBooleanDef $ pure mempty
instance Semiring Any where
Any x >< Any y = Any $ x && y
{-# INLINE (><) #-}
fromBoolean = fromBooleanDef $ Any True
instance Semiring All where
All x >< All y = All $ x || y
{-# INLINE (><) #-}
fromBoolean False = All True
fromBoolean True = All False
instance (Monoid a, Semiring a) => Semiring (IO a) where
(><) = liftA2 (><)
{-# INLINE (><) #-}
fromBoolean = fromBooleanDef $ pure mempty
instance Semiring (Predicate a) where
Predicate f >< Predicate g = Predicate $ \x -> f x || g x
{-# INLINE (><) #-}
fromBoolean False = Predicate $ const True
fromBoolean True = Predicate $ const False
instance Semiring (Equivalence a) where
Equivalence f >< Equivalence g = Equivalence $ \x y -> f x y || g x y
{-# INLINE (><) #-}
fromBoolean False = Equivalence $ \_ _ -> True
fromBoolean True = Equivalence $ \_ _ -> False
instance Ord a => Semiring (Set.Set a) where
(><) = Set.intersection
instance Monoid a => Semiring (Seq.Seq a) where
(><) = liftA2 (<>)
{-# INLINE (><) #-}
fromBoolean = fromBooleanDef $ Seq.singleton mempty
instance (Ord k, Monoid k, Monoid a) => Semiring (Map.Map k a) where
xs >< ys = foldMap (flip Map.map xs . (<>)) ys
{-# INLINE (><) #-}
fromBoolean = fromBooleanDef $ Map.singleton mempty mempty
instance Monoid a => Semiring (IntMap.IntMap a) where
xs >< ys = foldMap (flip IntMap.map xs . (<>)) ys
{-# INLINE (><) #-}
fromBoolean = fromBooleanDef $ IntMap.singleton 0 mempty
newtype Prod a = Prod { getProd :: a }
deriving (Eq,Ord,Show,Bounded,Generic,Generic1,Typeable,Functor)
instance Applicative Prod where
pure = Prod
Prod f <*> Prod a = Prod (f a)
instance Semiring a => Semigroup (Prod a) where
(<>) = liftA2 (><)
{-# INLINE (<>) #-}
instance (Monoid a, Semiring a) => Monoid (Prod a) where
mempty = Prod sunit
{-# INLINE mempty #-}