Copyright | (c) Justin Le 2019 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- newtype ListF f a = ListF {
- runListF :: [f a]
- mapListF :: ([f a] -> [g b]) -> ListF f a -> ListF g b
- newtype NonEmptyF f a where
- NonEmptyF {
- runNonEmptyF :: NonEmpty (f a)
- pattern ProdNonEmpty :: (f :*: ListF f) a -> NonEmptyF f a
- NonEmptyF {
- mapNonEmptyF :: (NonEmpty (f a) -> NonEmpty (g b)) -> NonEmptyF f a -> NonEmptyF g b
- toListF :: NonEmptyF f ~> ListF f
- fromListF :: ListF f ~> (Proxy :+: NonEmptyF f)
- newtype MaybeF f a = MaybeF {}
- mapMaybeF :: (Maybe (f a) -> Maybe (g b)) -> MaybeF f a -> MaybeF g b
- listToMaybeF :: ListF f ~> MaybeF f
- maybeToListF :: MaybeF f ~> ListF f
- newtype MapF k f a = MapF {}
- newtype NEMapF k f a = NEMapF {}
ListF
A list of f a
s. Can be used to describe a product of many different
values of type f a
.
This is the Free Plus
.
Incidentally, if used with a Contravariant
f
, this is instead the
free Divisible
.
Instances
HTraversable (ListF :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # | |
Defined in Data.HFunctor.HTraversable | |
HFunctor (ListF :: (k -> Type) -> k -> TYPE LiftedRep) Source # | |
HBind (ListF :: (k -> Type) -> k -> TYPE LiftedRep) Source # | |
Inject (ListF :: (k -> Type) -> k -> TYPE LiftedRep) Source # | |
FreeOf Plus (ListF :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # | This could also be |
Plus f => Interpret (ListF :: (Type -> Type) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | A free |
Foldable f => Foldable (ListF f) Source # | |
Defined in Control.Applicative.ListF fold :: Monoid m => ListF f m -> m # foldMap :: Monoid m => (a -> m) -> ListF f a -> 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 # elem :: Eq a => a -> ListF f a -> Bool # maximum :: Ord a => ListF f a -> a # minimum :: Ord a => ListF f a -> a # | |
Eq1 f => Eq1 (ListF f) Source # | |
Ord1 f => Ord1 (ListF f) Source # | |
Defined in Control.Applicative.ListF | |
Read1 f => Read1 (ListF f) Source # | |
Defined in Control.Applicative.ListF | |
Show1 f => Show1 (ListF f) Source # | |
Contravariant f => Contravariant (ListF f) Source # | Since: 0.3.0.0 |
Traversable f => Traversable (ListF f) Source # | |
Applicative f => Alternative (ListF f) Source # | |
Applicative f => Applicative (ListF f) Source # | |
Functor f => Functor (ListF f) Source # | |
Decidable f => Decidable (ListF f) Source # | Since: 0.3.0.0 |
Contravariant f => Divisible (ListF f) Source # | Since: 0.3.0.0 |
Conclude f => Conclude (ListF f) Source # | Since: 0.3.0.0 |
Decide f => Decide (ListF f) Source # | Since: 0.3.0.0 |
Contravariant f => Divise (ListF f) Source # | Since: 0.3.0.0 |
Invariant f => Invariant (ListF f) Source # | Since: 0.3.0.0 |
Defined in Control.Applicative.ListF | |
Pointed f => Pointed (ListF f) Source # | |
Defined in Control.Applicative.ListF | |
Functor f => Alt (ListF f) Source # | |
Apply f => Apply (ListF f) Source # | |
Functor f => Plus (ListF f) Source # | |
Defined in Control.Applicative.ListF | |
(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (ListF f a) Source # | |
Defined in Control.Applicative.ListF 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 :: forall r r'. (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) # | |
Monoid (ListF f a) Source # | |
Semigroup (ListF f a) Source # | |
Generic (ListF f a) Source # | |
Read (f a) => Read (ListF f a) Source # | |
Show (f a) => Show (ListF f a) Source # | |
Eq (f a) => Eq (ListF f a) Source # | |
Ord (f a) => Ord (ListF f a) Source # | |
Defined in Control.Applicative.ListF | |
type FreeFunctorBy (ListF :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # | |
Defined in Data.HFunctor.Final | |
type Rep (ListF f a) Source # | |
Defined in Control.Applicative.ListF |
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 a
s. 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
on any Functor
f
.
Incidentally, if used with a Contravariant
f
, this is instead the
free Divise
.
NonEmptyF | |
|
pattern ProdNonEmpty :: (f :*: ListF f) a -> NonEmptyF f a | Treat a
|
Instances
mapNonEmptyF :: (NonEmpty (f a) -> NonEmpty (g b)) -> NonEmptyF f a -> NonEmptyF g b Source #
Map a function over the inside of a NonEmptyF
.
MaybeF
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
.
Instances
HTraversable (MaybeF :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # | |
Defined in Data.HFunctor.HTraversable | |
HFunctor (MaybeF :: (k -> Type) -> k -> TYPE LiftedRep) Source # | |
HBind (MaybeF :: (k -> Type) -> k -> TYPE LiftedRep) Source # | |
Inject (MaybeF :: (k -> Type) -> k -> TYPE LiftedRep) Source # | |
Plus f => Interpret (MaybeF :: (Type -> Type) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | Technically, |
Foldable f => Foldable (MaybeF f) Source # | |
Defined in Control.Applicative.ListF fold :: Monoid m => MaybeF f m -> m # foldMap :: Monoid m => (a -> m) -> MaybeF f a -> 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 # elem :: Eq a => a -> MaybeF f a -> Bool # maximum :: Ord a => MaybeF f a -> a # minimum :: Ord a => MaybeF f a -> a # | |
Eq1 f => Eq1 (MaybeF f) Source # | |
Ord1 f => Ord1 (MaybeF f) Source # | |
Defined in Control.Applicative.ListF | |
Read1 f => Read1 (MaybeF f) Source # | |
Defined in Control.Applicative.ListF | |
Show1 f => Show1 (MaybeF f) Source # | |
Contravariant f => Contravariant (MaybeF f) Source # | Since: 0.3.3.0 |
Traversable f => Traversable (MaybeF f) Source # | |
Defined in Control.Applicative.ListF | |
Applicative f => Alternative (MaybeF f) Source # | |
Applicative f => Applicative (MaybeF f) Source # | |
Functor f => Functor (MaybeF f) Source # | |
Decidable f => Decidable (MaybeF f) Source # | Since: 0.3.3.0 |
Contravariant f => Divisible (MaybeF f) Source # | Since: 0.3.3.0 |
Conclude f => Conclude (MaybeF f) Source # | Since: 0.3.3.0 |
Decide f => Decide (MaybeF f) Source # | Since: 0.3.3.0 |
Contravariant f => Divise (MaybeF f) Source # | Since: 0.3.3.0 |
Invariant f => Invariant (MaybeF f) Source # | Since: 0.3.3.0 |
Defined in Control.Applicative.ListF | |
Pointed f => Pointed (MaybeF f) Source # | |
Defined in Control.Applicative.ListF | |
Functor f => Alt (MaybeF f) Source # | |
Functor f => Plus (MaybeF f) Source # | |
Defined in Control.Applicative.ListF | |
(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (MaybeF f a) Source # | |
Defined in Control.Applicative.ListF 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 :: forall r r'. (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) # | |
Monoid (MaybeF f a) Source # | |
Semigroup (MaybeF f a) Source # | Picks the first |
Generic (MaybeF f a) Source # | |
Read (f a) => Read (MaybeF f a) Source # | |
Show (f a) => Show (MaybeF f a) Source # | |
Eq (f a) => Eq (MaybeF f a) Source # | |
Ord (f a) => Ord (MaybeF f a) Source # | |
type Rep (MaybeF f a) Source # | |
Defined in Control.Applicative.ListF |
mapMaybeF :: (Maybe (f a) -> Maybe (g b)) -> MaybeF f a -> MaybeF g b Source #
Map a function over the inside of a MaybeF
.
MapF
A map of f a
s, 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
is like a MapF
k f a
with unique (and ordered)
keys.ListF
(EnvT
k f) a
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
.
Instances
HTraversable (MapF k :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # | |
Defined in Data.HFunctor.HTraversable | |
HFunctor (MapF k2 :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # | |
Monoid k2 => Inject (MapF k2 :: (k1 -> Type) -> k1 -> TYPE LiftedRep) Source # | Injects into a singleton map at |
(Monoid k, Plus f) => Interpret (MapF k :: (Type -> Type) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | |
Foldable f => Foldable (MapF k f) Source # | |
Defined in Control.Applicative.ListF fold :: Monoid m => MapF k f m -> m # foldMap :: Monoid m => (a -> m) -> MapF k f a -> 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 # 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 # | |
(Eq k, Eq1 f) => Eq1 (MapF k f) Source # | |
(Ord k, Ord1 f) => Ord1 (MapF k f) Source # | |
Defined in Control.Applicative.ListF | |
(Ord k, Read k, Read1 f) => Read1 (MapF k f) Source # | |
Defined in Control.Applicative.ListF | |
(Show k, Show1 f) => Show1 (MapF k f) Source # | |
Traversable f => Traversable (MapF k f) Source # | |
Defined in Control.Applicative.ListF | |
Functor f => Functor (MapF k f) Source # | |
(Monoid k, Pointed f) => Pointed (MapF k f) Source # | |
Defined in Control.Applicative.ListF | |
(Functor f, Ord k) => Alt (MapF k f) Source # | Left-biased union |
(Functor f, Ord k) => Plus (MapF k f) Source # | |
Defined in Control.Applicative.ListF | |
(Typeable a, Typeable f, Typeable k2, Data k1, Data (f a), Ord k1) => Data (MapF k1 f a) Source # | |
Defined in Control.Applicative.ListF gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MapF k1 f a -> c (MapF k1 f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MapF k1 f a) # toConstr :: MapF k1 f a -> Constr # dataTypeOf :: MapF k1 f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MapF k1 f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MapF k1 f a)) # gmapT :: (forall b. Data b => b -> b) -> MapF k1 f a -> MapF k1 f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MapF k1 f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MapF k1 f a -> r # gmapQ :: (forall d. Data d => d -> u) -> MapF k1 f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MapF k1 f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MapF k1 f a -> m (MapF k1 f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MapF k1 f a -> m (MapF k1 f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MapF k1 f a -> m (MapF k1 f a) # | |
(Ord k, Alt f) => Monoid (MapF k f a) Source # | |
(Ord k, Alt f) => Semigroup (MapF k f a) Source # | A union, combining matching keys with |
Generic (MapF k1 f a) Source # | |
(Ord k1, Read k1, Read (f a)) => Read (MapF k1 f a) Source # | |
(Show k1, Show (f a)) => Show (MapF k1 f a) Source # | |
(Eq k1, Eq (f a)) => Eq (MapF k1 f a) Source # | |
(Ord k1, Ord (f a)) => Ord (MapF k1 f a) Source # | |
Defined in Control.Applicative.ListF | |
type Rep (MapF k1 f a) Source # | |
Defined in Control.Applicative.ListF |
A non-empty map of f a
s, 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
is like a NEMapF
k f a
with unique (and ordered)
keys.NonEmptyF
(EnvT
k f) a
See MapF
for some use cases.
Instances
HTraversable (NEMapF k :: (k1 -> TYPE LiftedRep) -> k1 -> TYPE LiftedRep) Source # | |
Defined in Data.HFunctor.HTraversable | |
HTraversable1 (NEMapF k :: (k1 -> TYPE LiftedRep) -> k1 -> TYPE LiftedRep) Source # | |
Defined in Data.HFunctor.HTraversable | |
HFunctor (NEMapF k2 :: (k1 -> TYPE LiftedRep) -> k1 -> TYPE LiftedRep) Source # | |
Monoid k2 => Inject (NEMapF k2 :: (k1 -> TYPE LiftedRep) -> k1 -> TYPE LiftedRep) Source # | Injects into a singleton map at |
(Monoid k, Alt f) => Interpret (NEMapF k :: (Type -> TYPE LiftedRep) -> Type -> TYPE LiftedRep) (f :: Type -> Type) Source # | |
Foldable f => Foldable (NEMapF k f) Source # | |
Defined in Control.Applicative.ListF fold :: Monoid m => NEMapF k f m -> m # foldMap :: Monoid m => (a -> m) -> NEMapF k f a -> 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 # | |
(Eq k, Eq1 f) => Eq1 (NEMapF k f) Source # | |
(Ord k, Ord1 f) => Ord1 (NEMapF k f) Source # | |
Defined in Control.Applicative.ListF | |
(Ord k, Read k, Read1 f) => Read1 (NEMapF k f) Source # | |
Defined in Control.Applicative.ListF | |
(Show k, Show1 f) => Show1 (NEMapF k f) Source # | |
Traversable f => Traversable (NEMapF k f) Source # | |
Defined in Control.Applicative.ListF | |
Functor f => Functor (NEMapF k f) Source # | |
(Monoid k, Pointed f) => Pointed (NEMapF k f) Source # | |
Defined in Control.Applicative.ListF | |
(Functor f, Ord k) => Alt (NEMapF k f) Source # | Left-biased union |
Foldable1 f => Foldable1 (NEMapF k f) Source # | |
Traversable1 f => Traversable1 (NEMapF k f) Source # | |
(Typeable a, Typeable f, Typeable k2, Data k1, Data (f a), Ord k1) => Data (NEMapF k1 f a) Source # | |
Defined in Control.Applicative.ListF gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NEMapF k1 f a -> c (NEMapF k1 f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NEMapF k1 f a) # toConstr :: NEMapF k1 f a -> Constr # dataTypeOf :: NEMapF k1 f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NEMapF k1 f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NEMapF k1 f a)) # gmapT :: (forall b. Data b => b -> b) -> NEMapF k1 f a -> NEMapF k1 f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NEMapF k1 f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NEMapF k1 f a -> r # gmapQ :: (forall d. Data d => d -> u) -> NEMapF k1 f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NEMapF k1 f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NEMapF k1 f a -> m (NEMapF k1 f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NEMapF k1 f a -> m (NEMapF k1 f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NEMapF k1 f a -> m (NEMapF k1 f a) # | |
(Ord k, Alt f) => Semigroup (NEMapF k f a) Source # | A union, combining matching keys with |
Generic (NEMapF k1 f a) Source # | |
(Ord k1, Read k1, Read (f a)) => Read (NEMapF k1 f a) Source # | |
(Show k1, Show (f a)) => Show (NEMapF k1 f a) Source # | |
(Eq k1, Eq (f a)) => Eq (NEMapF k1 f a) Source # | |
(Ord k1, Ord (f a)) => Ord (NEMapF k1 f a) Source # | |
Defined in Control.Applicative.ListF compare :: NEMapF k1 f a -> NEMapF k1 f a -> Ordering # (<) :: NEMapF k1 f a -> NEMapF k1 f a -> Bool # (<=) :: NEMapF k1 f a -> NEMapF k1 f a -> Bool # (>) :: NEMapF k1 f a -> NEMapF k1 f a -> Bool # (>=) :: NEMapF k1 f a -> NEMapF k1 f a -> Bool # | |
type Rep (NEMapF k1 f a) Source # | |
Defined in Control.Applicative.ListF |