ten-0.1.0.1: Typeclasses like Functor, etc. over arity-1 type constructors.
Safe HaskellNone
LanguageHaskell2010

Data.Ten.Applicative

Description

Provides an analog of Applicative over arity-1 type constructors.

Synopsis

Documentation

class Functor10 f => Applicative10 f where Source #

Applicative over arity-1 type constructors.

See also Functor10 and Foldable10.

Minimal complete definition

pure10, ((<*>!) | liftA210)

Methods

pure10 :: (forall a. m a) -> f m Source #

Lift a parametric m value into an f m.

(<*>!) :: f (m :->: n) -> f m -> f n infixl 4 Source #

(<*>) for Applicative10: zip two fs with runArr10.

liftA210 :: (forall a. m a -> n a -> o a) -> f m -> f n -> f o Source #

liftA2 for Applicative10: zip two fs with a parametric function.

Instances

Instances details
Applicative10 (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Applicative

Methods

pure10 :: (forall (a :: k0). m a) -> U1 m Source #

(<*>!) :: forall (m :: k0 -> Type) (n :: k0 -> Type). U1 (m :->: n) -> U1 m -> U1 n Source #

liftA210 :: (forall (a :: k0). m a -> n a -> o a) -> U1 m -> U1 n -> U1 o Source #

Applicative10 (Ap10 a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Applicative

Methods

pure10 :: (forall (a0 :: k0). m a0) -> Ap10 a m Source #

(<*>!) :: forall (m :: k0 -> Type) (n :: k0 -> Type). Ap10 a (m :->: n) -> Ap10 a m -> Ap10 a n Source #

liftA210 :: (forall (a0 :: k0). m a0 -> n a0 -> o a0) -> Ap10 a m -> Ap10 a n -> Ap10 a o Source #

Applicative10 f => Applicative10 (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Applicative

Methods

pure10 :: (forall (a :: k0). m a) -> Rec1 f m Source #

(<*>!) :: forall (m :: k0 -> Type) (n :: k0 -> Type). Rec1 f (m :->: n) -> Rec1 f m -> Rec1 f n Source #

liftA210 :: (forall (a :: k0). m a -> n a -> o a) -> Rec1 f m -> Rec1 f n -> Rec1 f o Source #

(Applicative10 f, Applicative10 g) => Applicative10 (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Applicative

Methods

pure10 :: (forall (a :: k0). m a) -> (f :*: g) m Source #

(<*>!) :: forall (m :: k0 -> Type) (n :: k0 -> Type). (f :*: g) (m :->: n) -> (f :*: g) m -> (f :*: g) n Source #

liftA210 :: (forall (a :: k0). m a -> n a -> o a) -> (f :*: g) m -> (f :*: g) n -> (f :*: g) o Source #

Monoid a => Applicative10 (K1 i a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Applicative

Methods

pure10 :: (forall (a0 :: k0). m a0) -> K1 i a m Source #

(<*>!) :: forall (m :: k0 -> Type) (n :: k0 -> Type). K1 i a (m :->: n) -> K1 i a m -> K1 i a n Source #

liftA210 :: (forall (a0 :: k0). m a0 -> n a0 -> o a0) -> K1 i a m -> K1 i a n -> K1 i a o Source #

(Generic1 f, Applicative10 (Rep1 f)) => Applicative10 (Wrapped1 (Generic1 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Applicative

Methods

pure10 :: (forall (a :: k0). m a) -> Wrapped1 Generic1 f m Source #

(<*>!) :: forall (m :: k0 -> Type) (n :: k0 -> Type). Wrapped1 Generic1 f (m :->: n) -> Wrapped1 Generic1 f m -> Wrapped1 Generic1 f n Source #

liftA210 :: (forall (a :: k0). m a -> n a -> o a) -> Wrapped1 Generic1 f m -> Wrapped1 Generic1 f n -> Wrapped1 Generic1 f o Source #

(Applicative f, Applicative10 g) => Applicative10 (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Applicative

Methods

pure10 :: (forall (a :: k0). m a) -> (f :.: g) m Source #

(<*>!) :: forall (m :: k0 -> Type) (n :: k0 -> Type). (f :.: g) (m :->: n) -> (f :.: g) m -> (f :.: g) n Source #

liftA210 :: (forall (a :: k0). m a -> n a -> o a) -> (f :.: g) m -> (f :.: g) n -> (f :.: g) o Source #

Applicative10 f => Applicative10 (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Applicative

Methods

pure10 :: (forall (a :: k0). m a) -> M1 i c f m Source #

(<*>!) :: forall (m :: k0 -> Type) (n :: k0 -> Type). M1 i c f (m :->: n) -> M1 i c f m -> M1 i c f n Source #

liftA210 :: (forall (a :: k0). m a -> n a -> o a) -> M1 i c f m -> M1 i c f n -> M1 i c f o Source #

(<*!) :: Applicative10 f => f m -> f n -> f m infixl 4 Source #

(*>!) :: Applicative10 f => f m -> f n -> f n infixl 4 Source #

liftA310 :: Applicative10 f => (forall a. m a -> n a -> o a -> p a) -> f m -> f n -> f o -> f p Source #

newtype (m :->: n) a Source #

A function m a -> n a wrapped in a newtype for use as a type parameter.

This is used to represent the partially-applied functions in the left side of (<*>!).

Constructors

Arr10 

Fields

pure10C :: forall c f m. (Entails (Index10 f) c, Applicative10 f, Functor10WithIndex f) => (forall a. c a => m a) -> f m Source #

pure10 with access to an instance for every element.

liftA210C :: forall c f m n o. (Entails (Index10 f) c, Applicative10 f, Functor10WithIndex f) => (forall a. c a => m a -> n a -> o a) -> f m -> f n -> f o Source #

liftA210 with access to an instance for every element.

liftA310C :: forall c f m n o p. (Entails (Index10 f) c, Applicative10 f, Functor10WithIndex f) => (forall a. c a => m a -> n a -> o a -> p a) -> f m -> f n -> f o -> f p Source #

liftA310 with access to an instance for every element.