functor-combinators-0.2.0.0: Tools for functor combinator-based program design

Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Applicative.Step

Contents

Description

This module provides functor combinators that are the fixed points of applications of :+: and These1. They are useful for their Interpret instances, along with their relationship to the Monoidal instances of :+: and These1.

Synopsis

Fixed Points

data Step f a Source #

An f a, along with a Natural index.

Step f a ~ (Natural, f a)
Step f   ~ ((,) Natural) :.: f       -- functor composition

It is the fixed point of infinite applications of :+: (functor sums).

Intuitively, in an infinite f :+: f :+: f :+: f ..., you have exactly one f somewhere. A Step f a has that f, with a Natural giving you "where" the f is in the long chain.

Can be useful for using with the Monoidal instance of :+:.

interpreting it requires no constraint on the target context.

Note that this type and its instances equivalent to EnvT (Sum Natural).

Constructors

Step 

Fields

Instances
HFunctor (Step :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hmap :: (f ~> g) -> Step f ~> Step g Source #

HBind (Step :: (k -> Type) -> k -> Type) Source #

Equivalent to instance for EnvT (Sum Natural).

Instance details

Defined in Data.HFunctor

Methods

hbind :: (f ~> Step g) -> Step f ~> Step g Source #

hjoin :: Step (Step f) ~> Step f Source #

Inject (Step :: (k -> Type) -> k -> Type) Source #

Injects with 0.

Equivalent to instance for EnvT (Sum Natural).

Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> Step f Source #

Interpret (Step :: (k -> Type) -> k -> Type) (f :: k -> Type) Source #

Equivalent to instance for EnvT (Sum Natural).

Instance details

Defined in Data.HFunctor.Interpret

Methods

retract :: Step f ~> f Source #

interpret :: (g ~> f) -> Step g ~> f Source #

Functor f => Functor (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

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

Applicative f => Applicative (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

pure :: a -> Step f a #

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

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

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

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

Foldable f => Foldable (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fold :: Monoid m => Step f m -> m #

foldMap :: Monoid m => (a -> m) -> Step f a -> m #

foldr :: (a -> b -> b) -> b -> Step f a -> b #

foldr' :: (a -> b -> b) -> b -> Step f a -> b #

foldl :: (b -> a -> b) -> b -> Step f a -> b #

foldl' :: (b -> a -> b) -> b -> Step f a -> b #

foldr1 :: (a -> a -> a) -> Step f a -> a #

foldl1 :: (a -> a -> a) -> Step f a -> a #

toList :: Step f a -> [a] #

null :: Step f a -> Bool #

length :: Step f a -> Int #

elem :: Eq a => a -> Step f a -> Bool #

maximum :: Ord a => Step f a -> a #

minimum :: Ord a => Step f a -> a #

sum :: Num a => Step f a -> a #

product :: Num a => Step f a -> a #

Traversable f => Traversable (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Step f a -> f0 (Step f b) #

sequenceA :: Applicative f0 => Step f (f0 a) -> f0 (Step f a) #

mapM :: Monad m => (a -> m b) -> Step f a -> m (Step f b) #

sequence :: Monad m => Step f (m a) -> m (Step f a) #

Eq1 f => Eq1 (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

Ord1 f => Ord1 (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

Read1 f => Read1 (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Step f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Step f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Step f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Step f a] #

Show1 f => Show1 (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Step f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Step f a] -> ShowS #

Foldable1 f => Foldable1 (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fold1 :: Semigroup m => Step f m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Step f a -> m #

toNonEmpty :: Step f a -> NonEmpty a #

Pointed f => Pointed (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

point :: a -> Step f a #

Traversable1 f => Traversable1 (Step f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

traverse1 :: Apply f0 => (a -> f0 b) -> Step f a -> f0 (Step f b) #

sequence1 :: Apply f0 => Step f (f0 b) -> f0 (Step f b) #

Eq (f a) => Eq (Step f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

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

(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (Step f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Step f a -> c (Step f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Step f a) #

toConstr :: Step f a -> Constr #

dataTypeOf :: Step f a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Step f a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Step f a)) #

gmapT :: (forall b. Data b => b -> b) -> Step f a -> Step f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Step f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Step f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Step f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Step f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Step f a -> m (Step f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Step f a -> m (Step f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Step f a -> m (Step f a) #

Ord (f a) => Ord (Step f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

compare :: Step f a -> Step f a -> Ordering #

(<) :: Step f a -> Step f a -> Bool #

(<=) :: Step f a -> Step f a -> Bool #

(>) :: Step f a -> Step f a -> Bool #

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

max :: Step f a -> Step f a -> Step f a #

min :: Step f a -> Step f a -> Step f a #

Read (f a) => Read (Step f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

readsPrec :: Int -> ReadS (Step f a) #

readList :: ReadS [Step f a] #

readPrec :: ReadPrec (Step f a) #

readListPrec :: ReadPrec [Step f a] #

Show (f a) => Show (Step f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

showsPrec :: Int -> Step f a -> ShowS #

show :: Step f a -> String #

showList :: [Step f a] -> ShowS #

Generic (Step f a) Source # 
Instance details

Defined in Control.Applicative.Step

Associated Types

type Rep (Step f a) :: Type -> Type #

Methods

from :: Step f a -> Rep (Step f a) x #

to :: Rep (Step f a) x -> Step f a #

type Rep (Step f a) Source # 
Instance details

Defined in Control.Applicative.Step

type Rep (Step f a) = D1 (MetaData "Step" "Control.Applicative.Step" "functor-combinators-0.2.0.0-inplace" False) (C1 (MetaCons "Step" PrefixI True) (S1 (MetaSel (Just "stepPos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural) :*: S1 (MetaSel (Just "stepVal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))

newtype Steps f a Source #

A non-empty map of Natural to f a. Basically, contains multiple f as, each at a given Natural index.

Steps f a ~ Map Natural (f a)
Steps f   ~ Map Natural :.: f       -- functor composition

It is the fixed point of applications of TheseT.

You can think of this as an infinite sparse array of f as.

Intuitively, in an infinite f `TheseT` f `TheseT` f `TheseT` f ..., each of those infinite positions may have an f in them. However, because of the at-least-one nature of TheseT, we know we have at least one f at one position somewhere.

A Steps f a has potentially many fs, each stored at a different Natural position, with the guaruntee that at least one f exists.

Can be useful for using with the Monoidal instance of TheseT.

interpreting it requires at least an Alt instance in the target context, since we have to handle potentially more than one f.

This type is essentailly the same as NEMapF (Sum Natural) (except with a different Semigroup instance).

Constructors

Steps 

Fields

Instances
HFunctor (Steps :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hmap :: (f ~> g) -> Steps f ~> Steps g Source #

Inject (Steps :: (k -> Type) -> k -> Type) Source #

Injects into a singleton map at 0; same behavior as NEMapF (Sum Natural).

Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> Steps f Source #

Alt f => Interpret (Steps :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.Interpret

Methods

retract :: Steps f ~> f Source #

interpret :: (g ~> f) -> Steps g ~> f Source #

Functor f => Functor (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

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

Foldable f => Foldable (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fold :: Monoid m => Steps f m -> m #

foldMap :: Monoid m => (a -> m) -> Steps f a -> m #

foldr :: (a -> b -> b) -> b -> Steps f a -> b #

foldr' :: (a -> b -> b) -> b -> Steps f a -> b #

foldl :: (b -> a -> b) -> b -> Steps f a -> b #

foldl' :: (b -> a -> b) -> b -> Steps f a -> b #

foldr1 :: (a -> a -> a) -> Steps f a -> a #

foldl1 :: (a -> a -> a) -> Steps f a -> a #

toList :: Steps f a -> [a] #

null :: Steps f a -> Bool #

length :: Steps f a -> Int #

elem :: Eq a => a -> Steps f a -> Bool #

maximum :: Ord a => Steps f a -> a #

minimum :: Ord a => Steps f a -> a #

sum :: Num a => Steps f a -> a #

product :: Num a => Steps f a -> a #

Traversable f => Traversable (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Steps f a -> f0 (Steps f b) #

sequenceA :: Applicative f0 => Steps f (f0 a) -> f0 (Steps f a) #

mapM :: Monad m => (a -> m b) -> Steps f a -> m (Steps f b) #

sequence :: Monad m => Steps f (m a) -> m (Steps f a) #

Eq1 f => Eq1 (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

Ord1 f => Ord1 (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

Read1 f => Read1 (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Steps f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Steps f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Steps f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Steps f a] #

Show1 f => Show1 (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Steps f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Steps f a] -> ShowS #

Foldable1 f => Foldable1 (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fold1 :: Semigroup m => Steps f m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Steps f a -> m #

toNonEmpty :: Steps f a -> NonEmpty a #

Pointed f => Pointed (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

point :: a -> Steps f a #

Traversable1 f => Traversable1 (Steps f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

traverse1 :: Apply f0 => (a -> f0 b) -> Steps f a -> f0 (Steps f b) #

sequence1 :: Apply f0 => Steps f (f0 b) -> f0 (Steps f b) #

Functor f => Alt (Steps f) Source #

Left-biased untion

Instance details

Defined in Control.Applicative.Step

Methods

(<!>) :: Steps f a -> Steps f a -> Steps f a #

some :: Applicative (Steps f) => Steps f a -> Steps f [a] #

many :: Applicative (Steps f) => Steps f a -> Steps f [a] #

Eq (f a) => Eq (Steps f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

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

(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (Steps f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Steps f a -> c (Steps f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Steps f a) #

toConstr :: Steps f a -> Constr #

dataTypeOf :: Steps f a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Steps f a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Steps f a)) #

gmapT :: (forall b. Data b => b -> b) -> Steps f a -> Steps f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Steps f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Steps f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Steps f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Steps f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Steps f a -> m (Steps f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Steps f a -> m (Steps f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Steps f a -> m (Steps f a) #

Ord (f a) => Ord (Steps f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

compare :: Steps f a -> Steps f a -> Ordering #

(<) :: Steps f a -> Steps f a -> Bool #

(<=) :: Steps f a -> Steps f a -> Bool #

(>) :: Steps f a -> Steps f a -> Bool #

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

max :: Steps f a -> Steps f a -> Steps f a #

min :: Steps f a -> Steps f a -> Steps f a #

Read (f a) => Read (Steps f a) Source # 
Instance details

Defined in Control.Applicative.Step

Show (f a) => Show (Steps f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

showsPrec :: Int -> Steps f a -> ShowS #

show :: Steps f a -> String #

showList :: [Steps f a] -> ShowS #

Generic (Steps f a) Source # 
Instance details

Defined in Control.Applicative.Step

Associated Types

type Rep (Steps f a) :: Type -> Type #

Methods

from :: Steps f a -> Rep (Steps f a) x #

to :: Rep (Steps f a) x -> Steps f a #

Semigroup (Steps f a) Source #

Appends the items back-to-back, shifting all of the items in the second map. Matches the behavior as the fixed-point of These1.

Instance details

Defined in Control.Applicative.Step

Methods

(<>) :: Steps f a -> Steps f a -> Steps f a #

sconcat :: NonEmpty (Steps f a) -> Steps f a #

stimes :: Integral b => b -> Steps f a -> Steps f a #

type Rep (Steps f a) Source # 
Instance details

Defined in Control.Applicative.Step

type Rep (Steps f a) = D1 (MetaData "Steps" "Control.Applicative.Step" "functor-combinators-0.2.0.0-inplace" True) (C1 (MetaCons "Steps" PrefixI True) (S1 (MetaSel (Just "getSteps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NEMap Natural (f a)))))

data Flagged f a Source #

An f a, along with a Bool flag

Flagged f a ~ (Bool, f a)
Flagged f   ~ ((,) Bool) :.: f       -- functor composition

Creation with inject or pure uses False as the boolean.

You can think of it as an f a that is "flagged" with a boolean value, and that value can indicuate whether or not it is "pure" (made with inject or pure) as False, or "impure" (made from some other source) as True. However, False may be always created directly, of course, using the constructor.

You can think of it like a Step that is either 0 or 1, as well.

interpreting it requires no constraint on the target context.

This type is equivalent (along with its instances) to:

Constructors

Flagged 

Fields

Instances
HFunctor (Flagged :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hmap :: (f ~> g) -> Flagged f ~> Flagged g Source #

HBind (Flagged :: (k -> Type) -> k -> Type) Source #

Equivalent to instance for EnvT Any and HLift IdentityT.

Instance details

Defined in Data.HFunctor

Inject (Flagged :: (k -> Type) -> k -> Type) Source #

Injects with False.

Equivalent to instance for EnvT Any and HLift IdentityT.

Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> Flagged f Source #

Interpret (Flagged :: (k -> Type) -> k -> Type) (f :: k -> Type) Source #

Equivalent to instance for EnvT Any and HLift IdentityT.

Instance details

Defined in Data.HFunctor.Interpret

Methods

retract :: Flagged f ~> f Source #

interpret :: (g ~> f) -> Flagged g ~> f Source #

Functor f => Functor (Flagged f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

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

Applicative f => Applicative (Flagged f) Source #

Uses False for pure, and || for <*>.

Instance details

Defined in Control.Applicative.Step

Methods

pure :: a -> Flagged f a #

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

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

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

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

Foldable f => Foldable (Flagged f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fold :: Monoid m => Flagged f m -> m #

foldMap :: Monoid m => (a -> m) -> Flagged f a -> m #

foldr :: (a -> b -> b) -> b -> Flagged f a -> b #

foldr' :: (a -> b -> b) -> b -> Flagged f a -> b #

foldl :: (b -> a -> b) -> b -> Flagged f a -> b #

foldl' :: (b -> a -> b) -> b -> Flagged f a -> b #

foldr1 :: (a -> a -> a) -> Flagged f a -> a #

foldl1 :: (a -> a -> a) -> Flagged f a -> a #

toList :: Flagged f a -> [a] #

null :: Flagged f a -> Bool #

length :: Flagged f a -> Int #

elem :: Eq a => a -> Flagged f a -> Bool #

maximum :: Ord a => Flagged f a -> a #

minimum :: Ord a => Flagged f a -> a #

sum :: Num a => Flagged f a -> a #

product :: Num a => Flagged f a -> a #

Traversable f => Traversable (Flagged f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Flagged f a -> f0 (Flagged f b) #

sequenceA :: Applicative f0 => Flagged f (f0 a) -> f0 (Flagged f a) #

mapM :: Monad m => (a -> m b) -> Flagged f a -> m (Flagged f b) #

sequence :: Monad m => Flagged f (m a) -> m (Flagged f a) #

Eq1 f => Eq1 (Flagged f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

Ord1 f => Ord1 (Flagged f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

Read1 f => Read1 (Flagged f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Flagged f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Flagged f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Flagged f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Flagged f a] #

Show1 f => Show1 (Flagged f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Flagged f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Flagged f a] -> ShowS #

Foldable1 f => Foldable1 (Flagged f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fold1 :: Semigroup m => Flagged f m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Flagged f a -> m #

toNonEmpty :: Flagged f a -> NonEmpty a #

Pointed f => Pointed (Flagged f) Source #

Uses False for point.

Instance details

Defined in Control.Applicative.Step

Methods

point :: a -> Flagged f a #

Traversable1 f => Traversable1 (Flagged f) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

traverse1 :: Apply f0 => (a -> f0 b) -> Flagged f a -> f0 (Flagged f b) #

sequence1 :: Apply f0 => Flagged f (f0 b) -> f0 (Flagged f b) #

Eq (f a) => Eq (Flagged f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

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

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

(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (Flagged f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Flagged f a -> c (Flagged f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Flagged f a) #

toConstr :: Flagged f a -> Constr #

dataTypeOf :: Flagged f a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Flagged f a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Flagged f a)) #

gmapT :: (forall b. Data b => b -> b) -> Flagged f a -> Flagged f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Flagged f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Flagged f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Flagged f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Flagged f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Flagged f a -> m (Flagged f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Flagged f a -> m (Flagged f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Flagged f a -> m (Flagged f a) #

Ord (f a) => Ord (Flagged f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

compare :: Flagged f a -> Flagged f a -> Ordering #

(<) :: Flagged f a -> Flagged f a -> Bool #

(<=) :: Flagged f a -> Flagged f a -> Bool #

(>) :: Flagged f a -> Flagged f a -> Bool #

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

max :: Flagged f a -> Flagged f a -> Flagged f a #

min :: Flagged f a -> Flagged f a -> Flagged f a #

Read (f a) => Read (Flagged f a) Source # 
Instance details

Defined in Control.Applicative.Step

Show (f a) => Show (Flagged f a) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

showsPrec :: Int -> Flagged f a -> ShowS #

show :: Flagged f a -> String #

showList :: [Flagged f a] -> ShowS #

Generic (Flagged f a) Source # 
Instance details

Defined in Control.Applicative.Step

Associated Types

type Rep (Flagged f a) :: Type -> Type #

Methods

from :: Flagged f a -> Rep (Flagged f a) x #

to :: Rep (Flagged f a) x -> Flagged f a #

type Rep (Flagged f a) Source # 
Instance details

Defined in Control.Applicative.Step

type Rep (Flagged f a) = D1 (MetaData "Flagged" "Control.Applicative.Step" "functor-combinators-0.2.0.0-inplace" False) (C1 (MetaCons "Flagged" PrefixI True) (S1 (MetaSel (Just "flaggedFlag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "flaggedVal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))

Steppers

stepUp :: (f :+: Step f) ~> Step f Source #

Unshift an item into a Step. Because a Step f is f :+: f :+: f :+: f :+: ... forever, this basically conses an additional possibility of f to the beginning of it all.

You can think of it as reassociating

f :+: ( f :+: f :+: f :+: ...)

into

f :+: f :+: f :+: f :+: ...
stepUp (L1 "hello")
-- Step 0 "hello"
stepUp (R1 (Step 1 "hello"))
-- Step 2 "hello"

Forms an isomorphism with stepDown (see stepping).

stepDown :: Step f ~> (f :+: Step f) Source #

Pop off the first item in a Step. Because a Step f is f :+: f :+: f :+: ... forever, this matches on the first branch.

You can think of it as reassociating

f :+: f :+: f :+: f :+: ...

into

f :+: ( f :+: f :+: f :+: ...)
stepDown (Step 2 "hello")
-- R1 (Step 1 "hello")
stepDown (Step 0 "hello")
-- L1 "hello"

Forms an isomorphism with stepUp (see stepping).

stepping :: Step f <~> (f :+: Step f) Source #

"Uncons and cons" an f branch before a Step. This is basically a witness that stepDown and stepUp form an isomorphism.

stepsUp :: These1 f (Steps f) ~> Steps f Source #

Unshift an item into a Steps. Because a Steps f is f These1 f These1 f These1 f These1 ... forever, this basically conses an additional possibility of f to the beginning of it all.

You can think of it as reassociating

f These1 ( f These1 f These1 f These1 ...)

into

f These1 f These1 f These1 f These1 ...

If you give:

  • This1, then it returns a singleton Steps with one item at index 0
  • That1, then it shifts every item in the given Steps up one index.
  • These1, then it shifts every item in the given Steps up one index, and adds the given item (the f) at index zero.

Forms an isomorphism with stepDown (see stepping).

stepsDown :: Steps f ~> These1 f (Steps f) Source #

Pop off the first item in a Steps. Because a Steps f is f These1 f These1 f These1 ... forever, this matches on the first branch.

You can think of it as reassociating

f These1 f These1 f These1 f These1 ...

into

f These1 ( f These1 f These1 f These1 ...)

It returns:

  • This1 if the first item is the only item in the Steps
  • That1 if the first item in the Steps is empty, but there are more items left. The extra items are all shfited down.
  • These1 if the first item in the Steps exists, and there are also more items left. The extra items are all shifted down.

Forms an isomorphism with stepsUp (see steppings).

steppings :: Steps f <~> These1 f (Steps f) Source #

"Uncons and cons" an f branch before a Steps. This is basically a witness that stepsDown and stepsUp form an isomorphism.

Void

absurd1 :: V1 a -> f a Source #

We have a natural transformation between V1 and any other functor f with no constraints.

data Void2 a b Source #

Void2 a b is uninhabited for all a and b.

Instances
HFunctor (Void2 :: (k1 -> Type) -> k2 -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hmap :: (f ~> g) -> Void2 f ~> Void2 g Source #

Functor (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fmap :: (a0 -> b) -> Void2 a a0 -> Void2 a b #

(<$) :: a0 -> Void2 a b -> Void2 a a0 #

Foldable (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fold :: Monoid m => Void2 a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Void2 a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Void2 a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Void2 a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Void2 a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Void2 a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Void2 a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Void2 a a0 -> a0 #

toList :: Void2 a a0 -> [a0] #

null :: Void2 a a0 -> Bool #

length :: Void2 a a0 -> Int #

elem :: Eq a0 => a0 -> Void2 a a0 -> Bool #

maximum :: Ord a0 => Void2 a a0 -> a0 #

minimum :: Ord a0 => Void2 a a0 -> a0 #

sum :: Num a0 => Void2 a a0 -> a0 #

product :: Num a0 => Void2 a a0 -> a0 #

Traversable (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

traverse :: Applicative f => (a0 -> f b) -> Void2 a a0 -> f (Void2 a b) #

sequenceA :: Applicative f => Void2 a (f a0) -> f (Void2 a a0) #

mapM :: Monad m => (a0 -> m b) -> Void2 a a0 -> m (Void2 a b) #

sequence :: Monad m => Void2 a (m a0) -> m (Void2 a a0) #

Eq1 (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftEq :: (a0 -> b -> Bool) -> Void2 a a0 -> Void2 a b -> Bool #

Ord1 (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftCompare :: (a0 -> b -> Ordering) -> Void2 a a0 -> Void2 a b -> Ordering #

Read1 (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Void2 a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Void2 a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Void2 a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Void2 a a0] #

Show1 (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Void2 a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Void2 a a0] -> ShowS #

Apply (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(<.>) :: Void2 a (a0 -> b) -> Void2 a a0 -> Void2 a b #

(.>) :: Void2 a a0 -> Void2 a b -> Void2 a b #

(<.) :: Void2 a a0 -> Void2 a b -> Void2 a a0 #

liftF2 :: (a0 -> b -> c) -> Void2 a a0 -> Void2 a b -> Void2 a c #

Alt (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(<!>) :: Void2 a a0 -> Void2 a a0 -> Void2 a a0 #

some :: Applicative (Void2 a) => Void2 a a0 -> Void2 a [a0] #

many :: Applicative (Void2 a) => Void2 a a0 -> Void2 a [a0] #

Bind (Void2 a :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(>>-) :: Void2 a a0 -> (a0 -> Void2 a b) -> Void2 a b #

join :: Void2 a (Void2 a a0) -> Void2 a a0 #

Eq (Void2 a b) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(==) :: Void2 a b -> Void2 a b -> Bool #

(/=) :: Void2 a b -> Void2 a b -> Bool #

(Typeable a, Typeable b, Typeable k1, Typeable k2) => Data (Void2 a b) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Void2 a b -> c (Void2 a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Void2 a b) #

toConstr :: Void2 a b -> Constr #

dataTypeOf :: Void2 a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Void2 a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Void2 a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Void2 a b -> Void2 a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Void2 a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Void2 a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Void2 a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Void2 a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Void2 a b -> m (Void2 a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Void2 a b -> m (Void2 a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Void2 a b -> m (Void2 a b) #

Ord (Void2 a b) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

compare :: Void2 a b -> Void2 a b -> Ordering #

(<) :: Void2 a b -> Void2 a b -> Bool #

(<=) :: Void2 a b -> Void2 a b -> Bool #

(>) :: Void2 a b -> Void2 a b -> Bool #

(>=) :: Void2 a b -> Void2 a b -> Bool #

max :: Void2 a b -> Void2 a b -> Void2 a b #

min :: Void2 a b -> Void2 a b -> Void2 a b #

Read (Void2 a b) Source # 
Instance details

Defined in Control.Applicative.Step

Show (Void2 a b) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

showsPrec :: Int -> Void2 a b -> ShowS #

show :: Void2 a b -> String #

showList :: [Void2 a b] -> ShowS #

Generic (Void2 a b) Source # 
Instance details

Defined in Control.Applicative.Step

Associated Types

type Rep (Void2 a b) :: Type -> Type #

Methods

from :: Void2 a b -> Rep (Void2 a b) x #

to :: Rep (Void2 a b) x -> Void2 a b #

Semigroup (Void2 a b) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(<>) :: Void2 a b -> Void2 a b -> Void2 a b #

sconcat :: NonEmpty (Void2 a b) -> Void2 a b #

stimes :: Integral b0 => b0 -> Void2 a b -> Void2 a b #

type Rep (Void2 a b) Source # 
Instance details

Defined in Control.Applicative.Step

type Rep (Void2 a b) = D1 (MetaData "Void2" "Control.Applicative.Step" "functor-combinators-0.2.0.0-inplace" False) (V1 :: Type -> Type)

absurd2 :: Void2 f a -> t f a Source #

If you treat a Void2 f a as a functor combinator, then absurd2 lets you convert from a Void2 f a into a t f a for any functor combinator t.

data Void3 a b c Source #

Void3 a b is uninhabited for all a and b.

Instances
HFunctor (Void3 f :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hmap :: (f0 ~> g) -> Void3 f f0 ~> Void3 f g Source #

HBifunctor (Void3 :: (k -> Type) -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

hleft :: (f ~> j) -> Void3 f g ~> Void3 j g Source #

hright :: (g ~> l) -> Void3 f g ~> Void3 f l Source #

hbimap :: (f ~> j) -> (g ~> l) -> Void3 f g ~> Void3 j l Source #

Associative (Void3 :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

type NonEmptyBy Void3 :: (Type -> Type) -> Type -> Type Source #

SemigroupIn (Void3 :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source #

All functors are semigroups in the semigroupoidal category on Void3.

Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: Void3 f f ~> f Source #

binterpret :: (g ~> f) -> (h ~> f) -> Void3 g h ~> f Source #

Functor (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fmap :: (a0 -> b0) -> Void3 a b a0 -> Void3 a b b0 #

(<$) :: a0 -> Void3 a b b0 -> Void3 a b a0 #

Foldable (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

fold :: Monoid m => Void3 a b m -> m #

foldMap :: Monoid m => (a0 -> m) -> Void3 a b a0 -> m #

foldr :: (a0 -> b0 -> b0) -> b0 -> Void3 a b a0 -> b0 #

foldr' :: (a0 -> b0 -> b0) -> b0 -> Void3 a b a0 -> b0 #

foldl :: (b0 -> a0 -> b0) -> b0 -> Void3 a b a0 -> b0 #

foldl' :: (b0 -> a0 -> b0) -> b0 -> Void3 a b a0 -> b0 #

foldr1 :: (a0 -> a0 -> a0) -> Void3 a b a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Void3 a b a0 -> a0 #

toList :: Void3 a b a0 -> [a0] #

null :: Void3 a b a0 -> Bool #

length :: Void3 a b a0 -> Int #

elem :: Eq a0 => a0 -> Void3 a b a0 -> Bool #

maximum :: Ord a0 => Void3 a b a0 -> a0 #

minimum :: Ord a0 => Void3 a b a0 -> a0 #

sum :: Num a0 => Void3 a b a0 -> a0 #

product :: Num a0 => Void3 a b a0 -> a0 #

Traversable (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

traverse :: Applicative f => (a0 -> f b0) -> Void3 a b a0 -> f (Void3 a b b0) #

sequenceA :: Applicative f => Void3 a b (f a0) -> f (Void3 a b a0) #

mapM :: Monad m => (a0 -> m b0) -> Void3 a b a0 -> m (Void3 a b b0) #

sequence :: Monad m => Void3 a b (m a0) -> m (Void3 a b a0) #

Eq1 (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftEq :: (a0 -> b0 -> Bool) -> Void3 a b a0 -> Void3 a b b0 -> Bool #

Ord1 (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftCompare :: (a0 -> b0 -> Ordering) -> Void3 a b a0 -> Void3 a b b0 -> Ordering #

Read1 (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Void3 a b a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Void3 a b a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Void3 a b a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Void3 a b a0] #

Show1 (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Void3 a b a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Void3 a b a0] -> ShowS #

Apply (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(<.>) :: Void3 a b (a0 -> b0) -> Void3 a b a0 -> Void3 a b b0 #

(.>) :: Void3 a b a0 -> Void3 a b b0 -> Void3 a b b0 #

(<.) :: Void3 a b a0 -> Void3 a b b0 -> Void3 a b a0 #

liftF2 :: (a0 -> b0 -> c) -> Void3 a b a0 -> Void3 a b b0 -> Void3 a b c #

Alt (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(<!>) :: Void3 a b a0 -> Void3 a b a0 -> Void3 a b a0 #

some :: Applicative (Void3 a b) => Void3 a b a0 -> Void3 a b [a0] #

many :: Applicative (Void3 a b) => Void3 a b a0 -> Void3 a b [a0] #

Bind (Void3 a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(>>-) :: Void3 a b a0 -> (a0 -> Void3 a b b0) -> Void3 a b b0 #

join :: Void3 a b (Void3 a b a0) -> Void3 a b a0 #

Eq (Void3 a b c) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(==) :: Void3 a b c -> Void3 a b c -> Bool #

(/=) :: Void3 a b c -> Void3 a b c -> Bool #

(Typeable a, Typeable b, Typeable c, Typeable k1, Typeable k2, Typeable k3) => Data (Void3 a b c) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

gfoldl :: (forall d b0. Data d => c0 (d -> b0) -> d -> c0 b0) -> (forall g. g -> c0 g) -> Void3 a b c -> c0 (Void3 a b c) #

gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (Void3 a b c) #

toConstr :: Void3 a b c -> Constr #

dataTypeOf :: Void3 a b c -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (Void3 a b c)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (Void3 a b c)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Void3 a b c -> Void3 a b c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Void3 a b c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Void3 a b c -> r #

gmapQ :: (forall d. Data d => d -> u) -> Void3 a b c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Void3 a b c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Void3 a b c -> m (Void3 a b c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Void3 a b c -> m (Void3 a b c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Void3 a b c -> m (Void3 a b c) #

Ord (Void3 a b c) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

compare :: Void3 a b c -> Void3 a b c -> Ordering #

(<) :: Void3 a b c -> Void3 a b c -> Bool #

(<=) :: Void3 a b c -> Void3 a b c -> Bool #

(>) :: Void3 a b c -> Void3 a b c -> Bool #

(>=) :: Void3 a b c -> Void3 a b c -> Bool #

max :: Void3 a b c -> Void3 a b c -> Void3 a b c #

min :: Void3 a b c -> Void3 a b c -> Void3 a b c #

Read (Void3 a b c) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

readsPrec :: Int -> ReadS (Void3 a b c) #

readList :: ReadS [Void3 a b c] #

readPrec :: ReadPrec (Void3 a b c) #

readListPrec :: ReadPrec [Void3 a b c] #

Show (Void3 a b c) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

showsPrec :: Int -> Void3 a b c -> ShowS #

show :: Void3 a b c -> String #

showList :: [Void3 a b c] -> ShowS #

Generic (Void3 a b c) Source # 
Instance details

Defined in Control.Applicative.Step

Associated Types

type Rep (Void3 a b c) :: Type -> Type #

Methods

from :: Void3 a b c -> Rep (Void3 a b c) x #

to :: Rep (Void3 a b c) x -> Void3 a b c #

Semigroup (Void3 a b c) Source # 
Instance details

Defined in Control.Applicative.Step

Methods

(<>) :: Void3 a b c -> Void3 a b c -> Void3 a b c #

sconcat :: NonEmpty (Void3 a b c) -> Void3 a b c #

stimes :: Integral b0 => b0 -> Void3 a b c -> Void3 a b c #

type NonEmptyBy (Void3 :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

type NonEmptyBy (Void3 :: (Type -> Type) -> (Type -> Type) -> Type -> Type) = (IdentityT :: (Type -> Type) -> Type -> Type)
type Rep (Void3 a b c) Source # 
Instance details

Defined in Control.Applicative.Step

type Rep (Void3 a b c) = D1 (MetaData "Void3" "Control.Applicative.Step" "functor-combinators-0.2.0.0-inplace" False) (V1 :: Type -> Type)

absurd3 :: Void3 f g a -> t f g a Source #

If you treat a Void3 f a as a binary functor combinator, then absurd3 lets you convert from a Void3 f a into a t f a for any functor combinator t.