{-# LANGUAGE CPP #-}
{-# LANGUAGE DerivingVia #-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Data.Functor.Invariant.Inplicative (
Inply(..)
, Inplicative(..)
, WrappedApplicativeOnly(..)
, WrappedDivisibleOnly(..)
, runDay
, dather
, runDayApply
, runDayDivise
, gatheredN
, gatheredNMap
, gatheredN1
, gatheredN1Map
, gatheredNRec
, gatheredNMapRec
, gatheredN1Rec
, gatheredN1MapRec
, gatherN
, gatherN1
) where
import Control.Applicative
import Control.Applicative.Backwards (Backwards(..))
import Control.Applicative.Lift (Lift(Pure, Other))
import Control.Arrow (Arrow)
import Control.Monad.Trans.Cont (ContT)
import Control.Monad.Trans.Error (ErrorT(..))
import Control.Monad.Trans.Except (ExceptT(..))
import Control.Monad.Trans.Identity (IdentityT(..))
import Control.Monad.Trans.List (ListT(..))
import Control.Monad.Trans.Maybe (MaybeT(..))
import Control.Monad.Trans.RWS (RWST(..))
import Control.Monad.Trans.Reader (ReaderT(..))
import Control.Monad.Trans.State (StateT)
import Control.Monad.Trans.Writer (WriterT(..))
import Control.Natural
import Data.Complex (Complex)
import Data.Deriving
import Data.Functor.Apply
import Data.Functor.Bind.Class (Bind)
import Data.Functor.Constant (Constant)
import Data.Functor.Contravariant
import Data.Functor.Contravariant.Divise
import Data.Functor.Contravariant.Divisible
import Data.Functor.Identity
import Data.Functor.Invariant
import Data.Functor.Invariant.Day
import Data.Functor.Product (Product(..))
import Data.Functor.Reverse (Reverse(..))
import Data.Hashable (Hashable)
import Data.Kind
import Data.List.NonEmpty (NonEmpty)
import Data.SOP hiding (hmap)
import Data.Sequence (Seq)
import Data.StateVar (SettableStateVar)
import Data.Tagged (Tagged)
import Data.Tree (Tree)
import GHC.Generics (Generic)
import qualified Control.Monad.Trans.RWS.Strict as Strict (RWST(..))
import qualified Control.Monad.Trans.State.Strict as Strict (StateT)
import qualified Control.Monad.Trans.Writer.Strict as Strict (WriterT(..))
import qualified Data.HashMap.Lazy as HM
import qualified Data.IntMap as IM
import qualified Data.Map as M
import qualified Data.Monoid as Monoid
import qualified Data.Semigroup as Semigroup
import qualified Data.Sequence.NonEmpty as NESeq
import qualified Data.Vinyl as V
import qualified Data.Vinyl.Curry as V
import qualified Data.Vinyl.Functor as V
import qualified GHC.Generics as Generics
class Invariant f => Inply f where
gather
:: (b -> c -> a)
-> (a -> (b, c))
-> f b
-> f c
-> f a
gather b -> c -> a
f a -> (b, c)
g f b
x f c
y = forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry b -> c -> a
f) a -> (b, c)
g (forall (f :: * -> *) a b. Inply f => f a -> f b -> f (a, b)
gathered f b
x f c
y)
gathered
:: f a
-> f b
-> f (a, b)
gathered = forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather (,) forall a. a -> a
id
{-# MINIMAL gather | gathered #-}
class Inply f => Inplicative f where
knot :: a -> f a
runDay
:: Inply h
=> (f ~> h)
-> (g ~> h)
-> Day f g ~> h
runDay :: forall (h :: * -> *) (f :: * -> *) (g :: * -> *).
Inply h =>
(f ~> h) -> (g ~> h) -> Day f g ~> h
runDay f ~> h
f g ~> h
g (Day f b
x g c
y b -> c -> x
a x -> (b, c)
b) = forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> x
a x -> (b, c)
b (f ~> h
f f b
x) (g ~> h
g g c
y)
dather
:: Inply f
=> Day f f ~> f
dather :: forall (f :: * -> *). Inply f => Day f f ~> f
dather (Day f b
x f c
y b -> c -> x
a x -> (b, c)
b) = forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> x
a x -> (b, c)
b f b
x f c
y
instance Apply f => Inply (WrappedFunctor f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c))
-> WrappedFunctor f b
-> WrappedFunctor f c
-> WrappedFunctor f a
gather b -> c -> a
f a -> (b, c)
_ (WrapFunctor f b
x) (WrapFunctor f c
y) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedFunctor f a
WrapFunctor (forall (f :: * -> *) a b c.
Apply f =>
(a -> b -> c) -> f a -> f b -> f c
liftF2 b -> c -> a
f f b
x f c
y)
gathered :: forall a b.
WrappedFunctor f a -> WrappedFunctor f b -> WrappedFunctor f (a, b)
gathered (WrapFunctor f a
x) (WrapFunctor f b
y) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedFunctor f a
WrapFunctor (forall (f :: * -> *) a b c.
Apply f =>
(a -> b -> c) -> f a -> f b -> f c
liftF2 (,) f a
x f b
y)
instance (Applicative f, Apply f) => Inplicative (WrappedFunctor f) where
knot :: forall a. a -> WrappedFunctor f a
knot = forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance Divise f => Inply (WrappedContravariant f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c))
-> WrappedContravariant f b
-> WrappedContravariant f c
-> WrappedContravariant f a
gather b -> c -> a
_ a -> (b, c)
g (WrapContravariant f b
x) (WrapContravariant f c
y) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedContravariant f a
WrapContravariant (forall (f :: * -> *) a b c.
Divise f =>
(a -> (b, c)) -> f b -> f c -> f a
divise a -> (b, c)
g f b
x f c
y)
gathered :: forall a b.
WrappedContravariant f a
-> WrappedContravariant f b -> WrappedContravariant f (a, b)
gathered (WrapContravariant f a
x) (WrapContravariant f b
y) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedContravariant f a
WrapContravariant (forall (f :: * -> *) a b. Divise f => f a -> f b -> f (a, b)
divised f a
x f b
y)
instance (Divisible f, Divise f) => Inplicative (WrappedContravariant f) where
knot :: forall a. a -> WrappedContravariant f a
knot a
_ = forall (f :: * -> *) a. Divisible f => f a
conquer
instance Divise f => Inply (WrappedDivisible f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c))
-> WrappedDivisible f b
-> WrappedDivisible f c
-> WrappedDivisible f a
gather b -> c -> a
_ a -> (b, c)
g (WrapDivisible f b
x) (WrapDivisible f c
y) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedDivisible f a
WrapDivisible (forall (f :: * -> *) a b c.
Divise f =>
(a -> (b, c)) -> f b -> f c -> f a
divise a -> (b, c)
g f b
x f c
y)
gathered :: forall a b.
WrappedDivisible f a
-> WrappedDivisible f b -> WrappedDivisible f (a, b)
gathered (WrapDivisible f a
x) (WrapDivisible f b
y) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedDivisible f a
WrapDivisible (forall (f :: * -> *) a b. Divise f => f a -> f b -> f (a, b)
divised f a
x f b
y)
instance (Divisible f, Divise f) => Inplicative (WrappedDivisible f) where
knot :: forall a. a -> WrappedDivisible f a
knot a
_ = forall (f :: * -> *) a. Divisible f => f a
conquer
newtype WrappedApplicativeOnly f a =
WrapApplicativeOnly { forall {k} (f :: k -> *) (a :: k).
WrappedApplicativeOnly f a -> f a
unwrapApplicativeOnly :: f a }
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (f :: k -> *) (a :: k) x.
Rep (WrappedApplicativeOnly f a) x -> WrappedApplicativeOnly f a
forall k (f :: k -> *) (a :: k) x.
WrappedApplicativeOnly f a -> Rep (WrappedApplicativeOnly f a) x
$cto :: forall k (f :: k -> *) (a :: k) x.
Rep (WrappedApplicativeOnly f a) x -> WrappedApplicativeOnly f a
$cfrom :: forall k (f :: k -> *) (a :: k) x.
WrappedApplicativeOnly f a -> Rep (WrappedApplicativeOnly f a) x
Generic, WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (f :: k -> *) (a :: k).
Eq (f a) =>
WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
/= :: WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
$c/= :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
== :: WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
$c== :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
Eq, Int -> WrappedApplicativeOnly f a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> WrappedApplicativeOnly f a -> ShowS
forall k (f :: k -> *) (a :: k).
Show (f a) =>
[WrappedApplicativeOnly f a] -> ShowS
forall k (f :: k -> *) (a :: k).
Show (f a) =>
WrappedApplicativeOnly f a -> String
showList :: [WrappedApplicativeOnly f a] -> ShowS
$cshowList :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
[WrappedApplicativeOnly f a] -> ShowS
show :: WrappedApplicativeOnly f a -> String
$cshow :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
WrappedApplicativeOnly f a -> String
showsPrec :: Int -> WrappedApplicativeOnly f a -> ShowS
$cshowsPrec :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> WrappedApplicativeOnly f a -> ShowS
Show, WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> Ordering
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f 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 {k} {f :: k -> *} {a :: k}.
Ord (f a) =>
Eq (WrappedApplicativeOnly f a)
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> Ordering
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a
min :: WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a
$cmin :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a
max :: WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a
$cmax :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a
>= :: WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
$c>= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
> :: WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
$c> :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
<= :: WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
$c<= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
< :: WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
$c< :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a -> WrappedApplicativeOnly f a -> Bool
compare :: WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> Ordering
$ccompare :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f a -> Ordering
Ord, ReadPrec [WrappedApplicativeOnly f a]
ReadPrec (WrappedApplicativeOnly f a)
ReadS [WrappedApplicativeOnly f a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec [WrappedApplicativeOnly f a]
forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec (WrappedApplicativeOnly f a)
forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (WrappedApplicativeOnly f a)
forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadS [WrappedApplicativeOnly f a]
readListPrec :: ReadPrec [WrappedApplicativeOnly f a]
$creadListPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec [WrappedApplicativeOnly f a]
readPrec :: ReadPrec (WrappedApplicativeOnly f a)
$creadPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec (WrappedApplicativeOnly f a)
readList :: ReadS [WrappedApplicativeOnly f a]
$creadList :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadS [WrappedApplicativeOnly f a]
readsPrec :: Int -> ReadS (WrappedApplicativeOnly f a)
$creadsPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (WrappedApplicativeOnly f a)
Read, forall a b.
a -> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f a
forall a b.
(a -> b)
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f b
forall (f :: * -> *) a b.
Functor f =>
a -> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f a
forall (f :: * -> *) a b.
Functor f =>
(a -> b)
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b.
a -> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f a
$c<$ :: forall (f :: * -> *) a b.
Functor f =>
a -> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f a
fmap :: forall a b.
(a -> b)
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f b
$cfmap :: forall (f :: * -> *) a b.
Functor f =>
(a -> b)
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f b
Functor, forall a. Eq a => a -> WrappedApplicativeOnly f a -> Bool
forall a. Num a => WrappedApplicativeOnly f a -> a
forall a. Ord a => WrappedApplicativeOnly f a -> a
forall m. Monoid m => WrappedApplicativeOnly f m -> m
forall a. WrappedApplicativeOnly f a -> Bool
forall a. WrappedApplicativeOnly f a -> Int
forall a. WrappedApplicativeOnly f a -> [a]
forall a. (a -> a -> a) -> WrappedApplicativeOnly f a -> a
forall m a. Monoid m => (a -> m) -> WrappedApplicativeOnly f a -> m
forall b a. (b -> a -> b) -> b -> WrappedApplicativeOnly f a -> b
forall a b. (a -> b -> b) -> b -> WrappedApplicativeOnly f a -> b
forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> WrappedApplicativeOnly f a -> Bool
forall (f :: * -> *) a.
(Foldable f, Num a) =>
WrappedApplicativeOnly f a -> a
forall (f :: * -> *) a.
(Foldable f, Ord a) =>
WrappedApplicativeOnly f a -> a
forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
WrappedApplicativeOnly f m -> m
forall (f :: * -> *) a.
Foldable f =>
WrappedApplicativeOnly f a -> Bool
forall (f :: * -> *) a.
Foldable f =>
WrappedApplicativeOnly f a -> Int
forall (f :: * -> *) a.
Foldable f =>
WrappedApplicativeOnly f a -> [a]
forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedApplicativeOnly f a -> a
forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedApplicativeOnly f a -> m
forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedApplicativeOnly f a -> b
forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedApplicativeOnly f a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => WrappedApplicativeOnly f a -> a
$cproduct :: forall (f :: * -> *) a.
(Foldable f, Num a) =>
WrappedApplicativeOnly f a -> a
sum :: forall a. Num a => WrappedApplicativeOnly f a -> a
$csum :: forall (f :: * -> *) a.
(Foldable f, Num a) =>
WrappedApplicativeOnly f a -> a
minimum :: forall a. Ord a => WrappedApplicativeOnly f a -> a
$cminimum :: forall (f :: * -> *) a.
(Foldable f, Ord a) =>
WrappedApplicativeOnly f a -> a
maximum :: forall a. Ord a => WrappedApplicativeOnly f a -> a
$cmaximum :: forall (f :: * -> *) a.
(Foldable f, Ord a) =>
WrappedApplicativeOnly f a -> a
elem :: forall a. Eq a => a -> WrappedApplicativeOnly f a -> Bool
$celem :: forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> WrappedApplicativeOnly f a -> Bool
length :: forall a. WrappedApplicativeOnly f a -> Int
$clength :: forall (f :: * -> *) a.
Foldable f =>
WrappedApplicativeOnly f a -> Int
null :: forall a. WrappedApplicativeOnly f a -> Bool
$cnull :: forall (f :: * -> *) a.
Foldable f =>
WrappedApplicativeOnly f a -> Bool
toList :: forall a. WrappedApplicativeOnly f a -> [a]
$ctoList :: forall (f :: * -> *) a.
Foldable f =>
WrappedApplicativeOnly f a -> [a]
foldl1 :: forall a. (a -> a -> a) -> WrappedApplicativeOnly f a -> a
$cfoldl1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedApplicativeOnly f a -> a
foldr1 :: forall a. (a -> a -> a) -> WrappedApplicativeOnly f a -> a
$cfoldr1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedApplicativeOnly f a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> WrappedApplicativeOnly f a -> b
$cfoldl' :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedApplicativeOnly f a -> b
foldl :: forall b a. (b -> a -> b) -> b -> WrappedApplicativeOnly f a -> b
$cfoldl :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedApplicativeOnly f a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> WrappedApplicativeOnly f a -> b
$cfoldr' :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedApplicativeOnly f a -> b
foldr :: forall a b. (a -> b -> b) -> b -> WrappedApplicativeOnly f a -> b
$cfoldr :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedApplicativeOnly f a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> WrappedApplicativeOnly f a -> m
$cfoldMap' :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedApplicativeOnly f a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> WrappedApplicativeOnly f a -> m
$cfoldMap :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedApplicativeOnly f a -> m
fold :: forall m. Monoid m => WrappedApplicativeOnly f m -> m
$cfold :: forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
WrappedApplicativeOnly f m -> m
Foldable, forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall {f :: * -> *}.
Traversable f =>
Functor (WrappedApplicativeOnly f)
forall {f :: * -> *}.
Traversable f =>
Foldable (WrappedApplicativeOnly f)
forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
WrappedApplicativeOnly f (m a) -> m (WrappedApplicativeOnly f a)
forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
WrappedApplicativeOnly f (f a) -> f (WrappedApplicativeOnly f a)
forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b)
-> WrappedApplicativeOnly f a -> m (WrappedApplicativeOnly f b)
forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b)
-> WrappedApplicativeOnly f a -> f (WrappedApplicativeOnly f b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> WrappedApplicativeOnly f a -> f (WrappedApplicativeOnly f b)
sequence :: forall (m :: * -> *) a.
Monad m =>
WrappedApplicativeOnly f (m a) -> m (WrappedApplicativeOnly f a)
$csequence :: forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
WrappedApplicativeOnly f (m a) -> m (WrappedApplicativeOnly f a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> WrappedApplicativeOnly f a -> m (WrappedApplicativeOnly f b)
$cmapM :: forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b)
-> WrappedApplicativeOnly f a -> m (WrappedApplicativeOnly f b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
WrappedApplicativeOnly f (f a) -> f (WrappedApplicativeOnly f a)
$csequenceA :: forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
WrappedApplicativeOnly f (f a) -> f (WrappedApplicativeOnly f a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> WrappedApplicativeOnly f a -> f (WrappedApplicativeOnly f b)
$ctraverse :: forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b)
-> WrappedApplicativeOnly f a -> f (WrappedApplicativeOnly f b)
Traversable)
deriving newtype (forall a. a -> WrappedApplicativeOnly f a
forall a b.
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f a
forall a b.
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f b
forall a b.
WrappedApplicativeOnly f (a -> b)
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f b
forall a b c.
(a -> b -> c)
-> WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b
-> WrappedApplicativeOnly f c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall {f :: * -> *}.
Applicative f =>
Functor (WrappedApplicativeOnly f)
forall (f :: * -> *) a.
Applicative f =>
a -> WrappedApplicativeOnly f a
forall (f :: * -> *) a b.
Applicative f =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f a
forall (f :: * -> *) a b.
Applicative f =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f b
forall (f :: * -> *) a b.
Applicative f =>
WrappedApplicativeOnly f (a -> b)
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c)
-> WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b
-> WrappedApplicativeOnly f c
<* :: forall a b.
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f a
$c<* :: forall (f :: * -> *) a b.
Applicative f =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f a
*> :: forall a b.
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f b
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f b
liftA2 :: forall a b c.
(a -> b -> c)
-> WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b
-> WrappedApplicativeOnly f c
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c)
-> WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b
-> WrappedApplicativeOnly f c
<*> :: forall a b.
WrappedApplicativeOnly f (a -> b)
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f b
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
WrappedApplicativeOnly f (a -> b)
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f b
pure :: forall a. a -> WrappedApplicativeOnly f a
$cpure :: forall (f :: * -> *) a.
Applicative f =>
a -> WrappedApplicativeOnly f a
Applicative, forall a. a -> WrappedApplicativeOnly f a
forall a b.
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f b
forall a b.
WrappedApplicativeOnly f a
-> (a -> WrappedApplicativeOnly f b) -> WrappedApplicativeOnly f b
forall {f :: * -> *}.
Monad f =>
Applicative (WrappedApplicativeOnly f)
forall (f :: * -> *) a. Monad f => a -> WrappedApplicativeOnly f a
forall (f :: * -> *) a b.
Monad f =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f b
forall (f :: * -> *) a b.
Monad f =>
WrappedApplicativeOnly f a
-> (a -> WrappedApplicativeOnly f b) -> WrappedApplicativeOnly f b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> WrappedApplicativeOnly f a
$creturn :: forall (f :: * -> *) a. Monad f => a -> WrappedApplicativeOnly f a
>> :: forall a b.
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f b
$c>> :: forall (f :: * -> *) a b.
Monad f =>
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f b
>>= :: forall a b.
WrappedApplicativeOnly f a
-> (a -> WrappedApplicativeOnly f b) -> WrappedApplicativeOnly f b
$c>>= :: forall (f :: * -> *) a b.
Monad f =>
WrappedApplicativeOnly f a
-> (a -> WrappedApplicativeOnly f b) -> WrappedApplicativeOnly f b
Monad)
deriveShow1 ''WrappedApplicativeOnly
deriveRead1 ''WrappedApplicativeOnly
deriveEq1 ''WrappedApplicativeOnly
deriveOrd1 ''WrappedApplicativeOnly
instance Invariant f => Invariant (WrappedApplicativeOnly f) where
invmap :: forall a b.
(a -> b)
-> (b -> a)
-> WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b
invmap a -> b
f b -> a
g (WrapApplicativeOnly f a
x) = forall {k} (f :: k -> *) (a :: k).
f a -> WrappedApplicativeOnly f a
WrapApplicativeOnly (forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap a -> b
f b -> a
g f a
x)
instance (Applicative f, Invariant f) => Apply (WrappedApplicativeOnly f) where
WrappedApplicativeOnly f (a -> b)
x <.> :: forall a b.
WrappedApplicativeOnly f (a -> b)
-> WrappedApplicativeOnly f a -> WrappedApplicativeOnly f b
<.> WrappedApplicativeOnly f a
y = WrappedApplicativeOnly f (a -> b)
x forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> WrappedApplicativeOnly f a
y
instance (Applicative f, Invariant f) => Inply (WrappedApplicativeOnly f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c))
-> WrappedApplicativeOnly f b
-> WrappedApplicativeOnly f c
-> WrappedApplicativeOnly f a
gather b -> c -> a
f a -> (b, c)
_ (WrapApplicativeOnly f b
x) (WrapApplicativeOnly f c
y) = forall {k} (f :: k -> *) (a :: k).
f a -> WrappedApplicativeOnly f a
WrapApplicativeOnly (forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 b -> c -> a
f f b
x f c
y)
gathered :: forall a b.
WrappedApplicativeOnly f a
-> WrappedApplicativeOnly f b -> WrappedApplicativeOnly f (a, b)
gathered (WrapApplicativeOnly f a
x) (WrapApplicativeOnly f b
y) = forall {k} (f :: k -> *) (a :: k).
f a -> WrappedApplicativeOnly f a
WrapApplicativeOnly (forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) f a
x f b
y)
instance (Applicative f, Invariant f) => Inplicative (WrappedApplicativeOnly f) where
knot :: forall a. a -> WrappedApplicativeOnly f a
knot = forall (f :: * -> *) a. Applicative f => a -> f a
pure
newtype WrappedDivisibleOnly f a =
WrapDivisibleOnly { forall {k} (f :: k -> *) (a :: k). WrappedDivisibleOnly f a -> f a
unwrapDivisibleOnly :: f a }
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (f :: k -> *) (a :: k) x.
Rep (WrappedDivisibleOnly f a) x -> WrappedDivisibleOnly f a
forall k (f :: k -> *) (a :: k) x.
WrappedDivisibleOnly f a -> Rep (WrappedDivisibleOnly f a) x
$cto :: forall k (f :: k -> *) (a :: k) x.
Rep (WrappedDivisibleOnly f a) x -> WrappedDivisibleOnly f a
$cfrom :: forall k (f :: k -> *) (a :: k) x.
WrappedDivisibleOnly f a -> Rep (WrappedDivisibleOnly f a) x
Generic, WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (f :: k -> *) (a :: k).
Eq (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
/= :: WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
$c/= :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
== :: WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
$c== :: forall k (f :: k -> *) (a :: k).
Eq (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
Eq, Int -> WrappedDivisibleOnly f a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> WrappedDivisibleOnly f a -> ShowS
forall k (f :: k -> *) (a :: k).
Show (f a) =>
[WrappedDivisibleOnly f a] -> ShowS
forall k (f :: k -> *) (a :: k).
Show (f a) =>
WrappedDivisibleOnly f a -> String
showList :: [WrappedDivisibleOnly f a] -> ShowS
$cshowList :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
[WrappedDivisibleOnly f a] -> ShowS
show :: WrappedDivisibleOnly f a -> String
$cshow :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
WrappedDivisibleOnly f a -> String
showsPrec :: Int -> WrappedDivisibleOnly f a -> ShowS
$cshowsPrec :: forall k (f :: k -> *) (a :: k).
Show (f a) =>
Int -> WrappedDivisibleOnly f a -> ShowS
Show, WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Ordering
WrappedDivisibleOnly f a
-> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f 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 {k} {f :: k -> *} {a :: k}.
Ord (f a) =>
Eq (WrappedDivisibleOnly f a)
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Ordering
forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a
-> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a
min :: WrappedDivisibleOnly f a
-> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a
$cmin :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a
-> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a
max :: WrappedDivisibleOnly f a
-> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a
$cmax :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a
-> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a
>= :: WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
$c>= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
> :: WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
$c> :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
<= :: WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
$c<= :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
< :: WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
$c< :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Bool
compare :: WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Ordering
$ccompare :: forall k (f :: k -> *) (a :: k).
Ord (f a) =>
WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a -> Ordering
Ord, ReadPrec [WrappedDivisibleOnly f a]
ReadPrec (WrappedDivisibleOnly f a)
ReadS [WrappedDivisibleOnly f a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec [WrappedDivisibleOnly f a]
forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec (WrappedDivisibleOnly f a)
forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (WrappedDivisibleOnly f a)
forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadS [WrappedDivisibleOnly f a]
readListPrec :: ReadPrec [WrappedDivisibleOnly f a]
$creadListPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec [WrappedDivisibleOnly f a]
readPrec :: ReadPrec (WrappedDivisibleOnly f a)
$creadPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadPrec (WrappedDivisibleOnly f a)
readList :: ReadS [WrappedDivisibleOnly f a]
$creadList :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
ReadS [WrappedDivisibleOnly f a]
readsPrec :: Int -> ReadS (WrappedDivisibleOnly f a)
$creadsPrec :: forall k (f :: k -> *) (a :: k).
Read (f a) =>
Int -> ReadS (WrappedDivisibleOnly f a)
Read, forall a b.
a -> WrappedDivisibleOnly f b -> WrappedDivisibleOnly f a
forall a b.
(a -> b) -> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f b
forall (f :: * -> *) a b.
Functor f =>
a -> WrappedDivisibleOnly f b -> WrappedDivisibleOnly f a
forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b.
a -> WrappedDivisibleOnly f b -> WrappedDivisibleOnly f a
$c<$ :: forall (f :: * -> *) a b.
Functor f =>
a -> WrappedDivisibleOnly f b -> WrappedDivisibleOnly f a
fmap :: forall a b.
(a -> b) -> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f b
$cfmap :: forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f b
Functor, forall a. Eq a => a -> WrappedDivisibleOnly f a -> Bool
forall a. Num a => WrappedDivisibleOnly f a -> a
forall a. Ord a => WrappedDivisibleOnly f a -> a
forall m. Monoid m => WrappedDivisibleOnly f m -> m
forall a. WrappedDivisibleOnly f a -> Bool
forall a. WrappedDivisibleOnly f a -> Int
forall a. WrappedDivisibleOnly f a -> [a]
forall a. (a -> a -> a) -> WrappedDivisibleOnly f a -> a
forall m a. Monoid m => (a -> m) -> WrappedDivisibleOnly f a -> m
forall b a. (b -> a -> b) -> b -> WrappedDivisibleOnly f a -> b
forall a b. (a -> b -> b) -> b -> WrappedDivisibleOnly f a -> b
forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> WrappedDivisibleOnly f a -> Bool
forall (f :: * -> *) a.
(Foldable f, Num a) =>
WrappedDivisibleOnly f a -> a
forall (f :: * -> *) a.
(Foldable f, Ord a) =>
WrappedDivisibleOnly f a -> a
forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
WrappedDivisibleOnly f m -> m
forall (f :: * -> *) a.
Foldable f =>
WrappedDivisibleOnly f a -> Bool
forall (f :: * -> *) a.
Foldable f =>
WrappedDivisibleOnly f a -> Int
forall (f :: * -> *) a.
Foldable f =>
WrappedDivisibleOnly f a -> [a]
forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedDivisibleOnly f a -> a
forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedDivisibleOnly f a -> m
forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedDivisibleOnly f a -> b
forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedDivisibleOnly f a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => WrappedDivisibleOnly f a -> a
$cproduct :: forall (f :: * -> *) a.
(Foldable f, Num a) =>
WrappedDivisibleOnly f a -> a
sum :: forall a. Num a => WrappedDivisibleOnly f a -> a
$csum :: forall (f :: * -> *) a.
(Foldable f, Num a) =>
WrappedDivisibleOnly f a -> a
minimum :: forall a. Ord a => WrappedDivisibleOnly f a -> a
$cminimum :: forall (f :: * -> *) a.
(Foldable f, Ord a) =>
WrappedDivisibleOnly f a -> a
maximum :: forall a. Ord a => WrappedDivisibleOnly f a -> a
$cmaximum :: forall (f :: * -> *) a.
(Foldable f, Ord a) =>
WrappedDivisibleOnly f a -> a
elem :: forall a. Eq a => a -> WrappedDivisibleOnly f a -> Bool
$celem :: forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> WrappedDivisibleOnly f a -> Bool
length :: forall a. WrappedDivisibleOnly f a -> Int
$clength :: forall (f :: * -> *) a.
Foldable f =>
WrappedDivisibleOnly f a -> Int
null :: forall a. WrappedDivisibleOnly f a -> Bool
$cnull :: forall (f :: * -> *) a.
Foldable f =>
WrappedDivisibleOnly f a -> Bool
toList :: forall a. WrappedDivisibleOnly f a -> [a]
$ctoList :: forall (f :: * -> *) a.
Foldable f =>
WrappedDivisibleOnly f a -> [a]
foldl1 :: forall a. (a -> a -> a) -> WrappedDivisibleOnly f a -> a
$cfoldl1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedDivisibleOnly f a -> a
foldr1 :: forall a. (a -> a -> a) -> WrappedDivisibleOnly f a -> a
$cfoldr1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedDivisibleOnly f a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> WrappedDivisibleOnly f a -> b
$cfoldl' :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedDivisibleOnly f a -> b
foldl :: forall b a. (b -> a -> b) -> b -> WrappedDivisibleOnly f a -> b
$cfoldl :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedDivisibleOnly f a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> WrappedDivisibleOnly f a -> b
$cfoldr' :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedDivisibleOnly f a -> b
foldr :: forall a b. (a -> b -> b) -> b -> WrappedDivisibleOnly f a -> b
$cfoldr :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedDivisibleOnly f a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> WrappedDivisibleOnly f a -> m
$cfoldMap' :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedDivisibleOnly f a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> WrappedDivisibleOnly f a -> m
$cfoldMap :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedDivisibleOnly f a -> m
fold :: forall m. Monoid m => WrappedDivisibleOnly f m -> m
$cfold :: forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
WrappedDivisibleOnly f m -> m
Foldable, forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall {f :: * -> *}.
Traversable f =>
Functor (WrappedDivisibleOnly f)
forall {f :: * -> *}.
Traversable f =>
Foldable (WrappedDivisibleOnly f)
forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
WrappedDivisibleOnly f (m a) -> m (WrappedDivisibleOnly f a)
forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
WrappedDivisibleOnly f (f a) -> f (WrappedDivisibleOnly f a)
forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b)
-> WrappedDivisibleOnly f a -> m (WrappedDivisibleOnly f b)
forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b)
-> WrappedDivisibleOnly f a -> f (WrappedDivisibleOnly f b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> WrappedDivisibleOnly f a -> f (WrappedDivisibleOnly f b)
sequence :: forall (m :: * -> *) a.
Monad m =>
WrappedDivisibleOnly f (m a) -> m (WrappedDivisibleOnly f a)
$csequence :: forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
WrappedDivisibleOnly f (m a) -> m (WrappedDivisibleOnly f a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> WrappedDivisibleOnly f a -> m (WrappedDivisibleOnly f b)
$cmapM :: forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b)
-> WrappedDivisibleOnly f a -> m (WrappedDivisibleOnly f b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
WrappedDivisibleOnly f (f a) -> f (WrappedDivisibleOnly f a)
$csequenceA :: forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
WrappedDivisibleOnly f (f a) -> f (WrappedDivisibleOnly f a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> WrappedDivisibleOnly f a -> f (WrappedDivisibleOnly f b)
$ctraverse :: forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b)
-> WrappedDivisibleOnly f a -> f (WrappedDivisibleOnly f b)
Traversable)
deriving newtype (forall a. WrappedDivisibleOnly f a
forall a b c.
(a -> (b, c))
-> WrappedDivisibleOnly f b
-> WrappedDivisibleOnly f c
-> WrappedDivisibleOnly f a
forall (f :: * -> *).
Contravariant f
-> (forall a b c. (a -> (b, c)) -> f b -> f c -> f a)
-> (forall a. f a)
-> Divisible f
forall {f :: * -> *}.
Divisible f =>
Contravariant (WrappedDivisibleOnly f)
forall (f :: * -> *) a. Divisible f => WrappedDivisibleOnly f a
forall (f :: * -> *) a b c.
Divisible f =>
(a -> (b, c))
-> WrappedDivisibleOnly f b
-> WrappedDivisibleOnly f c
-> WrappedDivisibleOnly f a
conquer :: forall a. WrappedDivisibleOnly f a
$cconquer :: forall (f :: * -> *) a. Divisible f => WrappedDivisibleOnly f a
divide :: forall a b c.
(a -> (b, c))
-> WrappedDivisibleOnly f b
-> WrappedDivisibleOnly f c
-> WrappedDivisibleOnly f a
$cdivide :: forall (f :: * -> *) a b c.
Divisible f =>
(a -> (b, c))
-> WrappedDivisibleOnly f b
-> WrappedDivisibleOnly f c
-> WrappedDivisibleOnly f a
Divisible, forall b a.
b -> WrappedDivisibleOnly f b -> WrappedDivisibleOnly f a
forall a' a.
(a' -> a) -> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a'
forall (f :: * -> *) b a.
Contravariant f =>
b -> WrappedDivisibleOnly f b -> WrappedDivisibleOnly f a
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a'
forall (f :: * -> *).
(forall a' a. (a' -> a) -> f a -> f a')
-> (forall b a. b -> f b -> f a) -> Contravariant f
>$ :: forall b a.
b -> WrappedDivisibleOnly f b -> WrappedDivisibleOnly f a
$c>$ :: forall (f :: * -> *) b a.
Contravariant f =>
b -> WrappedDivisibleOnly f b -> WrappedDivisibleOnly f a
contramap :: forall a' a.
(a' -> a) -> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a'
$ccontramap :: forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f a'
Contravariant)
deriveShow1 ''WrappedDivisibleOnly
deriveRead1 ''WrappedDivisibleOnly
deriveEq1 ''WrappedDivisibleOnly
deriveOrd1 ''WrappedDivisibleOnly
instance Invariant f => Invariant (WrappedDivisibleOnly f) where
invmap :: forall a b.
(a -> b)
-> (b -> a) -> WrappedDivisibleOnly f a -> WrappedDivisibleOnly f b
invmap a -> b
f b -> a
g (WrapDivisibleOnly f a
x) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedDivisibleOnly f a
WrapDivisibleOnly (forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap a -> b
f b -> a
g f a
x)
instance (Divisible f, Invariant f) => Divise (WrappedDivisibleOnly f) where
divise :: forall a b c.
(a -> (b, c))
-> WrappedDivisibleOnly f b
-> WrappedDivisibleOnly f c
-> WrappedDivisibleOnly f a
divise a -> (b, c)
g (WrapDivisibleOnly f b
x) (WrapDivisibleOnly f c
y) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedDivisibleOnly f a
WrapDivisibleOnly (forall (f :: * -> *) a b c.
Divisible f =>
(a -> (b, c)) -> f b -> f c -> f a
divide a -> (b, c)
g f b
x f c
y)
instance (Divisible f, Invariant f) => Inply (WrappedDivisibleOnly f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c))
-> WrappedDivisibleOnly f b
-> WrappedDivisibleOnly f c
-> WrappedDivisibleOnly f a
gather b -> c -> a
_ a -> (b, c)
g (WrapDivisibleOnly f b
x) (WrapDivisibleOnly f c
y) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedDivisibleOnly f a
WrapDivisibleOnly (forall (f :: * -> *) a b c.
Divisible f =>
(a -> (b, c)) -> f b -> f c -> f a
divide a -> (b, c)
g f b
x f c
y)
gathered :: forall a b.
WrappedDivisibleOnly f a
-> WrappedDivisibleOnly f b -> WrappedDivisibleOnly f (a, b)
gathered (WrapDivisibleOnly f a
x) (WrapDivisibleOnly f b
y) = forall {k} (f :: k -> *) (a :: k). f a -> WrappedDivisibleOnly f a
WrapDivisibleOnly (forall (f :: * -> *) a b. Divisible f => f a -> f b -> f (a, b)
divided f a
x f b
y)
instance (Divisible f, Invariant f) => Inplicative (WrappedDivisibleOnly f) where
knot :: forall a. a -> WrappedDivisibleOnly f a
knot a
_ = forall (f :: * -> *) a. Divisible f => f a
conquer
funzip :: Functor f => f (a, b) -> (f a, f b)
funzip :: forall (f :: * -> *) a b. Functor f => f (a, b) -> (f a, f b)
funzip f (a, b)
x = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst f (a, b)
x, forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> b
snd f (a, b)
x)
instance Inply f => Inply (MaybeT f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> MaybeT f b -> MaybeT f c -> MaybeT f a
gather b -> c -> a
f a -> (b, c)
g (MaybeT f (Maybe b)
x) (MaybeT f (Maybe c)
y) = forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather (forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 b -> c -> a
f) (forall (f :: * -> *) a b. Functor f => f (a, b) -> (f a, f b)
funzip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> (b, c)
g) f (Maybe b)
x f (Maybe c)
y
instance Inplicative f => Inplicative (MaybeT f) where
knot :: forall a. a -> MaybeT f a
knot a
x = forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (forall (f :: * -> *) a. Inplicative f => a -> f a
knot (forall a. a -> Maybe a
Just a
x))
instance (Inply f, Semigroup w) => Inply (WriterT w f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> WriterT w f b -> WriterT w f c -> WriterT w f a
gather b -> c -> a
f a -> (b, c)
g (WriterT f (b, w)
x) (WriterT f (c, w)
y) = forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather (\case (b
a, w
q) -> \case (c
b, w
r) -> (b -> c -> a
f b
a c
b, w
q forall a. Semigroup a => a -> a -> a
<> w
r))
(\case (a
a, w
s) -> case a -> (b, c)
g a
a of (b
b, c
c) -> ((b
b, w
s), (c
c, w
s)))
f (b, w)
x f (c, w)
y
instance (Inplicative f, Monoid w) => Inplicative (WriterT w f) where
knot :: forall a. a -> WriterT w f a
knot a
x = forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (forall (f :: * -> *) a. Inplicative f => a -> f a
knot (a
x, forall a. Monoid a => a
mempty))
instance (Inply f, Semigroup w) => Inply (Strict.WriterT w f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> WriterT w f b -> WriterT w f c -> WriterT w f a
gather b -> c -> a
f a -> (b, c)
g (Strict.WriterT f (b, w)
x) (Strict.WriterT f (c, w)
y) = forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Strict.WriterT forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather (\(~(b
a, w
q)) (~(c
b, w
r)) -> (b -> c -> a
f b
a c
b, w
q forall a. Semigroup a => a -> a -> a
<> w
r))
(\(~(a
a, w
s)) -> let ~(b
b, c
c) = a -> (b, c)
g a
a in ((b
b, w
s), (c
c, w
s)))
f (b, w)
x f (c, w)
y
instance (Inplicative f, Monoid w) => Inplicative (Strict.WriterT w f) where
knot :: forall a. a -> WriterT w f a
knot a
x = forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Strict.WriterT (forall (f :: * -> *) a. Inplicative f => a -> f a
knot (a
x, forall a. Monoid a => a
mempty))
instance Inply f => Inply (ReaderT r f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> ReaderT r f b -> ReaderT r f c -> ReaderT r f a
gather b -> c -> a
f a -> (b, c)
g (ReaderT r -> f b
x) (ReaderT r -> f c
y) = forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \r
r ->
forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g (r -> f b
x r
r) (r -> f c
y r
r)
instance Inplicative f => Inplicative (ReaderT r f) where
knot :: forall a. a -> ReaderT r f a
knot a
x = forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT (\r
_ -> forall (f :: * -> *) a. Inplicative f => a -> f a
knot a
x)
instance Inply f => Inply (ExceptT e f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> ExceptT e f b -> ExceptT e f c -> ExceptT e f a
gather b -> c -> a
f a -> (b, c)
g (ExceptT f (Either e b)
x) (ExceptT f (Either e c)
y) = forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather (forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 b -> c -> a
f) (forall (f :: * -> *) a b. Functor f => f (a, b) -> (f a, f b)
funzip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> (b, c)
g) f (Either e b)
x f (Either e c)
y
instance Inplicative f => Inplicative (ExceptT e f) where
knot :: forall a. a -> ExceptT e f a
knot a
x = forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (forall (f :: * -> *) a. Inplicative f => a -> f a
knot (forall a b. b -> Either a b
Right a
x))
instance Inply f => Inply (ErrorT e f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> ErrorT e f b -> ErrorT e f c -> ErrorT e f a
gather b -> c -> a
f a -> (b, c)
g (ErrorT f (Either e b)
x) (ErrorT f (Either e c)
y) = forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather (forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 b -> c -> a
f) (forall (f :: * -> *) a b. Functor f => f (a, b) -> (f a, f b)
funzip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> (b, c)
g) f (Either e b)
x f (Either e c)
y
instance Inplicative f => Inplicative (ErrorT e f) where
knot :: forall a. a -> ErrorT e f a
knot a
x = forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (forall (f :: * -> *) a. Inplicative f => a -> f a
knot (forall a b. b -> Either a b
Right a
x))
instance Inply f => Inply (ListT f) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> ListT f b -> ListT f c -> ListT f a
gather b -> c -> a
f a -> (b, c)
g (ListT f [b]
x) (ListT f [c]
y) = forall (m :: * -> *) a. m [a] -> ListT m a
ListT forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather (forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 b -> c -> a
f) (forall (f :: * -> *) a b. Functor f => f (a, b) -> (f a, f b)
funzip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> (b, c)
g) f [b]
x f [c]
y
instance Inplicative f => Inplicative (ListT f) where
knot :: forall a. a -> ListT f a
knot a
x = forall (m :: * -> *) a. m [a] -> ListT m a
ListT (forall (f :: * -> *) a. Inplicative f => a -> f a
knot [a
x])
deriving via WrappedFunctor (RWST r w s m) instance (Bind m, Invariant m, Semigroup w) => Inply (RWST r w s m)
deriving via WrappedFunctor (RWST r w s m) instance (Monad m, Bind m, Invariant m, Monoid w) => Inplicative (RWST r w s m)
deriving via WrappedFunctor (Strict.RWST r w s m) instance (Bind m, Invariant m, Semigroup w) => Inply (Strict.RWST r w s m)
deriving via WrappedFunctor (Strict.RWST r w s m) instance (Monad m, Bind m, Invariant m, Monoid w) => Inplicative (Strict.RWST r w s m)
deriving via WrappedFunctor (StateT s m) instance (Bind m, Invariant m) => Inply (StateT s m)
deriving via WrappedFunctor (StateT s m) instance (Monad m, Bind m, Invariant m) => Inplicative (StateT s m)
deriving via WrappedFunctor (Strict.StateT s m) instance (Bind m, Invariant m) => Inply (Strict.StateT s m)
deriving via WrappedFunctor (Strict.StateT s m) instance (Monad m, Bind m, Invariant m) => Inplicative (Strict.StateT s m)
instance Inply f => Inply (Generics.M1 i t f :: Type -> Type) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> M1 i t f b -> M1 i t f c -> M1 i t f a
gather b -> c -> a
f a -> (b, c)
g (Generics.M1 f b
x) (Generics.M1 f c
y) = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Generics.M1 (forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g f b
x f c
y)
instance Inplicative f => Inplicative (Generics.M1 i t f :: Type -> Type) where
knot :: forall a. a -> M1 i t f a
knot = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Generics.M1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Inplicative f => a -> f a
knot
instance (Inply f, Inply g) => Inply (f Generics.:*: g) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> (:*:) f g b -> (:*:) f g c -> (:*:) f g a
gather b -> c -> a
f a -> (b, c)
g (f b
x1 Generics.:*: g b
y1) (f c
x2 Generics.:*: g c
y2) =
forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g f b
x1 f c
x2 forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
Generics.:*: forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g g b
y1 g c
y2
instance (Inplicative f, Inplicative g) => Inplicative (f Generics.:*: g) where
knot :: forall a. a -> (:*:) f g a
knot a
x = forall (f :: * -> *) a. Inplicative f => a -> f a
knot a
x forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
Generics.:*: forall (f :: * -> *) a. Inplicative f => a -> f a
knot a
x
instance (Inply f, Inply g) => Inply (Product f g) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> Product f g b -> Product f g c -> Product f g a
gather b -> c -> a
f a -> (b, c)
g (Pair f b
x1 g b
y1) (Pair f c
x2 g c
y2) =
forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g f b
x1 f c
x2 forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
`Pair` forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g g b
y1 g c
y2
instance (Inplicative f, Inplicative g) => Inplicative (Product f g) where
knot :: forall a. a -> Product f g a
knot a
x = forall (f :: * -> *) a. Inplicative f => a -> f a
knot a
x forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
`Pair` forall (f :: * -> *) a. Inplicative f => a -> f a
knot a
x
instance Inply f => Inply (Generics.Rec1 f :: Type -> Type) where
gather :: forall b c a.
(b -> c -> a) -> (a -> (b, c)) -> Rec1 f b -> Rec1 f c -> Rec1 f a
gather b -> c -> a
f a -> (b, c)
g (Generics.Rec1 f b
x) (Generics.Rec1 f c
y) = forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Generics.Rec1 (forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g f b
x f c
y)
instance Inplicative f => Inplicative (Generics.Rec1 f :: Type -> Type) where
knot :: forall a. a -> Rec1 f a
knot = forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Generics.Rec1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Inplicative f => a -> f a
knot
instance Inply f => Inply (Monoid.Alt f) where
gather :: forall b c a.
(b -> c -> a) -> (a -> (b, c)) -> Alt f b -> Alt f c -> Alt f a
gather b -> c -> a
f a -> (b, c)
g (Monoid.Alt f b
x) (Monoid.Alt f c
y) = forall {k} (f :: k -> *) (a :: k). f a -> Alt f a
Monoid.Alt (forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g f b
x f c
y)
instance Inplicative f => Inplicative (Monoid.Alt f) where
knot :: forall a. a -> Alt f a
knot = forall {k} (f :: k -> *) (a :: k). f a -> Alt f a
Monoid.Alt forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Inplicative f => a -> f a
knot
instance Inply f => Inply (IdentityT f :: Type -> Type) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> IdentityT f b -> IdentityT f c -> IdentityT f a
gather b -> c -> a
f a -> (b, c)
g (IdentityT f b
x) (IdentityT f c
y) = forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g f b
x f c
y)
instance Inplicative f => Inplicative (IdentityT f :: Type -> Type) where
knot :: forall a. a -> IdentityT f a
knot = forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Inplicative f => a -> f a
knot
instance Inply f => Inply (Reverse f :: Type -> Type) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> Reverse f b -> Reverse f c -> Reverse f a
gather b -> c -> a
f a -> (b, c)
g (Reverse f b
x) (Reverse f c
y) = forall {k} (f :: k -> *) (a :: k). f a -> Reverse f a
Reverse (forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g f b
x f c
y)
instance Inplicative f => Inplicative (Reverse f :: Type -> Type) where
knot :: forall a. a -> Reverse f a
knot = forall {k} (f :: k -> *) (a :: k). f a -> Reverse f a
Reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Inplicative f => a -> f a
knot
instance Inply f => Inply (Backwards f :: Type -> Type) where
gather :: forall b c a.
(b -> c -> a)
-> (a -> (b, c)) -> Backwards f b -> Backwards f c -> Backwards f a
gather b -> c -> a
f a -> (b, c)
g (Backwards f b
x) (Backwards f c
y) = forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g f b
x f c
y)
instance Inplicative f => Inplicative (Backwards f :: Type -> Type) where
knot :: forall a. a -> Backwards f a
knot = forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Inplicative f => a -> f a
knot
instance Inply f => Inply (Lift f) where
gather :: forall b c a.
(b -> c -> a) -> (a -> (b, c)) -> Lift f b -> Lift f c -> Lift f a
gather b -> c -> a
f a -> (b, c)
g = \case
Pure b
x -> \case
Pure c
y -> forall (f :: * -> *) a. a -> Lift f a
Pure (b -> c -> a
f b
x c
y)
Other f c
y -> forall (f :: * -> *) a. f a -> Lift f a
Other (forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap (b -> c -> a
f b
x) (forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> (b, c)
g) f c
y)
Other f b
x -> \case
Pure c
y -> forall (f :: * -> *) a. f a -> Lift f a
Other (forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap (b -> c -> a
`f` c
y) (forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> (b, c)
g) f b
x)
Other f c
y -> forall (f :: * -> *) a. f a -> Lift f a
Other (forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather b -> c -> a
f a -> (b, c)
g f b
x f c
y)
instance Inply f => Inplicative (Lift f) where
knot :: forall a. a -> Lift f a
knot = forall (f :: * -> *) a. a -> Lift f a
Pure
deriving via WrappedApplicativeOnly (Tagged a) instance Inply (Tagged a)
deriving via WrappedApplicativeOnly (Tagged a) instance Inplicative (Tagged a)
deriving via WrappedFunctor Identity instance Inply Identity
deriving via WrappedFunctor Identity instance Inplicative Identity
deriving via WrappedFunctor (Proxy :: Type -> Type) instance Inply Proxy
deriving via WrappedFunctor (Proxy :: Type -> Type) instance Inplicative Proxy
deriving via WrappedFunctor [] instance Inply []
deriving via WrappedFunctor [] instance Inplicative []
deriving via WrappedFunctor ((->) r) instance Inply ((->) r)
deriving via WrappedFunctor ((->) r) instance Inplicative ((->) r)
deriving via WrappedFunctor Maybe instance Inply Maybe
deriving via WrappedFunctor Maybe instance Inplicative Maybe
deriving via WrappedFunctor (Either e) instance Inply (Either e)
deriving via WrappedFunctor (Either e) instance Inplicative (Either e)
deriving via WrappedFunctor IO instance Inply IO
deriving via WrappedFunctor IO instance Inplicative IO
deriving via WrappedFunctor Generics.Par1 instance Inply Generics.Par1
deriving via WrappedFunctor Generics.Par1 instance Inplicative Generics.Par1
deriving via WrappedFunctor (Generics.U1 :: Type -> Type) instance Inply Generics.U1
deriving via WrappedFunctor (Generics.U1 :: Type -> Type) instance Inplicative Generics.U1
deriving via WrappedFunctor (Generics.K1 i c :: Type -> Type) instance Semigroup c => Inply (Generics.K1 i c)
deriving via WrappedFunctor (Generics.K1 i c :: Type -> Type) instance Monoid c => Inplicative (Generics.K1 i c)
deriving via WrappedFunctor Complex instance Inply Complex
deriving via WrappedFunctor Complex instance Inplicative Complex
deriving via WrappedFunctor Semigroup.Min instance Inply Semigroup.Min
deriving via WrappedFunctor Semigroup.Min instance Inplicative Semigroup.Min
deriving via WrappedFunctor Semigroup.Max instance Inply Semigroup.Max
deriving via WrappedFunctor Semigroup.Max instance Inplicative Semigroup.Max
deriving via WrappedFunctor Semigroup.First instance Inply Semigroup.First
deriving via WrappedFunctor Semigroup.First instance Inplicative Semigroup.First
deriving via WrappedFunctor Semigroup.Last instance Inply Semigroup.Last
deriving via WrappedFunctor Semigroup.Last instance Inplicative Semigroup.Last
#if !MIN_VERSION_base(4,16,0)
deriving via WrappedFunctor Semigroup.Option instance Inply Semigroup.Option
deriving via WrappedFunctor Semigroup.Option instance Inplicative Semigroup.Option
#endif
deriving via WrappedFunctor ZipList instance Inply ZipList
deriving via WrappedFunctor ZipList instance Inplicative ZipList
deriving via WrappedFunctor Monoid.First instance Inply Monoid.First
deriving via WrappedFunctor Monoid.First instance Inplicative Monoid.First
deriving via WrappedFunctor Monoid.Last instance Inply Monoid.Last
deriving via WrappedFunctor Monoid.Last instance Inplicative Monoid.Last
deriving via WrappedFunctor Monoid.Dual instance Inply Monoid.Dual
deriving via WrappedFunctor Monoid.Dual instance Inplicative Monoid.Dual
deriving via WrappedFunctor Monoid.Sum instance Inply Monoid.Sum
deriving via WrappedFunctor Monoid.Sum instance Inplicative Monoid.Sum
deriving via WrappedFunctor Monoid.Product instance Inply Monoid.Product
deriving via WrappedFunctor Monoid.Product instance Inplicative Monoid.Product
deriving via WrappedFunctor NonEmpty instance Inply NonEmpty
deriving via WrappedFunctor NonEmpty instance Inplicative NonEmpty
deriving via WrappedFunctor Tree instance Inply Tree
deriving via WrappedFunctor Tree instance Inplicative Tree
deriving via WrappedFunctor Seq instance Inply Seq
deriving via WrappedFunctor Seq instance Inplicative Seq
deriving via WrappedFunctor NESeq.NESeq instance Inply NESeq.NESeq
deriving via WrappedFunctor (WrappedArrow a b) instance Arrow a => Inply (WrappedArrow a b)
deriving via WrappedFunctor (WrappedArrow a b) instance Arrow a => Inplicative (WrappedArrow a b)
deriving via WrappedFunctor (Generics.V1 :: Type -> Type) instance Inply Generics.V1
deriving via WrappedFunctor IM.IntMap instance Inply IM.IntMap
deriving via WrappedFunctor (M.Map k) instance Ord k => Inply (M.Map k)
#if MIN_VERSION_base(4,16,0)
deriving via WrappedFunctor (HM.HashMap k) instance Hashable k => Inply (HM.HashMap k)
#else
deriving via WrappedFunctor (HM.HashMap k) instance (Hashable k, Eq k) => Inply (HM.HashMap k)
#endif
deriving via WrappedFunctor (Const w :: Type -> Type) instance Semigroup w => Inply (Const w)
deriving via WrappedFunctor (Const w :: Type -> Type) instance Monoid w => Inplicative (Const w)
deriving via WrappedFunctor (Constant w :: Type -> Type) instance Semigroup w => Inply (Constant w)
deriving via WrappedFunctor (Constant w :: Type -> Type) instance Monoid w => Inplicative (Constant w)
deriving via WrappedFunctor (ContT r (m :: Type -> Type)) instance Inply (ContT r m)
deriving via WrappedFunctor (ContT r (m :: Type -> Type)) instance Inplicative (ContT r m)
deriving via WrappedFunctor (WrappedMonad m) instance Monad m => Inply (WrappedMonad m)
deriving via WrappedFunctor (WrappedMonad m) instance Monad m => Inplicative (WrappedMonad m)
deriving via WrappedFunctor ((,) w :: Type -> Type) instance Semigroup w => Inply ((,) w)
deriving via WrappedFunctor ((,) w :: Type -> Type) instance Monoid w => Inplicative ((,) w)
deriving via WrappedDivisible SettableStateVar instance Inply SettableStateVar
deriving via WrappedDivisible SettableStateVar instance Inplicative SettableStateVar
deriving via WrappedDivisible Predicate instance Inply Predicate
deriving via WrappedDivisible Predicate instance Inplicative Predicate
deriving via WrappedDivisible Comparison instance Inply Comparison
deriving via WrappedDivisible Comparison instance Inplicative Comparison
deriving via WrappedDivisible Equivalence instance Inply Equivalence
deriving via WrappedDivisible Equivalence instance Inplicative Equivalence
deriving via WrappedDivisible (Op r) instance Semigroup r => Inply (Op r)
deriving via WrappedDivisible (Op r) instance Monoid r => Inplicative (Op r)
gatheredN
:: Inplicative f
=> NP f as
-> f (NP I as)
gatheredN :: forall (f :: * -> *) (as :: [*]).
Inplicative f =>
NP f as -> f (NP I as)
gatheredN = \case
NP f as
Nil -> forall (f :: * -> *) a. Inplicative f => a -> f a
knot forall {k} (a :: k -> *). NP a '[]
Nil
f x
x :* NP f xs
xs -> forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather
(\x
y NP I xs
ys -> forall a. a -> I a
I x
y forall {k} (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP I xs
ys)
(\case I x
y :* NP I xs
ys -> (x
y, NP I xs
ys))
f x
x
(forall (f :: * -> *) (as :: [*]).
Inplicative f =>
NP f as -> f (NP I as)
gatheredN NP f xs
xs)
gatheredNMap
:: Inplicative f
=> (NP I as -> b)
-> (b -> NP I as)
-> NP f as
-> f b
gatheredNMap :: forall (f :: * -> *) (as :: [*]) b.
Inplicative f =>
(NP I as -> b) -> (b -> NP I as) -> NP f as -> f b
gatheredNMap NP I as -> b
f b -> NP I as
g = forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap NP I as -> b
f b -> NP I as
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (as :: [*]).
Inplicative f =>
NP f as -> f (NP I as)
gatheredN
gatheredN1
:: Inply f
=> NP f (a ': as)
-> f (NP I (a ': as))
gatheredN1 :: forall (f :: * -> *) a (as :: [*]).
Inply f =>
NP f (a : as) -> f (NP I (a : as))
gatheredN1 (f x
x :* NP f xs
xs) = case NP f xs
xs of
NP f xs
Nil -> forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap ((forall {k} (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* forall {k} (a :: k -> *). NP a '[]
Nil) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> I a
I) (\case I x
y :* NP I xs
_ -> x
y) f x
x
f x
_ :* NP f xs
_ -> forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather
(\a
y NP I as
ys -> forall a. a -> I a
I a
y forall {k} (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP I as
ys)
(\case I x
y :* NP I xs
ys -> (x
y, NP I xs
ys))
f x
x
(forall (f :: * -> *) a (as :: [*]).
Inply f =>
NP f (a : as) -> f (NP I (a : as))
gatheredN1 NP f xs
xs)
gatheredN1Map
:: Inplicative f
=> (NP I (a ': as) -> b)
-> (b -> NP I (a ': as))
-> NP f (a ': as)
-> f b
gatheredN1Map :: forall (f :: * -> *) a (as :: [*]) b.
Inplicative f =>
(NP I (a : as) -> b)
-> (b -> NP I (a : as)) -> NP f (a : as) -> f b
gatheredN1Map NP I (a : as) -> b
f b -> NP I (a : as)
g = forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap NP I (a : as) -> b
f b -> NP I (a : as)
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a (as :: [*]).
Inply f =>
NP f (a : as) -> f (NP I (a : as))
gatheredN1
gatheredNRec
:: Inplicative f
=> V.Rec f as
-> f (V.XRec V.Identity as)
gatheredNRec :: forall (f :: * -> *) (as :: [*]).
Inplicative f =>
Rec f as -> f (XRec Identity as)
gatheredNRec = \case
Rec f as
V.RNil -> forall (f :: * -> *) a. Inplicative f => a -> f a
knot forall {u} (a :: u -> *). Rec a '[]
V.RNil
f r
x V.:& Rec f rs
xs -> forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather
forall {k} (f :: k -> *) (r :: k) (rs :: [k]).
HKD f r -> XRec f rs -> XRec f (r : rs)
(V.::&)
(\case HKD Identity r
y V.::& XRec Identity rs
ys -> (HKD Identity r
y, XRec Identity rs
ys))
f r
x
(forall (f :: * -> *) (as :: [*]).
Inplicative f =>
Rec f as -> f (XRec Identity as)
gatheredNRec Rec f rs
xs)
gatheredNMapRec
:: Inplicative f
=> (V.XRec V.Identity as -> b)
-> (b -> V.XRec V.Identity as)
-> V.Rec f as
-> f b
gatheredNMapRec :: forall (f :: * -> *) (as :: [*]) b.
Inplicative f =>
(XRec Identity as -> b)
-> (b -> XRec Identity as) -> Rec f as -> f b
gatheredNMapRec XRec Identity as -> b
f b -> XRec Identity as
g = forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap XRec Identity as -> b
f b -> XRec Identity as
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (as :: [*]).
Inplicative f =>
Rec f as -> f (XRec Identity as)
gatheredNRec
gatherN
:: forall f as b. (Inplicative f, V.IsoXRec V.Identity as, V.RecordCurry as)
=> V.Curried as b
-> (b -> V.XRec V.Identity as)
-> V.CurriedF f as (f b)
gatherN :: forall (f :: * -> *) (as :: [*]) b.
(Inplicative f, IsoXRec Identity as, RecordCurry as) =>
Curried as b -> (b -> XRec Identity as) -> CurriedF f as (f b)
gatherN Curried as b
f b -> XRec Identity as
g = forall {u} (ts :: [u]) (f :: u -> *) a.
RecordCurry ts =>
(Rec f ts -> a) -> CurriedF f ts a
V.rcurry @as @f forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap (forall (ts :: [*]) a. Curried ts a -> Rec Identity ts -> a
V.runcurry' Curried as b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {u} (f :: u -> *) (ts :: [u]).
IsoXRec f ts =>
XRec f ts -> Rec f ts
V.fromXRec) b -> XRec Identity as
g
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (as :: [*]).
Inplicative f =>
Rec f as -> f (XRec Identity as)
gatheredNRec
gatheredN1Rec
:: Inply f
=> V.Rec f (a ': as)
-> f (V.XRec V.Identity (a ': as))
gatheredN1Rec :: forall (f :: * -> *) a (as :: [*]).
Inply f =>
Rec f (a : as) -> f (XRec Identity (a : as))
gatheredN1Rec (f r
x V.:& Rec f rs
xs) = case Rec f rs
xs of
Rec f rs
V.RNil -> forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap (forall {k} (f :: k -> *) (r :: k) (rs :: [k]).
HKD f r -> XRec f rs -> XRec f (r : rs)
V.::& forall {u} (a :: u -> *). Rec a '[]
V.RNil) (\case HKD Identity a
z V.::& XRec Identity as
_ -> HKD Identity a
z) f r
x
f r
_ V.:& Rec f rs
_ -> forall (f :: * -> *) b c a.
Inply f =>
(b -> c -> a) -> (a -> (b, c)) -> f b -> f c -> f a
gather
forall {k} (f :: k -> *) (r :: k) (rs :: [k]).
HKD f r -> XRec f rs -> XRec f (r : rs)
(V.::&)
(\case HKD Identity a
y V.::& XRec Identity as
ys -> (HKD Identity a
y, XRec Identity as
ys))
f r
x
(forall (f :: * -> *) a (as :: [*]).
Inply f =>
Rec f (a : as) -> f (XRec Identity (a : as))
gatheredN1Rec Rec f rs
xs)
gatheredN1MapRec
:: Inplicative f
=> (V.XRec V.Identity (a ': as) -> b)
-> (b -> V.XRec V.Identity (a ': as))
-> V.Rec f (a ': as)
-> f b
gatheredN1MapRec :: forall (f :: * -> *) a (as :: [*]) b.
Inplicative f =>
(XRec Identity (a : as) -> b)
-> (b -> XRec Identity (a : as)) -> Rec f (a : as) -> f b
gatheredN1MapRec XRec Identity (a : as) -> b
f b -> XRec Identity (a : as)
g = forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap XRec Identity (a : as) -> b
f b -> XRec Identity (a : as)
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a (as :: [*]).
Inply f =>
Rec f (a : as) -> f (XRec Identity (a : as))
gatheredN1Rec
gatherN1
:: forall f a as b. (Inply f, V.IsoXRec V.Identity as, V.RecordCurry as)
=> V.Curried (a ': as) b
-> (b -> V.XRec V.Identity (a ': as))
-> V.CurriedF f (a ': as) (f b)
gatherN1 :: forall (f :: * -> *) a (as :: [*]) b.
(Inply f, IsoXRec Identity as, RecordCurry as) =>
Curried (a : as) b
-> (b -> XRec Identity (a : as)) -> CurriedF f (a : as) (f b)
gatherN1 Curried (a : as) b
f b -> XRec Identity (a : as)
g = forall {u} (ts :: [u]) (f :: u -> *) a.
RecordCurry ts =>
(Rec f ts -> a) -> CurriedF f ts a
V.rcurry @(a ': as) @f forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) a b.
Invariant f =>
(a -> b) -> (b -> a) -> f a -> f b
invmap (forall (ts :: [*]) a. Curried ts a -> Rec Identity ts -> a
V.runcurry' Curried (a : as) b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {u} (f :: u -> *) (ts :: [u]).
IsoXRec f ts =>
XRec f ts -> Rec f ts
V.fromXRec) b -> XRec Identity (a : as)
g
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a (as :: [*]).
Inply f =>
Rec f (a : as) -> f (XRec Identity (a : as))
gatheredN1Rec
runDayApply
:: forall f g h. Apply h
=> f ~> h
-> g ~> h
-> Day f g ~> h
runDayApply :: forall (f :: * -> *) (g :: * -> *) (h :: * -> *).
Apply h =>
(f ~> h) -> (g ~> h) -> Day f g ~> h
runDayApply f ~> h
f g ~> h
g (Day f b
x g c
y b -> c -> x
j x -> (b, c)
_) = forall (f :: * -> *) a b c.
Apply f =>
(a -> b -> c) -> f a -> f b -> f c
liftF2 b -> c -> x
j (f ~> h
f f b
x) (g ~> h
g g c
y)
runDayDivise
:: forall f g h. Divise h
=> f ~> h
-> g ~> h
-> Day f g ~> h
runDayDivise :: forall (f :: * -> *) (g :: * -> *) (h :: * -> *).
Divise h =>
(f ~> h) -> (g ~> h) -> Day f g ~> h
runDayDivise f ~> h
f g ~> h
g (Day f b
x g c
y b -> c -> x
_ x -> (b, c)
h) = forall (f :: * -> *) a b c.
Divise f =>
(a -> (b, c)) -> f b -> f c -> f a
divise x -> (b, c)
h (f ~> h
f f b
x) (g ~> h
g g c
y)