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

Copyright(c) Justin Le 2019
LicenseBSD3
Maintainer[email protected]
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Applicative.ListF

Contents

Description

This module provides functor combinators that are wrappers over lists or maybes of f as, especially for their Interpret instances.

Each one transforms a functor into some product of itself. For example, NonEmptyF f represents f :*: f, or f :*: f :*: f, or f :*: f :*: f :*: f, etc.

Synopsis

ListF

newtype ListF f a Source #

A list of f as. Can be used to describe a product of many different values of type f a.

This is the Free Plus.

Constructors

ListF 

Fields

Instances
Interpret ListF Source #

A free Plus

Instance details

Defined in Data.HFunctor.Interpret

Associated Types

type C ListF :: (Type -> Type) -> Constraint Source #

Methods

retract :: C ListF f => ListF f ~> f Source #

interpret :: C ListF g => (f ~> g) -> ListF f ~> g Source #

FreeOf Plus ListF Source # 
Instance details

Defined in Data.HFunctor.Final

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

Defined in Control.Applicative.ListF

Methods

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

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

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

Defined in Control.Applicative.ListF

Methods

pure :: a -> ListF f a #

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

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

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

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

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

null :: ListF f a -> Bool #

length :: ListF f a -> Int #

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

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

Applicative f => Alternative (ListF f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

empty :: ListF f a #

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

Defined in Control.Applicative.ListF

Methods

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

Apply f => Apply (ListF f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

(<.>) :: ListF f (a -> b) -> ListF f a -> ListF f b #

(.>) :: ListF f a -> ListF f b -> ListF f b #

(<.) :: ListF f a -> ListF f b -> ListF f a #

liftF2 :: (a -> b -> c) -> ListF f a -> ListF f b -> ListF f c #

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

Defined in Control.Applicative.ListF

Methods

point :: a -> ListF f a #

Functor f => Plus (ListF f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

zero :: ListF f a #

Functor f => Alt (ListF f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

HBind ListF Source # 
Instance details

Defined in Data.HFunctor

Methods

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

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

Inject ListF Source # 
Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> ListF f Source #

HFunctor ListF Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

toConstr :: ListF f a -> Constr #

dataTypeOf :: ListF f a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

max :: ListF f a -> ListF f a -> ListF f a #

min :: ListF f a -> ListF f a -> ListF f a #

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

Defined in Control.Applicative.ListF

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

Defined in Control.Applicative.ListF

Methods

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

show :: ListF f a -> String #

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

Generic (ListF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Associated Types

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

Methods

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

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

Semigroup (ListF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

Monoid (ListF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

mempty :: ListF f a #

mappend :: ListF f a -> ListF f a -> ListF f a #

mconcat :: [ListF f a] -> ListF f a #

type C ListF Source # 
Instance details

Defined in Data.HFunctor.Interpret

type C ListF = Plus
type Rep (ListF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

type Rep (ListF f a) = D1 (MetaData "ListF" "Control.Applicative.ListF" "functor-combinators-0.1.1.0-inplace" True) (C1 (MetaCons "ListF" PrefixI True) (S1 (MetaSel (Just "runListF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [f a])))

mapListF :: ([f a] -> [g b]) -> ListF f a -> ListF g b Source #

Map a function over the inside of a ListF.

NonEmptyF

newtype NonEmptyF f a Source #

A non-empty list of f as. Can be used to describe a product between many different possible values of type f a.

Essentially:

NonEmptyF f
    ~ f                          -- one f
  :+: (f :*: f)              -- two f's
  :+: (f :*: f :*: f)            -- three f's
  :+: (f :*: f :*: f :*: f)      -- four f's
  :+: ...                        -- etc.

This is the Free Plus.

Constructors

NonEmptyF 

Fields

Bundled Patterns

pattern ProdNonEmpty :: (f :*: ListF f) a -> NonEmptyF f a

Treat a NonEmptyF f as a product between an f and a ListF f.

nonEmptyProd is the record accessor.

Instances
Interpret NonEmptyF Source #

A free Alt

Instance details

Defined in Data.HFunctor.Interpret

Associated Types

type C NonEmptyF :: (Type -> Type) -> Constraint Source #

Methods

retract :: C NonEmptyF f => NonEmptyF f ~> f Source #

interpret :: C NonEmptyF g => (f ~> g) -> NonEmptyF f ~> g Source #

FreeOf Alt NonEmptyF Source # 
Instance details

Defined in Data.HFunctor.Final

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

Defined in Control.Applicative.ListF

Methods

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

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

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

Defined in Control.Applicative.ListF

Methods

pure :: a -> NonEmptyF f a #

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

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

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

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

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

null :: NonEmptyF f a -> Bool #

length :: NonEmptyF f a -> Int #

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

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

Defined in Control.Applicative.ListF

Methods

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

Defined in Control.Applicative.ListF

Methods

point :: a -> NonEmptyF f a #

Functor f => Alt (NonEmptyF f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

HBind NonEmptyF Source # 
Instance details

Defined in Data.HFunctor

Inject NonEmptyF Source # 
Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> NonEmptyF f Source #

HFunctor NonEmptyF Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

toConstr :: NonEmptyF f a -> Constr #

dataTypeOf :: NonEmptyF f a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

max :: NonEmptyF f a -> NonEmptyF f a -> NonEmptyF f a #

min :: NonEmptyF f a -> NonEmptyF f a -> NonEmptyF f a #

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

Defined in Control.Applicative.ListF

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

Defined in Control.Applicative.ListF

Methods

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

show :: NonEmptyF f a -> String #

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

Generic (NonEmptyF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Associated Types

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

Methods

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

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

Semigroup (NonEmptyF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

type C NonEmptyF Source # 
Instance details

Defined in Data.HFunctor.Interpret

type C NonEmptyF = Alt
type Rep (NonEmptyF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

type Rep (NonEmptyF f a) = D1 (MetaData "NonEmptyF" "Control.Applicative.ListF" "functor-combinators-0.1.1.0-inplace" True) (C1 (MetaCons "NonEmptyF" PrefixI True) (S1 (MetaSel (Just "runNonEmptyF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (f a)))))

mapNonEmptyF :: (NonEmpty (f a) -> NonEmpty (g b)) -> NonEmptyF f a -> NonEmptyF g b Source #

Map a function over the inside of a NonEmptyF.

toListF :: NonEmptyF f ~> ListF f Source #

Convert a NonEmptyF into a ListF with at least one item.

fromListF :: ListF f ~> (Proxy :+: NonEmptyF f) Source #

Convert a ListF either a NonEmptyF, or a Proxy in the case that the list was empty.

MaybeF

newtype MaybeF f a Source #

A maybe f a.

Can be useful for describing a "an f a that may or may not be there".

This is the free structure for a "fail"-like typeclass that would only have zero :: f a.

Constructors

MaybeF 

Fields

Instances
Interpret MaybeF Source #

Technically, C is over-constrained: we only need zero :: f a, but we don't really have that typeclass in any standard hierarchies. We use Plus here instead, but we never use <!>. This would only go wrong in situations where your type supports zero but not <!>, like instances of MonadFail without MonadPlus.

Instance details

Defined in Data.HFunctor.Interpret

Associated Types

type C MaybeF :: (Type -> Type) -> Constraint Source #

Methods

retract :: C MaybeF f => MaybeF f ~> f Source #

interpret :: C MaybeF g => (f ~> g) -> MaybeF f ~> g Source #

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

Defined in Control.Applicative.ListF

Methods

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

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

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

Defined in Control.Applicative.ListF

Methods

pure :: a -> MaybeF f a #

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

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

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

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

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

null :: MaybeF f a -> Bool #

length :: MaybeF f a -> Int #

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

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

Applicative f => Alternative (MaybeF f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

empty :: MaybeF f a #

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

Defined in Control.Applicative.ListF

Methods

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

Defined in Control.Applicative.ListF

Methods

point :: a -> MaybeF f a #

Functor f => Plus (MaybeF f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

zero :: MaybeF f a #

Functor f => Alt (MaybeF f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

HBind MaybeF Source # 
Instance details

Defined in Data.HFunctor

Methods

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

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

Inject MaybeF Source # 
Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> MaybeF f Source #

HFunctor MaybeF Source # 
Instance details

Defined in Data.HFunctor.Internal

Methods

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

toConstr :: MaybeF f a -> Constr #

dataTypeOf :: MaybeF f a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Control.Applicative.ListF

Methods

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

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

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

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

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

max :: MaybeF f a -> MaybeF f a -> MaybeF f a #

min :: MaybeF f a -> MaybeF f a -> MaybeF f a #

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

Defined in Control.Applicative.ListF

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

Defined in Control.Applicative.ListF

Methods

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

show :: MaybeF f a -> String #

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

Generic (MaybeF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Associated Types

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

Methods

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

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

Semigroup (MaybeF f a) Source #

Picks the first Just.

Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

Monoid (MaybeF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

mempty :: MaybeF f a #

mappend :: MaybeF f a -> MaybeF f a -> MaybeF f a #

mconcat :: [MaybeF f a] -> MaybeF f a #

type C MaybeF Source # 
Instance details

Defined in Data.HFunctor.Interpret

type C MaybeF = Plus
type Rep (MaybeF f a) Source # 
Instance details

Defined in Control.Applicative.ListF

type Rep (MaybeF f a) = D1 (MetaData "MaybeF" "Control.Applicative.ListF" "functor-combinators-0.1.1.0-inplace" True) (C1 (MetaCons "MaybeF" PrefixI True) (S1 (MetaSel (Just "runMaybeF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (f a)))))

mapMaybeF :: (Maybe (f a) -> Maybe (g b)) -> MaybeF f a -> MaybeF g b Source #

Map a function over the inside of a MaybeF.

listToMaybeF :: ListF f ~> MaybeF f Source #

Convert a ListF into a MaybeF containing the first f a in the list, if it exists.

maybeToListF :: MaybeF f ~> ListF f Source #

Convert a MaybeF into a ListF with zero or one items.

MapF

newtype MapF k f a Source #

A map of f as, indexed by keys of type k. It can be useful for represeting a product of many different values of type f a, each "at" a different k location.

Can be considered a combination of EnvT and ListF, in a way --- a MapF k f a is like a ListF (EnvT k f) a with unique (and ordered) keys.

One use case might be to extend a schema with many "options", indexed by some string.

For example, if you had a command line argument parser for a single command

data Command a

Then you can represent a command line argument parser for multiple named commands with

type Commands = MapF String Command

See NEMapF for a non-empty variant, if you want to enforce that your bag has at least one f a.

Constructors

MapF 

Fields

Instances
Monoid k => Interpret (MapF k) Source # 
Instance details

Defined in Data.HFunctor.Interpret

Associated Types

type C (MapF k) :: (Type -> Type) -> Constraint Source #

Methods

retract :: C (MapF k) f => MapF k f ~> f Source #

interpret :: C (MapF k) g => (f ~> g) -> MapF k f ~> g Source #

Monoid k => Inject (MapF k :: (Type -> Type) -> Type -> Type) Source #

Injects into a singleton map at mempty.

Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> MapF k f Source #

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

Defined in Data.HFunctor.Internal

Methods

hmap :: (f ~> g) -> MapF k f ~> MapF k g Source #

Functor f => Functor (MapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

fmap :: (a -> b) -> MapF k f a -> MapF k f b #

(<$) :: a -> MapF k f b -> MapF k f a #

Foldable f => Foldable (MapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

fold :: Monoid m => MapF k f m -> m #

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

foldr :: (a -> b -> b) -> b -> MapF k f a -> b #

foldr' :: (a -> b -> b) -> b -> MapF k f a -> b #

foldl :: (b -> a -> b) -> b -> MapF k f a -> b #

foldl' :: (b -> a -> b) -> b -> MapF k f a -> b #

foldr1 :: (a -> a -> a) -> MapF k f a -> a #

foldl1 :: (a -> a -> a) -> MapF k f a -> a #

toList :: MapF k f a -> [a] #

null :: MapF k f a -> Bool #

length :: MapF k f a -> Int #

elem :: Eq a => a -> MapF k f a -> Bool #

maximum :: Ord a => MapF k f a -> a #

minimum :: Ord a => MapF k f a -> a #

sum :: Num a => MapF k f a -> a #

product :: Num a => MapF k f a -> a #

Traversable f => Traversable (MapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

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

(Eq k, Eq1 f) => Eq1 (MapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

liftEq :: (a -> b -> Bool) -> MapF k f a -> MapF k f b -> Bool #

(Ord k, Ord1 f) => Ord1 (MapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

liftCompare :: (a -> b -> Ordering) -> MapF k f a -> MapF k f b -> Ordering #

(Ord k, Read k, Read1 f) => Read1 (MapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [MapF k f a] #

(Show k, Show1 f) => Show1 (MapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

(Monoid k, Pointed f) => Pointed (MapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

point :: a -> MapF k f a #

(Functor f, Ord k) => Plus (MapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

zero :: MapF k f a #

(Functor f, Ord k) => Alt (MapF k f) Source #

Left-biased union

Instance details

Defined in Control.Applicative.ListF

Methods

(<!>) :: MapF k f a -> MapF k f a -> MapF k f a #

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

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

(Eq k, Eq (f a)) => Eq (MapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

(==) :: MapF k f a -> MapF k f a -> Bool #

(/=) :: MapF k f a -> MapF k f a -> Bool #

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

Defined in Control.Applicative.ListF

Methods

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

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

toConstr :: MapF k f a -> Constr #

dataTypeOf :: MapF k f a -> DataType #

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

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

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

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

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

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

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

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

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

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

(Ord k, Ord (f a)) => Ord (MapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

compare :: MapF k f a -> MapF k f a -> Ordering #

(<) :: MapF k f a -> MapF k f a -> Bool #

(<=) :: MapF k f a -> MapF k f a -> Bool #

(>) :: MapF k f a -> MapF k f a -> Bool #

(>=) :: MapF k f a -> MapF k f a -> Bool #

max :: MapF k f a -> MapF k f a -> MapF k f a #

min :: MapF k f a -> MapF k f a -> MapF k f a #

(Ord k, Read k, Read (f a)) => Read (MapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

readsPrec :: Int -> ReadS (MapF k f a) #

readList :: ReadS [MapF k f a] #

readPrec :: ReadPrec (MapF k f a) #

readListPrec :: ReadPrec [MapF k f a] #

(Show k, Show (f a)) => Show (MapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

showsPrec :: Int -> MapF k f a -> ShowS #

show :: MapF k f a -> String #

showList :: [MapF k f a] -> ShowS #

Generic (MapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Associated Types

type Rep (MapF k f a) :: Type -> Type #

Methods

from :: MapF k f a -> Rep (MapF k f a) x #

to :: Rep (MapF k f a) x -> MapF k f a #

(Ord k, Alt f) => Semigroup (MapF k f a) Source #

A union, combining matching keys with <!>.

Instance details

Defined in Control.Applicative.ListF

Methods

(<>) :: MapF k f a -> MapF k f a -> MapF k f a #

sconcat :: NonEmpty (MapF k f a) -> MapF k f a #

stimes :: Integral b => b -> MapF k f a -> MapF k f a #

(Ord k, Alt f) => Monoid (MapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

mempty :: MapF k f a #

mappend :: MapF k f a -> MapF k f a -> MapF k f a #

mconcat :: [MapF k f a] -> MapF k f a #

type C (MapF k) Source # 
Instance details

Defined in Data.HFunctor.Interpret

type C (MapF k) = Plus
type Rep (MapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

type Rep (MapF k f a) = D1 (MetaData "MapF" "Control.Applicative.ListF" "functor-combinators-0.1.1.0-inplace" True) (C1 (MetaCons "MapF" PrefixI True) (S1 (MetaSel (Just "runMapF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map k (f a)))))

newtype NEMapF k f a Source #

A non-empty map of f as, indexed by keys of type k. It can be useful for represeting a product of many different values of type f a, each "at" a different k location, where you need to have at least one f a at all times.

Can be considered a combination of EnvT and NonEmptyF, in a way --- an NEMapF k f a is like a NonEmptyF (EnvT k f) a with unique (and ordered) keys.

See MapF for some use cases.

Constructors

NEMapF 

Fields

Instances
Monoid k => Interpret (NEMapF k) Source # 
Instance details

Defined in Data.HFunctor.Interpret

Associated Types

type C (NEMapF k) :: (Type -> Type) -> Constraint Source #

Methods

retract :: C (NEMapF k) f => NEMapF k f ~> f Source #

interpret :: C (NEMapF k) g => (f ~> g) -> NEMapF k f ~> g Source #

Monoid k => Inject (NEMapF k :: (Type -> Type) -> Type -> Type) Source #

Injects into a singleton map at mempty.

Instance details

Defined in Data.HFunctor

Methods

inject :: f ~> NEMapF k f Source #

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

Defined in Data.HFunctor.Internal

Methods

hmap :: (f ~> g) -> NEMapF k f ~> NEMapF k g Source #

Functor f => Functor (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

fmap :: (a -> b) -> NEMapF k f a -> NEMapF k f b #

(<$) :: a -> NEMapF k f b -> NEMapF k f a #

Foldable f => Foldable (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

fold :: Monoid m => NEMapF k f m -> m #

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

foldr :: (a -> b -> b) -> b -> NEMapF k f a -> b #

foldr' :: (a -> b -> b) -> b -> NEMapF k f a -> b #

foldl :: (b -> a -> b) -> b -> NEMapF k f a -> b #

foldl' :: (b -> a -> b) -> b -> NEMapF k f a -> b #

foldr1 :: (a -> a -> a) -> NEMapF k f a -> a #

foldl1 :: (a -> a -> a) -> NEMapF k f a -> a #

toList :: NEMapF k f a -> [a] #

null :: NEMapF k f a -> Bool #

length :: NEMapF k f a -> Int #

elem :: Eq a => a -> NEMapF k f a -> Bool #

maximum :: Ord a => NEMapF k f a -> a #

minimum :: Ord a => NEMapF k f a -> a #

sum :: Num a => NEMapF k f a -> a #

product :: Num a => NEMapF k f a -> a #

Traversable f => Traversable (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

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

(Eq k, Eq1 f) => Eq1 (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

liftEq :: (a -> b -> Bool) -> NEMapF k f a -> NEMapF k f b -> Bool #

(Ord k, Ord1 f) => Ord1 (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

liftCompare :: (a -> b -> Ordering) -> NEMapF k f a -> NEMapF k f b -> Ordering #

(Ord k, Read k, Read1 f) => Read1 (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

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

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NEMapF k f a] #

(Show k, Show1 f) => Show1 (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

Foldable1 f => Foldable1 (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

fold1 :: Semigroup m => NEMapF k f m -> m #

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

toNonEmpty :: NEMapF k f a -> NonEmpty a #

(Monoid k, Pointed f) => Pointed (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

point :: a -> NEMapF k f a #

Traversable1 f => Traversable1 (NEMapF k f) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

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

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

(Functor f, Ord k) => Alt (NEMapF k f) Source #

Left-biased union

Instance details

Defined in Control.Applicative.ListF

Methods

(<!>) :: NEMapF k f a -> NEMapF k f a -> NEMapF k f a #

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

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

(Eq k, Eq (f a)) => Eq (NEMapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

(==) :: NEMapF k f a -> NEMapF k f a -> Bool #

(/=) :: NEMapF k f a -> NEMapF k f a -> Bool #

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

Defined in Control.Applicative.ListF

Methods

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

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

toConstr :: NEMapF k f a -> Constr #

dataTypeOf :: NEMapF k f a -> DataType #

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

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

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

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

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

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

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

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

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

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

(Ord k, Ord (f a)) => Ord (NEMapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

compare :: NEMapF k f a -> NEMapF k f a -> Ordering #

(<) :: NEMapF k f a -> NEMapF k f a -> Bool #

(<=) :: NEMapF k f a -> NEMapF k f a -> Bool #

(>) :: NEMapF k f a -> NEMapF k f a -> Bool #

(>=) :: NEMapF k f a -> NEMapF k f a -> Bool #

max :: NEMapF k f a -> NEMapF k f a -> NEMapF k f a #

min :: NEMapF k f a -> NEMapF k f a -> NEMapF k f a #

(Ord k, Read k, Read (f a)) => Read (NEMapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

readsPrec :: Int -> ReadS (NEMapF k f a) #

readList :: ReadS [NEMapF k f a] #

readPrec :: ReadPrec (NEMapF k f a) #

readListPrec :: ReadPrec [NEMapF k f a] #

(Show k, Show (f a)) => Show (NEMapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Methods

showsPrec :: Int -> NEMapF k f a -> ShowS #

show :: NEMapF k f a -> String #

showList :: [NEMapF k f a] -> ShowS #

Generic (NEMapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

Associated Types

type Rep (NEMapF k f a) :: Type -> Type #

Methods

from :: NEMapF k f a -> Rep (NEMapF k f a) x #

to :: Rep (NEMapF k f a) x -> NEMapF k f a #

(Ord k, Alt f) => Semigroup (NEMapF k f a) Source #

A union, combining matching keys with <!>.

Instance details

Defined in Control.Applicative.ListF

Methods

(<>) :: NEMapF k f a -> NEMapF k f a -> NEMapF k f a #

sconcat :: NonEmpty (NEMapF k f a) -> NEMapF k f a #

stimes :: Integral b => b -> NEMapF k f a -> NEMapF k f a #

type C (NEMapF k) Source # 
Instance details

Defined in Data.HFunctor.Interpret

type C (NEMapF k) = Alt
type Rep (NEMapF k f a) Source # 
Instance details

Defined in Control.Applicative.ListF

type Rep (NEMapF k f a) = D1 (MetaData "NEMapF" "Control.Applicative.ListF" "functor-combinators-0.1.1.0-inplace" True) (C1 (MetaCons "NEMapF" PrefixI True) (S1 (MetaSel (Just "runNEMapF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NEMap k (f a)))))