cartesian-profunctors
Safe HaskellNone
LanguageHaskell2010

Data.PTraversable

Synopsis

Documentation

class (Ord1 t, Traversable t) => PTraversable (t :: Type -> Type) where Source #

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> t a) -> (t b -> bs) -> p a b -> p as bs Source #

Instances

Instances details
PTraversable Identity Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Identity a) -> (Identity b -> bs) -> p a b -> p as bs Source #

PTraversable Par1 Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Par1 a) -> (Par1 b -> bs) -> p a b -> p as bs Source #

PTraversable Maybe Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Maybe a) -> (Maybe b -> bs) -> p a b -> p as bs Source #

PTraversable [] Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> [a]) -> ([b] -> bs) -> p a b -> p as bs Source #

Enum a => PTraversable (Either a) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Either a a0) -> (Either a b -> bs) -> p a0 b -> p as bs Source #

PTraversable (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> U1 a) -> (U1 b -> bs) -> p a b -> p as bs Source #

PTraversable (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> V1 a) -> (V1 b -> bs) -> p a b -> p as bs Source #

PTraversable t => PTraversable (WrappedPTraversable t) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> WrappedPTraversable t a) -> (WrappedPTraversable t b -> bs) -> p a b -> p as bs Source #

Enum a => PTraversable ((,) a) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> (a, a0)) -> ((a, b) -> bs) -> p a0 b -> p as bs Source #

(Generic1 t, PTraversable (Rep1 t)) => PTraversable (Generically1 t) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Generically1 t a) -> (Generically1 t b -> bs) -> p a b -> p as bs Source #

PTraversable f => PTraversable (Rec1 f) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Rec1 f a) -> (Rec1 f b -> bs) -> p a b -> p as bs Source #

(PTraversable t, PTraversable u) => PTraversable (Product t u) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Product t u a) -> (Product t u b -> bs) -> p a b -> p as bs Source #

(PTraversable t, PTraversable u) => PTraversable (Sum t u) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Sum t u a) -> (Sum t u b -> bs) -> p a b -> p as bs Source #

(PTraversable f, PTraversable g) => PTraversable (f :*: g) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> (f :*: g) a) -> ((f :*: g) b -> bs) -> p a b -> p as bs Source #

(PTraversable t, PTraversable u) => PTraversable (t :+: u) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> (t :+: u) a) -> ((t :+: u) b -> bs) -> p a b -> p as bs Source #

Enum c => PTraversable (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> K1 i c a) -> (K1 i c b -> bs) -> p a b -> p as bs Source #

(PTraversable t, PTraversable u) => PTraversable (Compose t u) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Compose t u a) -> (Compose t u b -> bs) -> p a b -> p as bs Source #

(PTraversable t, PTraversable u) => PTraversable (t :.: u) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> (t :.: u) a) -> ((t :.: u) b -> bs) -> p a b -> p as bs Source #

PTraversable f => PTraversable (M1 i c f) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> M1 i c f a) -> (M1 i c f b -> bs) -> p a b -> p as bs Source #

ptraverse :: (PTraversable t, Cartesian p, Cocartesian p) => p a b -> p (t a) (t b) Source #

fmapDefault :: PTraversable t => (a -> b) -> t a -> t b Source #

foldMapDefault :: (PTraversable t, Monoid m) => (a -> m) -> t a -> m Source #

traverseDefault :: (PTraversable t, Applicative f) => (a -> f b) -> t a -> f (t b) Source #

Default equality and comparison

eq1Default :: (PTraversable t, Eq a) => t a -> t a -> Bool Source #

liftEq' :: PTraversable t => (a -> a -> Bool) -> t a -> t a -> Bool Source #

Type-restricted version of liftEq.

liftEq  :: forall t a b. (Eq1 t) => (a -> b -> Bool) -> t a -> t b -> Bool
liftEq' :: forall t a.   (.....) => (a -> a -> Bool) -> t a -> t a -> Bool

liftEqDefault :: PTraversable t => (a -> b -> Bool) -> t a -> t b -> Bool Source #

compare1Default :: (PTraversable t, Ord a) => t a -> t a -> Ordering Source #

liftCompare' :: PTraversable t => (a -> a -> Ordering) -> t a -> t a -> Ordering Source #

Type-restricted version of liftCompare.

liftEq  :: forall t a b. (Eq1 t) => (a -> b -> Bool) -> t a -> t b -> Bool
liftEq' :: forall t a.   (.....) => (a -> a -> Bool) -> t a -> t a -> Bool

liftCompareDefault :: PTraversable t => (a -> b -> Ordering) -> t a -> t b -> Ordering Source #

cardinality1 :: forall (t :: Type -> Type) proxy. PTraversable t => proxy t -> Int -> Int Source #

enum1 :: (PTraversable t, Alternative f) => f a -> f (t a) Source #

coenum1 :: (PTraversable t, Divisible f, Decidable f) => f b -> f (t b) Source #

newtype WrappedPTraversable (t :: Type -> Type) a Source #

Constructors

WrapPTraversable 

Fields

Instances

Instances details
PTraversable t => Foldable (WrappedPTraversable t) Source # 
Instance details

Defined in Data.PTraversable

Methods

fold :: Monoid m => WrappedPTraversable t m -> m #

foldMap :: Monoid m => (a -> m) -> WrappedPTraversable t a -> m #

foldMap' :: Monoid m => (a -> m) -> WrappedPTraversable t a -> m #

foldr :: (a -> b -> b) -> b -> WrappedPTraversable t a -> b #

foldr' :: (a -> b -> b) -> b -> WrappedPTraversable t a -> b #

foldl :: (b -> a -> b) -> b -> WrappedPTraversable t a -> b #

foldl' :: (b -> a -> b) -> b -> WrappedPTraversable t a -> b #

foldr1 :: (a -> a -> a) -> WrappedPTraversable t a -> a #

foldl1 :: (a -> a -> a) -> WrappedPTraversable t a -> a #

toList :: WrappedPTraversable t a -> [a] #

null :: WrappedPTraversable t a -> Bool #

length :: WrappedPTraversable t a -> Int #

elem :: Eq a => a -> WrappedPTraversable t a -> Bool #

maximum :: Ord a => WrappedPTraversable t a -> a #

minimum :: Ord a => WrappedPTraversable t a -> a #

sum :: Num a => WrappedPTraversable t a -> a #

product :: Num a => WrappedPTraversable t a -> a #

PTraversable t => Eq1 (WrappedPTraversable t) Source # 
Instance details

Defined in Data.PTraversable

Methods

liftEq :: (a -> b -> Bool) -> WrappedPTraversable t a -> WrappedPTraversable t b -> Bool #

PTraversable t => Ord1 (WrappedPTraversable t) Source # 
Instance details

Defined in Data.PTraversable

Methods

liftCompare :: (a -> b -> Ordering) -> WrappedPTraversable t a -> WrappedPTraversable t b -> Ordering #

PTraversable t => Traversable (WrappedPTraversable t) Source # 
Instance details

Defined in Data.PTraversable

Methods

traverse :: Applicative f => (a -> f b) -> WrappedPTraversable t a -> f (WrappedPTraversable t b) #

sequenceA :: Applicative f => WrappedPTraversable t (f a) -> f (WrappedPTraversable t a) #

mapM :: Monad m => (a -> m b) -> WrappedPTraversable t a -> m (WrappedPTraversable t b) #

sequence :: Monad m => WrappedPTraversable t (m a) -> m (WrappedPTraversable t a) #

PTraversable t => Functor (WrappedPTraversable t) Source # 
Instance details

Defined in Data.PTraversable

Methods

fmap :: (a -> b) -> WrappedPTraversable t a -> WrappedPTraversable t b #

(<$) :: a -> WrappedPTraversable t b -> WrappedPTraversable t a #

PTraversable t => PTraversable (WrappedPTraversable t) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> WrappedPTraversable t a) -> (WrappedPTraversable t b -> bs) -> p a b -> p as bs Source #

(Enum a, PTraversable t) => Enum (WrappedPTraversable t a) Source # 
Instance details

Defined in Data.PTraversable

Methods

enumeration :: FinFn (WrappedPTraversable t a) (WrappedPTraversable t a) Source #

withEnum :: (forall (n :: Nat). KnownNat n => (WrappedPTraversable t a -> Finite n) -> (Finite n -> WrappedPTraversable t a) -> r) -> r Source #

(Eq a, PTraversable t) => Eq (WrappedPTraversable t a) Source # 
Instance details

Defined in Data.PTraversable

(Ord a, PTraversable t) => Ord (WrappedPTraversable t a) Source # 
Instance details

Defined in Data.PTraversable

newtype Generically1 (f :: k -> Type) (a :: k) where #

A type whose instances are defined generically, using the Generic1 representation. Generically1 is a higher-kinded version of Generically that uses Generic.

Generic instances can be derived for type constructors via Generically1 F using -XDerivingVia.

{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia        #-}

import GHC.Generics (Generic)

data V4 a = V4 a a a a
  deriving stock (Functor, Generic1)

  deriving Applicative
  via Generically1 V4

This corresponds to Applicative instances defined by pointwise lifting:

instance Applicative V4 where
  pure :: a -> V4 a
  pure a = V4 a a a a

  liftA2 :: (a -> b -> c) -> (V4 a -> V4 b -> V4 c)
  liftA2 (·) (V4 a1 b1 c1 d1) (V4 a2 b2 c2 d2) =
    V4 (a1 · a2) (b1 · b2) (c1 · c2) (d1 · d2)

Historically this required modifying the type class to include generic method definitions (-XDefaultSignatures) and deriving it with the anyclass strategy (-XDeriveAnyClass). Having a /via type/ like Generically1 decouples the instance from the type class.

Since: base-4.17.0.0

Constructors

Generically1 :: forall {k} (f :: k -> Type) (a :: k). f a -> Generically1 f a 

Instances

Instances details
(Generic1 t, Foldable (Rep1 t)) => Foldable (Generically1 t) Source # 
Instance details

Defined in GHC.Generics.Orphans

Methods

fold :: Monoid m => Generically1 t m -> m #

foldMap :: Monoid m => (a -> m) -> Generically1 t a -> m #

foldMap' :: Monoid m => (a -> m) -> Generically1 t a -> m #

foldr :: (a -> b -> b) -> b -> Generically1 t a -> b #

foldr' :: (a -> b -> b) -> b -> Generically1 t a -> b #

foldl :: (b -> a -> b) -> b -> Generically1 t a -> b #

foldl' :: (b -> a -> b) -> b -> Generically1 t a -> b #

foldr1 :: (a -> a -> a) -> Generically1 t a -> a #

foldl1 :: (a -> a -> a) -> Generically1 t a -> a #

toList :: Generically1 t a -> [a] #

null :: Generically1 t a -> Bool #

length :: Generically1 t a -> Int #

elem :: Eq a => a -> Generically1 t a -> Bool #

maximum :: Ord a => Generically1 t a -> a #

minimum :: Ord a => Generically1 t a -> a #

sum :: Num a => Generically1 t a -> a #

product :: Num a => Generically1 t a -> a #

(Generic1 f, Eq1 (Rep1 f)) => Eq1 (Generically1 f)

Since: base-4.17.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool #

(Generic1 f, Ord1 (Rep1 f)) => Ord1 (Generically1 f)

Since: base-4.17.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering #

(Generic1 t, Traversable (Rep1 t)) => Traversable (Generically1 t) Source # 
Instance details

Defined in GHC.Generics.Orphans

Methods

traverse :: Applicative f => (a -> f b) -> Generically1 t a -> f (Generically1 t b) #

sequenceA :: Applicative f => Generically1 t (f a) -> f (Generically1 t a) #

mapM :: Monad m => (a -> m b) -> Generically1 t a -> m (Generically1 t b) #

sequence :: Monad m => Generically1 t (m a) -> m (Generically1 t a) #

(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f)

Since: base-4.17.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: Generically1 f a #

(<|>) :: Generically1 f a -> Generically1 f a -> Generically1 f a #

some :: Generically1 f a -> Generically1 f [a] #

many :: Generically1 f a -> Generically1 f [a] #

(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f)

Since: base-4.17.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> Generically1 f a #

(<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b #

liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c #

(*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b #

(<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a #

(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f)

Since: base-4.17.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> Generically1 f a -> Generically1 f b #

(<$) :: a -> Generically1 f b -> Generically1 f a #

(Generic1 t, PTraversable (Rep1 t)) => PTraversable (Generically1 t) Source # 
Instance details

Defined in Data.PTraversable

Methods

ptraverseWith :: (Cartesian p, Cocartesian p) => (as -> Generically1 t a) -> (Generically1 t b -> bs) -> p a b -> p as bs Source #

(Generic1 f, Eq (Rep1 f a)) => Eq (Generically1 f a)

Since: base-4.18.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: Generically1 f a -> Generically1 f a -> Bool #

(/=) :: Generically1 f a -> Generically1 f a -> Bool #

(Generic1 f, Ord (Rep1 f a)) => Ord (Generically1 f a)

Since: base-4.18.0.0

Instance details

Defined in GHC.Generics

ptraverseDay :: forall (t :: Type -> Type) (u :: Type -> Type) p a b. (PTraversable t, PTraversable u, Cartesian p, Cocartesian p) => p a b -> p (Day t u a) (Day t u b) Source #

Day lacks various instances required to be PTraversable

ptraverseDayWith :: forall (t :: Type -> Type) (u :: Type -> Type) p x a b y. (PTraversable t, PTraversable u, Cartesian p, Cocartesian p) => (x -> Day t u a) -> (Day t u b -> y) -> p a b -> p x y Source #