{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ConstraintKinds #-}
module Data.Act.Act
(
LAct (..)
, LActSg
, LActMn
, LActGp
, LActDistrib
, LActSgMorph
, LActNeutral
, LActMnMorph
, RAct (..)
, RActSg
, RActMn
, RActGp
, RActDistrib
, RActSgMorph
, RActNeutral
, RActMnMorph
, ActSelf (..)
, ActSelf' (..)
, ActMap (..)
, ActFold (..)
, ActFold' (..)
, ActTrivial (..)
) where
import Data.Semigroup as Sg
import Data.Monoid as Mn
import Data.Group
import Data.Functor.Identity
import Data.Foldable
import Data.Coerce
class LAct x s where
{-# MINIMAL lact | (<>$) #-}
lact :: s -> x -> x
lact = s -> x -> x
forall x s. LAct x s => s -> x -> x
(<>$)
{-# INLINE lact #-}
infixr 5 `lact`
(<>$) :: s -> x -> x
(<>$) = s -> x -> x
forall x s. LAct x s => s -> x -> x
lact
{-# INLINE (<>$) #-}
infixr 5 <>$
class (LAct x s, Semigroup s) => LActSg x s
class (LActSg x s, Monoid s) => LActMn x s
type LActGp x s = (LActMn x s, Group s)
class (LAct x s, Semigroup x) => LActDistrib x s
type LActSgMorph x s = (LActSg x s, LActDistrib x s)
class (LAct x s, Monoid x) => LActNeutral x s
type LActMnMorph x s = (LActMn x s, LActSgMorph x s, LActNeutral x s)
class RAct x s where
{-# MINIMAL ract | ($<>) #-}
ract :: x -> s -> x
ract = x -> s -> x
forall x s. RAct x s => x -> s -> x
($<>)
{-# INLINE ract #-}
infixl 5 `ract`
($<>) :: x -> s -> x
($<>) = x -> s -> x
forall x s. RAct x s => x -> s -> x
ract
{-# INLINE ($<>) #-}
infixl 5 $<>
class (RAct x s, Semigroup s) => RActSg x s
class (RActSg x s, Monoid s) => RActMn x s
type RActGp x s = (RActMn x s, Group s)
class (RAct x s, Semigroup x) => RActDistrib x s
type RActSgMorph x s = (RActSg x s, RActDistrib x s)
class (RAct x s, Monoid x) => RActNeutral x s
type RActMnMorph x s = (RActMn x s, RActSgMorph x s, RActNeutral x s)
newtype ActSelf s = ActSelf {forall s. ActSelf s -> s
unactSelf :: s}
deriving stock (Int -> ActSelf s -> ShowS
[ActSelf s] -> ShowS
ActSelf s -> String
(Int -> ActSelf s -> ShowS)
-> (ActSelf s -> String)
-> ([ActSelf s] -> ShowS)
-> Show (ActSelf s)
forall s. Show s => Int -> ActSelf s -> ShowS
forall s. Show s => [ActSelf s] -> ShowS
forall s. Show s => ActSelf s -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall s. Show s => Int -> ActSelf s -> ShowS
showsPrec :: Int -> ActSelf s -> ShowS
$cshow :: forall s. Show s => ActSelf s -> String
show :: ActSelf s -> String
$cshowList :: forall s. Show s => [ActSelf s] -> ShowS
showList :: [ActSelf s] -> ShowS
Show, ActSelf s -> ActSelf s -> Bool
(ActSelf s -> ActSelf s -> Bool)
-> (ActSelf s -> ActSelf s -> Bool) -> Eq (ActSelf s)
forall s. Eq s => ActSelf s -> ActSelf s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall s. Eq s => ActSelf s -> ActSelf s -> Bool
== :: ActSelf s -> ActSelf s -> Bool
$c/= :: forall s. Eq s => ActSelf s -> ActSelf s -> Bool
/= :: ActSelf s -> ActSelf s -> Bool
Eq)
deriving newtype (NonEmpty (ActSelf s) -> ActSelf s
ActSelf s -> ActSelf s -> ActSelf s
(ActSelf s -> ActSelf s -> ActSelf s)
-> (NonEmpty (ActSelf s) -> ActSelf s)
-> (forall b. Integral b => b -> ActSelf s -> ActSelf s)
-> Semigroup (ActSelf s)
forall b. Integral b => b -> ActSelf s -> ActSelf s
forall s. Semigroup s => NonEmpty (ActSelf s) -> ActSelf s
forall s. Semigroup s => ActSelf s -> ActSelf s -> ActSelf s
forall s b.
(Semigroup s, Integral b) =>
b -> ActSelf s -> ActSelf s
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: forall s. Semigroup s => ActSelf s -> ActSelf s -> ActSelf s
<> :: ActSelf s -> ActSelf s -> ActSelf s
$csconcat :: forall s. Semigroup s => NonEmpty (ActSelf s) -> ActSelf s
sconcat :: NonEmpty (ActSelf s) -> ActSelf s
$cstimes :: forall s b.
(Semigroup s, Integral b) =>
b -> ActSelf s -> ActSelf s
stimes :: forall b. Integral b => b -> ActSelf s -> ActSelf s
Semigroup, Semigroup (ActSelf s)
ActSelf s
Semigroup (ActSelf s) =>
ActSelf s
-> (ActSelf s -> ActSelf s -> ActSelf s)
-> ([ActSelf s] -> ActSelf s)
-> Monoid (ActSelf s)
[ActSelf s] -> ActSelf s
ActSelf s -> ActSelf s -> ActSelf s
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall s. Monoid s => Semigroup (ActSelf s)
forall s. Monoid s => ActSelf s
forall s. Monoid s => [ActSelf s] -> ActSelf s
forall s. Monoid s => ActSelf s -> ActSelf s -> ActSelf s
$cmempty :: forall s. Monoid s => ActSelf s
mempty :: ActSelf s
$cmappend :: forall s. Monoid s => ActSelf s -> ActSelf s -> ActSelf s
mappend :: ActSelf s -> ActSelf s -> ActSelf s
$cmconcat :: forall s. Monoid s => [ActSelf s] -> ActSelf s
mconcat :: [ActSelf s] -> ActSelf s
Monoid, Monoid (ActSelf s)
Monoid (ActSelf s) =>
(ActSelf s -> ActSelf s)
-> (ActSelf s -> ActSelf s -> ActSelf s)
-> (forall x. Integral x => ActSelf s -> x -> ActSelf s)
-> Group (ActSelf s)
ActSelf s -> ActSelf s
ActSelf s -> ActSelf s -> ActSelf s
forall x. Integral x => ActSelf s -> x -> ActSelf s
forall m.
Monoid m =>
(m -> m)
-> (m -> m -> m)
-> (forall x. Integral x => m -> x -> m)
-> Group m
forall s. Group s => Monoid (ActSelf s)
forall s. Group s => ActSelf s -> ActSelf s
forall s. Group s => ActSelf s -> ActSelf s -> ActSelf s
forall s x. (Group s, Integral x) => ActSelf s -> x -> ActSelf s
$cinvert :: forall s. Group s => ActSelf s -> ActSelf s
invert :: ActSelf s -> ActSelf s
$c~~ :: forall s. Group s => ActSelf s -> ActSelf s -> ActSelf s
~~ :: ActSelf s -> ActSelf s -> ActSelf s
$cpow :: forall s x. (Group s, Integral x) => ActSelf s -> x -> ActSelf s
pow :: forall x. Integral x => ActSelf s -> x -> ActSelf s
Group)
instance Semigroup s => LAct s (ActSelf s) where
ActSelf s
s <>$ :: ActSelf s -> s -> s
<>$ s
x = s
s s -> s -> s
forall a. Semigroup a => a -> a -> a
<> s
x
{-# INLINE (<>$) #-}
instance Semigroup s => LActSg s (ActSelf s)
instance Monoid s => LActMn s (ActSelf s)
instance Semigroup s => RAct s (ActSelf s) where
s
x $<> :: s -> ActSelf s -> s
$<> ActSelf s
s = s
x s -> s -> s
forall a. Semigroup a => a -> a -> a
<> s
s
{-# INLINE ($<>) #-}
instance Semigroup s => RActSg s (ActSelf s)
instance Monoid s => RActMn s (ActSelf s)
newtype ActSelf' x = ActSelf' {forall x. ActSelf' x -> x
unactCoerce :: x}
deriving stock (Int -> ActSelf' x -> ShowS
[ActSelf' x] -> ShowS
ActSelf' x -> String
(Int -> ActSelf' x -> ShowS)
-> (ActSelf' x -> String)
-> ([ActSelf' x] -> ShowS)
-> Show (ActSelf' x)
forall x. Show x => Int -> ActSelf' x -> ShowS
forall x. Show x => [ActSelf' x] -> ShowS
forall x. Show x => ActSelf' x -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall x. Show x => Int -> ActSelf' x -> ShowS
showsPrec :: Int -> ActSelf' x -> ShowS
$cshow :: forall x. Show x => ActSelf' x -> String
show :: ActSelf' x -> String
$cshowList :: forall x. Show x => [ActSelf' x] -> ShowS
showList :: [ActSelf' x] -> ShowS
Show, ActSelf' x -> ActSelf' x -> Bool
(ActSelf' x -> ActSelf' x -> Bool)
-> (ActSelf' x -> ActSelf' x -> Bool) -> Eq (ActSelf' x)
forall x. Eq x => ActSelf' x -> ActSelf' x -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall x. Eq x => ActSelf' x -> ActSelf' x -> Bool
== :: ActSelf' x -> ActSelf' x -> Bool
$c/= :: forall x. Eq x => ActSelf' x -> ActSelf' x -> Bool
/= :: ActSelf' x -> ActSelf' x -> Bool
Eq)
deriving newtype (NonEmpty (ActSelf' x) -> ActSelf' x
ActSelf' x -> ActSelf' x -> ActSelf' x
(ActSelf' x -> ActSelf' x -> ActSelf' x)
-> (NonEmpty (ActSelf' x) -> ActSelf' x)
-> (forall b. Integral b => b -> ActSelf' x -> ActSelf' x)
-> Semigroup (ActSelf' x)
forall b. Integral b => b -> ActSelf' x -> ActSelf' x
forall x. Semigroup x => NonEmpty (ActSelf' x) -> ActSelf' x
forall x. Semigroup x => ActSelf' x -> ActSelf' x -> ActSelf' x
forall x b.
(Semigroup x, Integral b) =>
b -> ActSelf' x -> ActSelf' x
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: forall x. Semigroup x => ActSelf' x -> ActSelf' x -> ActSelf' x
<> :: ActSelf' x -> ActSelf' x -> ActSelf' x
$csconcat :: forall x. Semigroup x => NonEmpty (ActSelf' x) -> ActSelf' x
sconcat :: NonEmpty (ActSelf' x) -> ActSelf' x
$cstimes :: forall x b.
(Semigroup x, Integral b) =>
b -> ActSelf' x -> ActSelf' x
stimes :: forall b. Integral b => b -> ActSelf' x -> ActSelf' x
Semigroup, Semigroup (ActSelf' x)
ActSelf' x
Semigroup (ActSelf' x) =>
ActSelf' x
-> (ActSelf' x -> ActSelf' x -> ActSelf' x)
-> ([ActSelf' x] -> ActSelf' x)
-> Monoid (ActSelf' x)
[ActSelf' x] -> ActSelf' x
ActSelf' x -> ActSelf' x -> ActSelf' x
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall x. Monoid x => Semigroup (ActSelf' x)
forall x. Monoid x => ActSelf' x
forall x. Monoid x => [ActSelf' x] -> ActSelf' x
forall x. Monoid x => ActSelf' x -> ActSelf' x -> ActSelf' x
$cmempty :: forall x. Monoid x => ActSelf' x
mempty :: ActSelf' x
$cmappend :: forall x. Monoid x => ActSelf' x -> ActSelf' x -> ActSelf' x
mappend :: ActSelf' x -> ActSelf' x -> ActSelf' x
$cmconcat :: forall x. Monoid x => [ActSelf' x] -> ActSelf' x
mconcat :: [ActSelf' x] -> ActSelf' x
Monoid, Monoid (ActSelf' x)
Monoid (ActSelf' x) =>
(ActSelf' x -> ActSelf' x)
-> (ActSelf' x -> ActSelf' x -> ActSelf' x)
-> (forall x. Integral x => ActSelf' x -> x -> ActSelf' x)
-> Group (ActSelf' x)
ActSelf' x -> ActSelf' x
ActSelf' x -> ActSelf' x -> ActSelf' x
forall x. Integral x => ActSelf' x -> x -> ActSelf' x
forall m.
Monoid m =>
(m -> m)
-> (m -> m -> m)
-> (forall x. Integral x => m -> x -> m)
-> Group m
forall x. Group x => Monoid (ActSelf' x)
forall x. Group x => ActSelf' x -> ActSelf' x
forall x. Group x => ActSelf' x -> ActSelf' x -> ActSelf' x
forall x x. (Group x, Integral x) => ActSelf' x -> x -> ActSelf' x
$cinvert :: forall x. Group x => ActSelf' x -> ActSelf' x
invert :: ActSelf' x -> ActSelf' x
$c~~ :: forall x. Group x => ActSelf' x -> ActSelf' x -> ActSelf' x
~~ :: ActSelf' x -> ActSelf' x -> ActSelf' x
$cpow :: forall x x. (Group x, Integral x) => ActSelf' x -> x -> ActSelf' x
pow :: forall x. Integral x => ActSelf' x -> x -> ActSelf' x
Group)
instance {-# OVERLAPPABLE #-} (Semigroup s, Coercible x s)
=> LAct x (ActSelf' s) where
ActSelf' s
s <>$ :: ActSelf' s -> x -> x
<>$ x
x = s -> x
forall a b. Coercible a b => a -> b
coerce (s -> x) -> s -> x
forall a b. (a -> b) -> a -> b
$ s
s s -> s -> s
forall a. Semigroup a => a -> a -> a
<> (x -> s
forall a b. Coercible a b => a -> b
coerce x
x :: s)
{-# INLINE (<>$) #-}
instance (Coercible x s, Semigroup s) => LActSg x (ActSelf' s)
instance (Coercible x s, Monoid s) => LActMn x (ActSelf' s)
instance {-# OVERLAPPABLE #-} (Semigroup s, Coercible x s)
=> RAct x (ActSelf' s) where
x
x $<> :: x -> ActSelf' s -> x
$<> ActSelf' s
s = s -> x
forall a b. Coercible a b => a -> b
coerce (s -> x) -> s -> x
forall a b. (a -> b) -> a -> b
$ (x -> s
forall a b. Coercible a b => a -> b
coerce x
x :: s) s -> s -> s
forall a. Semigroup a => a -> a -> a
<> s
s
{-# INLINE ($<>) #-}
instance (Coercible x s, Semigroup s) => RActSg x (ActSelf' s)
instance (Coercible x s, Monoid s) => RActMn x (ActSelf' s)
newtype ActTrivial x = ActTrivial {forall x. ActTrivial x -> x
unactId :: x}
deriving stock (Int -> ActTrivial x -> ShowS
[ActTrivial x] -> ShowS
ActTrivial x -> String
(Int -> ActTrivial x -> ShowS)
-> (ActTrivial x -> String)
-> ([ActTrivial x] -> ShowS)
-> Show (ActTrivial x)
forall x. Show x => Int -> ActTrivial x -> ShowS
forall x. Show x => [ActTrivial x] -> ShowS
forall x. Show x => ActTrivial x -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall x. Show x => Int -> ActTrivial x -> ShowS
showsPrec :: Int -> ActTrivial x -> ShowS
$cshow :: forall x. Show x => ActTrivial x -> String
show :: ActTrivial x -> String
$cshowList :: forall x. Show x => [ActTrivial x] -> ShowS
showList :: [ActTrivial x] -> ShowS
Show, ActTrivial x -> ActTrivial x -> Bool
(ActTrivial x -> ActTrivial x -> Bool)
-> (ActTrivial x -> ActTrivial x -> Bool) -> Eq (ActTrivial x)
forall x. Eq x => ActTrivial x -> ActTrivial x -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall x. Eq x => ActTrivial x -> ActTrivial x -> Bool
== :: ActTrivial x -> ActTrivial x -> Bool
$c/= :: forall x. Eq x => ActTrivial x -> ActTrivial x -> Bool
/= :: ActTrivial x -> ActTrivial x -> Bool
Eq)
deriving newtype (NonEmpty (ActTrivial x) -> ActTrivial x
ActTrivial x -> ActTrivial x -> ActTrivial x
(ActTrivial x -> ActTrivial x -> ActTrivial x)
-> (NonEmpty (ActTrivial x) -> ActTrivial x)
-> (forall b. Integral b => b -> ActTrivial x -> ActTrivial x)
-> Semigroup (ActTrivial x)
forall b. Integral b => b -> ActTrivial x -> ActTrivial x
forall x. Semigroup x => NonEmpty (ActTrivial x) -> ActTrivial x
forall x.
Semigroup x =>
ActTrivial x -> ActTrivial x -> ActTrivial x
forall x b.
(Semigroup x, Integral b) =>
b -> ActTrivial x -> ActTrivial x
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: forall x.
Semigroup x =>
ActTrivial x -> ActTrivial x -> ActTrivial x
<> :: ActTrivial x -> ActTrivial x -> ActTrivial x
$csconcat :: forall x. Semigroup x => NonEmpty (ActTrivial x) -> ActTrivial x
sconcat :: NonEmpty (ActTrivial x) -> ActTrivial x
$cstimes :: forall x b.
(Semigroup x, Integral b) =>
b -> ActTrivial x -> ActTrivial x
stimes :: forall b. Integral b => b -> ActTrivial x -> ActTrivial x
Semigroup, Semigroup (ActTrivial x)
ActTrivial x
Semigroup (ActTrivial x) =>
ActTrivial x
-> (ActTrivial x -> ActTrivial x -> ActTrivial x)
-> ([ActTrivial x] -> ActTrivial x)
-> Monoid (ActTrivial x)
[ActTrivial x] -> ActTrivial x
ActTrivial x -> ActTrivial x -> ActTrivial x
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall x. Monoid x => Semigroup (ActTrivial x)
forall x. Monoid x => ActTrivial x
forall x. Monoid x => [ActTrivial x] -> ActTrivial x
forall x. Monoid x => ActTrivial x -> ActTrivial x -> ActTrivial x
$cmempty :: forall x. Monoid x => ActTrivial x
mempty :: ActTrivial x
$cmappend :: forall x. Monoid x => ActTrivial x -> ActTrivial x -> ActTrivial x
mappend :: ActTrivial x -> ActTrivial x -> ActTrivial x
$cmconcat :: forall x. Monoid x => [ActTrivial x] -> ActTrivial x
mconcat :: [ActTrivial x] -> ActTrivial x
Monoid, Monoid (ActTrivial x)
Monoid (ActTrivial x) =>
(ActTrivial x -> ActTrivial x)
-> (ActTrivial x -> ActTrivial x -> ActTrivial x)
-> (forall x. Integral x => ActTrivial x -> x -> ActTrivial x)
-> Group (ActTrivial x)
ActTrivial x -> ActTrivial x
ActTrivial x -> ActTrivial x -> ActTrivial x
forall x. Integral x => ActTrivial x -> x -> ActTrivial x
forall m.
Monoid m =>
(m -> m)
-> (m -> m -> m)
-> (forall x. Integral x => m -> x -> m)
-> Group m
forall x. Group x => Monoid (ActTrivial x)
forall x. Group x => ActTrivial x -> ActTrivial x
forall x. Group x => ActTrivial x -> ActTrivial x -> ActTrivial x
forall x x.
(Group x, Integral x) =>
ActTrivial x -> x -> ActTrivial x
$cinvert :: forall x. Group x => ActTrivial x -> ActTrivial x
invert :: ActTrivial x -> ActTrivial x
$c~~ :: forall x. Group x => ActTrivial x -> ActTrivial x -> ActTrivial x
~~ :: ActTrivial x -> ActTrivial x -> ActTrivial x
$cpow :: forall x x.
(Group x, Integral x) =>
ActTrivial x -> x -> ActTrivial x
pow :: forall x. Integral x => ActTrivial x -> x -> ActTrivial x
Group)
instance LAct x (ActTrivial s) where
<>$ :: ActTrivial s -> x -> x
(<>$) ActTrivial s
_ = x -> x
forall a. a -> a
id
{-# INLINE (<>$) #-}
instance Semigroup s => LActSg x (ActTrivial s)
instance Monoid s => LActMn x (ActTrivial s)
instance Semigroup x => LActDistrib x (ActTrivial s)
instance Monoid x => LActNeutral x (ActTrivial s)
instance RAct x (ActTrivial s) where
x
x $<> :: x -> ActTrivial s -> x
$<> ActTrivial s
_ = x
x
{-# INLINE ($<>) #-}
instance Semigroup s => RActSg x (ActTrivial s)
instance Monoid s => RActMn x (ActTrivial s)
instance Semigroup x => RActDistrib x (ActTrivial s)
instance Monoid x => RActNeutral x (ActTrivial s)
newtype ActMap s = ActMap {forall s. ActMap s -> s
unactMap :: s}
deriving stock (Int -> ActMap s -> ShowS
[ActMap s] -> ShowS
ActMap s -> String
(Int -> ActMap s -> ShowS)
-> (ActMap s -> String) -> ([ActMap s] -> ShowS) -> Show (ActMap s)
forall s. Show s => Int -> ActMap s -> ShowS
forall s. Show s => [ActMap s] -> ShowS
forall s. Show s => ActMap s -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall s. Show s => Int -> ActMap s -> ShowS
showsPrec :: Int -> ActMap s -> ShowS
$cshow :: forall s. Show s => ActMap s -> String
show :: ActMap s -> String
$cshowList :: forall s. Show s => [ActMap s] -> ShowS
showList :: [ActMap s] -> ShowS
Show, ActMap s -> ActMap s -> Bool
(ActMap s -> ActMap s -> Bool)
-> (ActMap s -> ActMap s -> Bool) -> Eq (ActMap s)
forall s. Eq s => ActMap s -> ActMap s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall s. Eq s => ActMap s -> ActMap s -> Bool
== :: ActMap s -> ActMap s -> Bool
$c/= :: forall s. Eq s => ActMap s -> ActMap s -> Bool
/= :: ActMap s -> ActMap s -> Bool
Eq)
deriving newtype (NonEmpty (ActMap s) -> ActMap s
ActMap s -> ActMap s -> ActMap s
(ActMap s -> ActMap s -> ActMap s)
-> (NonEmpty (ActMap s) -> ActMap s)
-> (forall b. Integral b => b -> ActMap s -> ActMap s)
-> Semigroup (ActMap s)
forall b. Integral b => b -> ActMap s -> ActMap s
forall s. Semigroup s => NonEmpty (ActMap s) -> ActMap s
forall s. Semigroup s => ActMap s -> ActMap s -> ActMap s
forall s b. (Semigroup s, Integral b) => b -> ActMap s -> ActMap s
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: forall s. Semigroup s => ActMap s -> ActMap s -> ActMap s
<> :: ActMap s -> ActMap s -> ActMap s
$csconcat :: forall s. Semigroup s => NonEmpty (ActMap s) -> ActMap s
sconcat :: NonEmpty (ActMap s) -> ActMap s
$cstimes :: forall s b. (Semigroup s, Integral b) => b -> ActMap s -> ActMap s
stimes :: forall b. Integral b => b -> ActMap s -> ActMap s
Semigroup, Semigroup (ActMap s)
ActMap s
Semigroup (ActMap s) =>
ActMap s
-> (ActMap s -> ActMap s -> ActMap s)
-> ([ActMap s] -> ActMap s)
-> Monoid (ActMap s)
[ActMap s] -> ActMap s
ActMap s -> ActMap s -> ActMap s
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall s. Monoid s => Semigroup (ActMap s)
forall s. Monoid s => ActMap s
forall s. Monoid s => [ActMap s] -> ActMap s
forall s. Monoid s => ActMap s -> ActMap s -> ActMap s
$cmempty :: forall s. Monoid s => ActMap s
mempty :: ActMap s
$cmappend :: forall s. Monoid s => ActMap s -> ActMap s -> ActMap s
mappend :: ActMap s -> ActMap s -> ActMap s
$cmconcat :: forall s. Monoid s => [ActMap s] -> ActMap s
mconcat :: [ActMap s] -> ActMap s
Monoid, Monoid (ActMap s)
Monoid (ActMap s) =>
(ActMap s -> ActMap s)
-> (ActMap s -> ActMap s -> ActMap s)
-> (forall x. Integral x => ActMap s -> x -> ActMap s)
-> Group (ActMap s)
ActMap s -> ActMap s
ActMap s -> ActMap s -> ActMap s
forall x. Integral x => ActMap s -> x -> ActMap s
forall m.
Monoid m =>
(m -> m)
-> (m -> m -> m)
-> (forall x. Integral x => m -> x -> m)
-> Group m
forall s. Group s => Monoid (ActMap s)
forall s. Group s => ActMap s -> ActMap s
forall s. Group s => ActMap s -> ActMap s -> ActMap s
forall s x. (Group s, Integral x) => ActMap s -> x -> ActMap s
$cinvert :: forall s. Group s => ActMap s -> ActMap s
invert :: ActMap s -> ActMap s
$c~~ :: forall s. Group s => ActMap s -> ActMap s -> ActMap s
~~ :: ActMap s -> ActMap s -> ActMap s
$cpow :: forall s x. (Group s, Integral x) => ActMap s -> x -> ActMap s
pow :: forall x. Integral x => ActMap s -> x -> ActMap s
Group)
instance (LAct x s, Functor f) => LAct (f x) (ActMap s) where
ActMap s
s <>$ :: ActMap s -> f x -> f x
<>$ f x
x = (x -> x) -> f x -> f x
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (s
s s -> x -> x
forall x s. LAct x s => s -> x -> x
<>$) f x
x
{-# INLINE (<>$) #-}
instance (LActSg x s, Functor f) => LActSg (f x) (ActMap s)
instance (LActMn x s, Functor f) => LActMn (f x) (ActMap s)
instance LAct x s => LActDistrib [x] (ActMap s)
instance LAct x s => LActNeutral [x] (ActMap s)
instance (RAct x s, Functor f) => RAct (f x) (ActMap s) where
f x
x $<> :: f x -> ActMap s -> f x
$<> ActMap s
s = (x -> x) -> f x -> f x
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (x -> s -> x
forall x s. RAct x s => x -> s -> x
$<> s
s) f x
x
{-# INLINE ($<>) #-}
instance (RActSg x s, Functor f) => RActSg (f x) (ActMap s)
instance (RActMn x s, Functor f) => RActMn (f x) (ActMap s)
instance RAct x s => RActDistrib [x] (ActMap s)
instance RAct x s => RActNeutral [x] (ActMap s)
newtype ActFold s = ActFold {forall s. ActFold s -> s
unactFold :: s}
deriving stock (Int -> ActFold s -> ShowS
[ActFold s] -> ShowS
ActFold s -> String
(Int -> ActFold s -> ShowS)
-> (ActFold s -> String)
-> ([ActFold s] -> ShowS)
-> Show (ActFold s)
forall s. Show s => Int -> ActFold s -> ShowS
forall s. Show s => [ActFold s] -> ShowS
forall s. Show s => ActFold s -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall s. Show s => Int -> ActFold s -> ShowS
showsPrec :: Int -> ActFold s -> ShowS
$cshow :: forall s. Show s => ActFold s -> String
show :: ActFold s -> String
$cshowList :: forall s. Show s => [ActFold s] -> ShowS
showList :: [ActFold s] -> ShowS
Show, ActFold s -> ActFold s -> Bool
(ActFold s -> ActFold s -> Bool)
-> (ActFold s -> ActFold s -> Bool) -> Eq (ActFold s)
forall s. Eq s => ActFold s -> ActFold s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall s. Eq s => ActFold s -> ActFold s -> Bool
== :: ActFold s -> ActFold s -> Bool
$c/= :: forall s. Eq s => ActFold s -> ActFold s -> Bool
/= :: ActFold s -> ActFold s -> Bool
Eq)
deriving newtype (NonEmpty (ActFold s) -> ActFold s
ActFold s -> ActFold s -> ActFold s
(ActFold s -> ActFold s -> ActFold s)
-> (NonEmpty (ActFold s) -> ActFold s)
-> (forall b. Integral b => b -> ActFold s -> ActFold s)
-> Semigroup (ActFold s)
forall b. Integral b => b -> ActFold s -> ActFold s
forall s. Semigroup s => NonEmpty (ActFold s) -> ActFold s
forall s. Semigroup s => ActFold s -> ActFold s -> ActFold s
forall s b.
(Semigroup s, Integral b) =>
b -> ActFold s -> ActFold s
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: forall s. Semigroup s => ActFold s -> ActFold s -> ActFold s
<> :: ActFold s -> ActFold s -> ActFold s
$csconcat :: forall s. Semigroup s => NonEmpty (ActFold s) -> ActFold s
sconcat :: NonEmpty (ActFold s) -> ActFold s
$cstimes :: forall s b.
(Semigroup s, Integral b) =>
b -> ActFold s -> ActFold s
stimes :: forall b. Integral b => b -> ActFold s -> ActFold s
Semigroup, Semigroup (ActFold s)
ActFold s
Semigroup (ActFold s) =>
ActFold s
-> (ActFold s -> ActFold s -> ActFold s)
-> ([ActFold s] -> ActFold s)
-> Monoid (ActFold s)
[ActFold s] -> ActFold s
ActFold s -> ActFold s -> ActFold s
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall s. Monoid s => Semigroup (ActFold s)
forall s. Monoid s => ActFold s
forall s. Monoid s => [ActFold s] -> ActFold s
forall s. Monoid s => ActFold s -> ActFold s -> ActFold s
$cmempty :: forall s. Monoid s => ActFold s
mempty :: ActFold s
$cmappend :: forall s. Monoid s => ActFold s -> ActFold s -> ActFold s
mappend :: ActFold s -> ActFold s -> ActFold s
$cmconcat :: forall s. Monoid s => [ActFold s] -> ActFold s
mconcat :: [ActFold s] -> ActFold s
Monoid, Monoid (ActFold s)
Monoid (ActFold s) =>
(ActFold s -> ActFold s)
-> (ActFold s -> ActFold s -> ActFold s)
-> (forall x. Integral x => ActFold s -> x -> ActFold s)
-> Group (ActFold s)
ActFold s -> ActFold s
ActFold s -> ActFold s -> ActFold s
forall x. Integral x => ActFold s -> x -> ActFold s
forall m.
Monoid m =>
(m -> m)
-> (m -> m -> m)
-> (forall x. Integral x => m -> x -> m)
-> Group m
forall s. Group s => Monoid (ActFold s)
forall s. Group s => ActFold s -> ActFold s
forall s. Group s => ActFold s -> ActFold s -> ActFold s
forall s x. (Group s, Integral x) => ActFold s -> x -> ActFold s
$cinvert :: forall s. Group s => ActFold s -> ActFold s
invert :: ActFold s -> ActFold s
$c~~ :: forall s. Group s => ActFold s -> ActFold s -> ActFold s
~~ :: ActFold s -> ActFold s -> ActFold s
$cpow :: forall s x. (Group s, Integral x) => ActFold s -> x -> ActFold s
pow :: forall x. Integral x => ActFold s -> x -> ActFold s
Group)
instance (Foldable f, LAct x s) => LAct x (ActFold (f s)) where
ActFold f s
f <>$ :: ActFold (f s) -> x -> x
<>$ x
x = (s -> x -> x) -> x -> f s -> x
forall a b. (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr s -> x -> x
forall x s. LAct x s => s -> x -> x
(<>$) x
x f s
f
{-# INLINE (<>$) #-}
instance LAct x s => LActSg x (ActFold [s])
instance (Foldable f, RAct x s) => RAct x (ActFold (f s)) where
x
x $<> :: x -> ActFold (f s) -> x
$<> ActFold f s
f = (x -> s -> x) -> x -> f s -> x
forall b a. (b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl x -> s -> x
forall x s. RAct x s => x -> s -> x
($<>) x
x f s
f
{-# INLINE ($<>) #-}
newtype ActFold' s = ActFold' {forall s. ActFold' s -> s
unactFold' :: s}
deriving stock (Int -> ActFold' s -> ShowS
[ActFold' s] -> ShowS
ActFold' s -> String
(Int -> ActFold' s -> ShowS)
-> (ActFold' s -> String)
-> ([ActFold' s] -> ShowS)
-> Show (ActFold' s)
forall s. Show s => Int -> ActFold' s -> ShowS
forall s. Show s => [ActFold' s] -> ShowS
forall s. Show s => ActFold' s -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall s. Show s => Int -> ActFold' s -> ShowS
showsPrec :: Int -> ActFold' s -> ShowS
$cshow :: forall s. Show s => ActFold' s -> String
show :: ActFold' s -> String
$cshowList :: forall s. Show s => [ActFold' s] -> ShowS
showList :: [ActFold' s] -> ShowS
Show, ActFold' s -> ActFold' s -> Bool
(ActFold' s -> ActFold' s -> Bool)
-> (ActFold' s -> ActFold' s -> Bool) -> Eq (ActFold' s)
forall s. Eq s => ActFold' s -> ActFold' s -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall s. Eq s => ActFold' s -> ActFold' s -> Bool
== :: ActFold' s -> ActFold' s -> Bool
$c/= :: forall s. Eq s => ActFold' s -> ActFold' s -> Bool
/= :: ActFold' s -> ActFold' s -> Bool
Eq)
deriving newtype (NonEmpty (ActFold' s) -> ActFold' s
ActFold' s -> ActFold' s -> ActFold' s
(ActFold' s -> ActFold' s -> ActFold' s)
-> (NonEmpty (ActFold' s) -> ActFold' s)
-> (forall b. Integral b => b -> ActFold' s -> ActFold' s)
-> Semigroup (ActFold' s)
forall b. Integral b => b -> ActFold' s -> ActFold' s
forall s. Semigroup s => NonEmpty (ActFold' s) -> ActFold' s
forall s. Semigroup s => ActFold' s -> ActFold' s -> ActFold' s
forall s b.
(Semigroup s, Integral b) =>
b -> ActFold' s -> ActFold' s
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: forall s. Semigroup s => ActFold' s -> ActFold' s -> ActFold' s
<> :: ActFold' s -> ActFold' s -> ActFold' s
$csconcat :: forall s. Semigroup s => NonEmpty (ActFold' s) -> ActFold' s
sconcat :: NonEmpty (ActFold' s) -> ActFold' s
$cstimes :: forall s b.
(Semigroup s, Integral b) =>
b -> ActFold' s -> ActFold' s
stimes :: forall b. Integral b => b -> ActFold' s -> ActFold' s
Semigroup, Semigroup (ActFold' s)
ActFold' s
Semigroup (ActFold' s) =>
ActFold' s
-> (ActFold' s -> ActFold' s -> ActFold' s)
-> ([ActFold' s] -> ActFold' s)
-> Monoid (ActFold' s)
[ActFold' s] -> ActFold' s
ActFold' s -> ActFold' s -> ActFold' s
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall s. Monoid s => Semigroup (ActFold' s)
forall s. Monoid s => ActFold' s
forall s. Monoid s => [ActFold' s] -> ActFold' s
forall s. Monoid s => ActFold' s -> ActFold' s -> ActFold' s
$cmempty :: forall s. Monoid s => ActFold' s
mempty :: ActFold' s
$cmappend :: forall s. Monoid s => ActFold' s -> ActFold' s -> ActFold' s
mappend :: ActFold' s -> ActFold' s -> ActFold' s
$cmconcat :: forall s. Monoid s => [ActFold' s] -> ActFold' s
mconcat :: [ActFold' s] -> ActFold' s
Monoid, Monoid (ActFold' s)
Monoid (ActFold' s) =>
(ActFold' s -> ActFold' s)
-> (ActFold' s -> ActFold' s -> ActFold' s)
-> (forall x. Integral x => ActFold' s -> x -> ActFold' s)
-> Group (ActFold' s)
ActFold' s -> ActFold' s
ActFold' s -> ActFold' s -> ActFold' s
forall x. Integral x => ActFold' s -> x -> ActFold' s
forall m.
Monoid m =>
(m -> m)
-> (m -> m -> m)
-> (forall x. Integral x => m -> x -> m)
-> Group m
forall s. Group s => Monoid (ActFold' s)
forall s. Group s => ActFold' s -> ActFold' s
forall s. Group s => ActFold' s -> ActFold' s -> ActFold' s
forall s x. (Group s, Integral x) => ActFold' s -> x -> ActFold' s
$cinvert :: forall s. Group s => ActFold' s -> ActFold' s
invert :: ActFold' s -> ActFold' s
$c~~ :: forall s. Group s => ActFold' s -> ActFold' s -> ActFold' s
~~ :: ActFold' s -> ActFold' s -> ActFold' s
$cpow :: forall s x. (Group s, Integral x) => ActFold' s -> x -> ActFold' s
pow :: forall x. Integral x => ActFold' s -> x -> ActFold' s
Group)
instance (Foldable f, LAct x s) => LAct x (ActFold' (f s)) where
ActFold' f s
f <>$ :: ActFold' (f s) -> x -> x
<>$ x
x = (s -> x -> x) -> x -> f s -> x
forall a b. (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr' s -> x -> x
forall x s. LAct x s => s -> x -> x
(<>$) x
x f s
f
{-# INLINE (<>$) #-}
instance LAct x s => LActSg x (ActFold' [s])
instance (Foldable f, RAct x s) => RAct x (ActFold' (f s)) where
x
x $<> :: x -> ActFold' (f s) -> x
$<> ActFold' f s
f = (x -> s -> x) -> x -> f s -> x
forall b a. (b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' x -> s -> x
forall x s. RAct x s => x -> s -> x
($<>) x
x f s
f
{-# INLINE ($<>) #-}
instance LAct x () where
() <>$ :: () -> x -> x
<>$ x
x = x
x
{-# INLINE (<>$) #-}
instance LActSg x ()
instance LActMn x ()
instance Semigroup x => LActDistrib x ()
instance Monoid x => LActNeutral x ()
instance RAct x () where
x
x $<> :: x -> () -> x
$<> () = x
x
{-# INLINE ($<>) #-}
instance RActSg x ()
instance RActMn x ()
instance Semigroup x => RActDistrib x ()
instance Monoid x => RActNeutral x ()
instance {-# INCOHERENT #-} LAct () s where
s
_ <>$ :: s -> () -> ()
<>$ () = ()
{-# INLINE (<>$) #-}
instance {-# INCOHERENT #-} Semigroup s =>LActSg () s
instance {-# INCOHERENT #-} Monoid s => LActMn () s
instance {-# INCOHERENT #-} LActDistrib () s
instance {-# INCOHERENT #-} LActNeutral () s
instance {-# INCOHERENT #-} RAct () s where
() $<> :: () -> s -> ()
$<> s
_ = ()
{-# INLINE ($<>) #-}
instance {-# INCOHERENT #-} Semigroup s => RActSg () s
instance {-# INCOHERENT #-} Monoid s => RActMn () s
instance {-# INCOHERENT #-} RActDistrib () s
instance {-# INCOHERENT #-} RActNeutral () s
instance LAct x s => LAct x (Maybe s) where
Maybe s
Nothing <>$ :: Maybe s -> x -> x
<>$ x
x = x
x
Just s
s <>$ x
x = s
s s -> x -> x
forall x s. LAct x s => s -> x -> x
<>$ x
x
instance LActSg x s => LActSg x (Maybe s)
instance LActSg x s => LActMn x (Maybe s)
instance RAct x s => RAct x (Maybe s) where
x
x $<> :: x -> Maybe s -> x
$<> Maybe s
Nothing = x
x
x
x $<> Just s
s = x
x x -> s -> x
forall x s. RAct x s => x -> s -> x
$<> s
s
instance RActSg x s => RActSg x (Maybe s)
instance RActSg x s => RActMn x (Maybe s)
instance (LAct x1 s1, LAct x2 s2) => LAct (x1, x2) (s1, s2) where
(s1
s1, s2
s2) <>$ :: (s1, s2) -> (x1, x2) -> (x1, x2)
<>$ (x1
x1, x2
x2) = (s1
s1 s1 -> x1 -> x1
forall x s. LAct x s => s -> x -> x
<>$ x1
x1, s2
s2 s2 -> x2 -> x2
forall x s. LAct x s => s -> x -> x
<>$ x2
x2)
instance (LActSg x1 s1, LActSg x2 s2) => LActSg (x1, x2) (s1, s2)
instance (LActMn x1 s1, LActMn x2 s2) => LActMn (x1, x2) (s1, s2)
instance (LActDistrib x1 s1, LActDistrib x2 s2) => LActDistrib (x1, x2) (s1, s2)
instance (LActNeutral x1 s1, LActNeutral x2 s2) => LActNeutral (x1, x2) (s1, s2)
instance (RAct x1 s1, RAct x2 s2) => RAct (x1, x2) (s1, s2) where
(x1
x1, x2
x2) $<> :: (x1, x2) -> (s1, s2) -> (x1, x2)
$<> (s1
s1, s2
s2) = (x1
x1 x1 -> s1 -> x1
forall x s. RAct x s => x -> s -> x
$<> s1
s1, x2
x2 x2 -> s2 -> x2
forall x s. RAct x s => x -> s -> x
$<> s2
s2)
instance (RActSg x1 s1, RActSg x2 s2) => RActSg (x1, x2) (s1, s2)
instance (RActMn x1 s1, RActMn x2 s2) => RActMn (x1, x2) (s1, s2)
instance (RActDistrib x1 s1, RActDistrib x2 s2) => RActDistrib (x1, x2) (s1, s2)
instance (RActNeutral x1 s1, RActNeutral x2 s2) => RActNeutral (x1, x2) (s1, s2)
instance (LAct x s, LAct x t) => LAct x (Either s t) where
(Left s
s) <>$ :: Either s t -> x -> x
<>$ x
x = s
s s -> x -> x
forall x s. LAct x s => s -> x -> x
<>$ x
x
(Right t
s) <>$ x
x = t
s t -> x -> x
forall x s. LAct x s => s -> x -> x
<>$ x
x
instance (RAct x s, RAct x t) => RAct x (Either s t) where
x
x $<> :: x -> Either s t -> x
$<> (Left s
s) = x
x x -> s -> x
forall x s. RAct x s => x -> s -> x
$<> s
s
x
x $<> (Right t
s) = x
x x -> t -> x
forall x s. RAct x s => x -> s -> x
$<> t
s
instance LAct x s => LAct x (Identity s) where
Identity s
s <>$ :: Identity s -> x -> x
<>$ x
x = s
s s -> x -> x
forall x s. LAct x s => s -> x -> x
<>$ x
x
{-# INLINE (<>$) #-}
instance LActSg x s => LActSg x (Identity s)
instance LActMn x s => LActMn x (Identity s)
instance LActDistrib x s => LActDistrib x (Identity s)
instance LActNeutral x s => LActNeutral x (Identity s)
instance {-# OVERLAPPING #-} LAct x s => LAct (Identity x) (Identity s) where
Identity s
s <>$ :: Identity s -> Identity x -> Identity x
<>$ Identity x
x = x -> Identity x
forall a. a -> Identity a
Identity (s
s s -> x -> x
forall x s. LAct x s => s -> x -> x
<>$ x
x)
instance {-# OVERLAPPING #-} LActSg x s => LActSg (Identity x) (Identity s)
instance {-# OVERLAPPING #-} LActMn x s => LActMn (Identity x) (Identity s)
instance {-# OVERLAPPING #-} LActDistrib x s
=> LActDistrib (Identity x) (Identity s)
instance {-# OVERLAPPING #-} LActNeutral x s
=> LActNeutral (Identity x) (Identity s)
instance RAct x s => RAct x (Identity s) where
x
x $<> :: x -> Identity s -> x
$<> Identity s
s = x
x x -> s -> x
forall x s. RAct x s => x -> s -> x
$<> s
s
{-# INLINE ($<>) #-}
instance RActSg x s => RActSg x (Identity s)
instance RActMn x s => RActMn x (Identity s)
instance RActDistrib x s => RActDistrib x (Identity s)
instance RActNeutral x s => RActNeutral x (Identity s)
instance {-# OVERLAPPING #-} RAct x s => RAct (Identity x) (Identity s) where
Identity x
x $<> :: Identity x -> Identity s -> Identity x
$<> Identity s
s = x -> Identity x
forall a. a -> Identity a
Identity (x
x x -> s -> x
forall x s. RAct x s => x -> s -> x
$<> s
s)
instance {-# OVERLAPPING #-} RActSg x s => RActSg (Identity x) (Identity s)
instance {-# OVERLAPPING #-} RActMn x s => RActMn (Identity x) (Identity s)
instance {-# OVERLAPPING #-} RActDistrib x s
=> RActDistrib (Identity x) (Identity s)
instance {-# OVERLAPPING #-} RActNeutral x s
=> RActNeutral (Identity x) (Identity s)
instance LAct x s => RAct x (Dual s) where
x
x $<> :: x -> Dual s -> x
$<> Dual s
s = s
s s -> x -> x
forall x s. LAct x s => s -> x -> x
<>$ x
x
{-# INLINE ($<>) #-}
instance LActSg x s => RActSg x (Dual s)
instance LActMn x s => RActMn x (Dual s)
instance LActDistrib x s => RActDistrib x (Dual s)
instance LActNeutral x s => RActNeutral x (Dual s)
instance RAct x s => LAct x (Dual s) where
Dual s
s <>$ :: Dual s -> x -> x
<>$ x
x = x
x x -> s -> x
forall x s. RAct x s => x -> s -> x
$<> s
s
{-# INLINE (<>$) #-}
instance RActSg x s => LActSg x (Dual s)
instance RActMn x s => LActMn x (Dual s)
instance RActDistrib x s => LActDistrib x (Dual s)
instance RActNeutral x s => LActNeutral x (Dual s)
instance LAct x (Endo x) where
Endo x -> x
f <>$ :: Endo x -> x -> x
<>$ x
x = x -> x
f x
x
{-# INLINE (<>$) #-}
instance LActSg x (Endo x)
instance LActMn x (Endo x)
instance Num x => LAct x (Sum x) where
<>$ :: Sum x -> x -> x
(<>$) Sum x
s = (Sum x -> Sum x) -> x -> x
forall a b. Coercible a b => a -> b
coerce (Sum x
s Sum x -> Sum x -> Sum x
forall a. Semigroup a => a -> a -> a
<>)
{-# INLINE (<>$) #-}
instance Num x => LActSg x (Sum x)
instance Num x => LActMn x (Sum x)
instance Num x => RAct x (Sum x) where
x
x $<> :: x -> Sum x -> x
$<> Sum x
s = Sum x -> x
forall a b. Coercible a b => a -> b
coerce (Sum x -> x) -> Sum x -> x
forall a b. (a -> b) -> a -> b
$ x -> Sum x
forall a b. Coercible a b => a -> b
coerce x
x Sum x -> Sum x -> Sum x
forall a. Semigroup a => a -> a -> a
<> Sum x
s
{-# INLINE ($<>) #-}
instance Num x => RActSg x (Sum x)
instance Num x => RActMn x (Sum x)
instance Num x => LAct x (Product x) where
<>$ :: Product x -> x -> x
(<>$) Product x
s = (Product x -> Product x) -> x -> x
forall a b. Coercible a b => a -> b
coerce (Product x
s Product x -> Product x -> Product x
forall a. Semigroup a => a -> a -> a
<>)
{-# INLINE (<>$) #-}
instance Num x => LActSg x (Product x)
instance Num x => LActMn x (Product x)
instance Num x => RAct x (Product x) where
x
x $<> :: x -> Product x -> x
$<> Product x
s = Product x -> x
forall a b. Coercible a b => a -> b
coerce (Product x -> x) -> Product x -> x
forall a b. (a -> b) -> a -> b
$ x -> Product x
forall a b. Coercible a b => a -> b
coerce x
x Product x -> Product x -> Product x
forall a. Semigroup a => a -> a -> a
<> Product x
s
{-# INLINE ($<>) #-}
instance Num x => RActSg x (Product x)
instance Num x => RActMn x (Product x)
instance {-# OVERLAPPING #-} Num x => LAct (Sum x) (Sum x) where
<>$ :: Sum x -> Sum x -> Sum x
(<>$) = Sum x -> Sum x -> Sum x
forall a. Semigroup a => a -> a -> a
(<>)
{-# INLINE (<>$) #-}
instance {-# OVERLAPPING #-} Num x => LActSg (Sum x) (Sum x)
instance {-# OVERLAPPING #-} Num x => LActMn (Sum x) (Sum x)
instance {-# OVERLAPPING #-} Num x => RAct (Sum x) (Sum x) where
$<> :: Sum x -> Sum x -> Sum x
($<>) = Sum x -> Sum x -> Sum x
forall a. Semigroup a => a -> a -> a
(<>)
{-# INLINE ($<>) #-}
instance {-# OVERLAPPING #-} Num x => RActSg (Sum x) (Sum x)
instance {-# OVERLAPPING #-} Num x => RActMn (Sum x) (Sum x)
instance {-# OVERLAPPING #-} Num x => LAct (Product x) (Product x) where
<>$ :: Product x -> Product x -> Product x
(<>$) Product x
s = (Product x -> Product x) -> Product x -> Product x
forall a b. Coercible a b => a -> b
coerce (Product x
s Product x -> Product x -> Product x
forall a. Semigroup a => a -> a -> a
<>)
{-# INLINE (<>$) #-}
instance {-# OVERLAPPING #-} Num x => LActSg (Product x) (Product x)
instance {-# OVERLAPPING #-} Num x => LActMn (Product x) (Product x)
instance {-# OVERLAPPING #-} Num x => RAct (Product x) (Product x) where
$<> :: Product x -> Product x -> Product x
($<>) = Product x -> Product x -> Product x
forall a. Semigroup a => a -> a -> a
(<>)
{-# INLINE ($<>) #-}
instance {-# OVERLAPPING #-} Num x => RActSg (Product x) (Product x)
instance {-# OVERLAPPING #-} Num x => RActMn (Product x) (Product x)
instance Num x => LAct (Sum x) (Product x) where
<>$ :: Product x -> Sum x -> Sum x
(<>$) Product x
s = (Product x -> Product x) -> Sum x -> Sum x
forall a b. Coercible a b => a -> b
coerce (Product x
s Product x -> Product x -> Product x
forall a. Semigroup a => a -> a -> a
<>)
{-# INLINE (<>$) #-}
instance Num x => LActSg (Sum x) (Product x)
instance Num x => LActMn (Sum x) (Product x)
instance Num x => LActDistrib (Sum x) (Product x)
instance Num x => LActNeutral (Sum x) (Product x)
instance Num x => RAct (Sum x) (Product x) where
Sum x
x $<> :: Sum x -> Product x -> Sum x
$<> Product x
s = Product x -> Sum x
forall a b. Coercible a b => a -> b
coerce (Product x -> Sum x) -> Product x -> Sum x
forall a b. (a -> b) -> a -> b
$ Sum x -> Product x
forall a b. Coercible a b => a -> b
coerce Sum x
x Product x -> Product x -> Product x
forall a. Semigroup a => a -> a -> a
<> Product x
s
{-# INLINE ($<>) #-}
instance Num x => RActSg (Sum x) (Product x)
instance Num x => RActMn (Sum x) (Product x)
instance Num x => RActDistrib (Sum x) (Product x)
instance Num x => RActNeutral (Sum x) (Product x)
instance LAct Bool Any where
<>$ :: Any -> Bool -> Bool
(<>$) Any
s = (Any -> Any) -> Bool -> Bool
forall a b. Coercible a b => a -> b
coerce (Any
s Any -> Any -> Any
forall a. Semigroup a => a -> a -> a
<>)
{-# INLINE (<>$) #-}
instance LActSg Bool Any
instance LActMn Bool Any
instance RAct Bool Any where
Bool
x $<> :: Bool -> Any -> Bool
$<> Any
s = Any -> Bool
forall a b. Coercible a b => a -> b
coerce (Any -> Bool) -> Any -> Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Any
forall a b. Coercible a b => a -> b
coerce Bool
x Any -> Any -> Any
forall a. Semigroup a => a -> a -> a
<> Any
s
{-# INLINE ($<>) #-}
instance RActSg Bool Any
instance RActMn Bool Any
instance LAct Bool All where
<>$ :: All -> Bool -> Bool
(<>$) All
s = (All -> All) -> Bool -> Bool
forall a b. Coercible a b => a -> b
coerce (All
s All -> All -> All
forall a. Semigroup a => a -> a -> a
<>)
{-# INLINE (<>$) #-}
instance LActSg Bool All
instance LActMn Bool All
instance RAct Bool All where
Bool
x $<> :: Bool -> All -> Bool
$<> All
s = All -> Bool
forall a b. Coercible a b => a -> b
coerce (All -> Bool) -> All -> Bool
forall a b. (a -> b) -> a -> b
$ Bool -> All
forall a b. Coercible a b => a -> b
coerce Bool
x All -> All -> All
forall a. Semigroup a => a -> a -> a
<> All
s
{-# INLINE ($<>) #-}
instance RActSg Bool All
instance RActMn Bool All
instance LAct x (Sg.First x) where
<>$ :: First x -> x -> x
(<>$) First x
s = (First x -> First x) -> x -> x
forall a b. Coercible a b => a -> b
coerce (First x
s First x -> First x -> First x
forall a. Semigroup a => a -> a -> a
<>)
{-# INLINE (<>$) #-}
instance LActSg x (Sg.First x)
instance RAct x (Sg.Last x) where
x
x $<> :: x -> Last x -> x
$<> Last x
s = Last x -> x
forall a b. Coercible a b => a -> b
coerce (Last x -> x) -> Last x -> x
forall a b. (a -> b) -> a -> b
$ x -> Last x
forall a b. Coercible a b => a -> b
coerce x
x Last x -> Last x -> Last x
forall a. Semigroup a => a -> a -> a
<> Last x
s
{-# INLINE ($<>) #-}
instance RActSg x (Sg.Last x)
instance LAct x (Mn.First x) where
Mn.First Maybe x
Nothing <>$ :: First x -> x -> x
<>$ x
x = x
x
Mn.First (Just x
s) <>$ x
_ = x
s
{-# INLINE (<>$) #-}
instance LActSg x (Mn.First x)
instance LActMn x (Mn.First x)
instance RAct x (Mn.Last x) where
x
x $<> :: x -> Last x -> x
$<> Mn.Last Maybe x
Nothing = x
x
x
_ $<> Mn.Last (Just x
s) = x
s
{-# INLINE ($<>) #-}
instance RActSg x (Mn.Last x)
instance RActMn x (Mn.Last x)