stacked-0.1.0: A modern indexed monad stack
Safe HaskellNone
LanguageGHC2021

Control.Monad.Indexed.Cont2.Lead.Generic

Description

Leads are a concept which emerge from the bidirectional aspect of stacked applicatives and monads. This module defines leads generically for every constructor of a type with a Generic instance (see lead below).

What is a lead?

When implementing a traversal with regular applicative functors, we write things like

foo :: (Applicative f) => (a -> f b) -> Maybe a -> f (Maybe b)
foo f (Just a) = Just <$> f a
foo _ Maybe = Maybe

With stacked applicatives, however, the argument is on the abstract stack, rather than a proper argument to the function. That is we want a function:

bar :: (Indexed.Applicative m, Stacked m)
    => m (a -> r) r b -> m (Maybe a -> r) r (Maybe b)

So we have to provide a way to pattern-match on the the top element of the stack. This is what lead provide. Leads are effectful actions, because they can fail, representing each constructor. Because they're effectful they are used with (*) rather than ($) like constructors are. So that bar would be implemented as

bar f =
  lead @"Just" <*> f
  <|> lead @None

Or, with OverloadedLabels and Control.Monad.Indexed.Cont2.Lead.Labels,

bar f =
  #Just <*> f
  <|> #None

The strength of stacked applicatives (or monads) is that leads extend to constructors with several fields in much the same way as regular applicatives do.

data OneOrTwo a b = One a | Two a b
  deriving (Generic)

baz :: (Indexed.Applicative m, Stacked m)
    => m (a -> r) r b -> m (OneOrTwo a a -> r) r (OneOrTwo b b)
baz f =
  #One <*> f
  <|> #Two <*> f <*> f

baz2 :: (Indexed.Applicative m, Stacked m)
     => m (a -> r) r a' -> m (b -> r) r b' -> m (OneOrTwo a b -> r) r (OneOrTwo a' b')
baz2 f g =
  #One <*> f
  <|> #Two <*> f <*> g
Synopsis

Documentation

lead :: forall (c :: Symbol) t r m. (Leading c t, MonadPlus m, Stacked m) => m (t -> r) (CFieldsType c (Rep t ()) r) (CFieldsType c (Rep t ()) t) Source #

lead C is the lead for any constructor C of a Generic data type. For instance

lead @Just :: m (Maybe a -> r) (a -> r) (b -> Maybe b)

With OverloadedLabels and Control.Monad.Indexed.Cont2.Lead.Labels, this can be written simply #Just instead.

For a constructors with several arguments the type would be

data OneOrTwo a b = One a | Two a b
  deriving (Generic)

lead @Two :: m (OneOrTwo a b -> r) (a -> b -> r) (c -> d -> OneOrTwo c d)

Manual definitions

Expand

Here are some manual, specialised, definitions of lead for inspiration if the generic derivation aren't enough.

lead @True :: (Indexed.MonadPlus m, Cont2.Stacked m) => m (Bool -> r) r Bool
lead @True = Indexed.do
  Cont2.stack (\cases _ k True -> k; fl _ b -> fl b) (\k -> k True)
  Indexed.pure True
lead @Just :: (Indexed.MonadPlus m, Cont2.Stacked m) => m (Maybe a -> r) (a -> r) (b -> Maybe b)
lead @Just = Indexed.do
  Cont2.stack (\cases _ k (Just a) -> k a; fl _ b -> fl b) (\k a -> k (Just a))
  Indexed.pure Just
lead @Two :: (Indexed.MonadPlus m, Cont2.Stacked m) => m (OneOrTwo a b -> r) (a -> b -> r) (c -> d -> OneOrTwo c d)
lead @Two = Indexed.do
  Cont2.stack (\cases _ k (Two a b) -> k a b; fl _ b -> fl b) (\k a b -> k (Two a b))
  Indexed.pure Two

Auxiliary definitions

class Leading (c :: Symbol) t Source #

Minimal complete definition

match, unmatch

Instances

Instances details
(Generic t, Defined (Rep t) (TypeError (NoGeneric t) :: Constraint) (), GLeading c (Rep t) ()) => Leading c t Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2.Lead.Generic

Methods

match :: (t -> i) -> CFieldsType c (Rep t ()) i -> t -> i

unmatch :: (t -> i) -> CFieldsType c (Rep t ()) i

type family CFieldsType (c :: Symbol) rep tgt where ... Source #

Equations

CFieldsType c rep tgt = FieldsType (FromJust (SelectConstructor c rep)) tgt