generic-data-functions-0.2.0: Familiar functions lifted to generic data types
Safe HaskellSafe-Inferred
LanguageGHC2021

Generic.Data.Function.Traverse.Constructor

Synopsis

Documentation

data A a Source #

Constructors

A a (Sum Int) () 

Instances

Instances details
Generic (A a) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.Constructor

Associated Types

type Rep (A a) :: Type -> Type Source #

Methods

from :: A a -> Rep (A a) x Source #

to :: Rep (A a) x -> A a Source #

Show a => Show (A a) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.Constructor

Methods

showsPrec :: Int -> A a -> ShowS Source #

show :: A a -> String Source #

showList :: [A a] -> ShowS Source #

type Rep (A a) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.Constructor

type Rep (A a) = D1 ('MetaData "A" "Generic.Data.Function.Traverse.Constructor" "generic-data-functions-0.2.0-inplace" 'False) (C1 ('MetaCons "A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Sum Int)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ()))))

class GenericTraverse f where Source #

Applicative functors that can be generically traversed.

Associated Types

type GenericTraverseC f a :: Constraint Source #

The type class providing (applicative) actions for permitted types.

Methods

genericTraverseAction Source #

Arguments

:: GenericTraverseC f a 
=> String

data type name

-> String

constructor name

-> Maybe String

record name (if present)

-> Natural

field index

-> f a 

The action in traverse (first argument).

We include data type metadata because this function is useful for monadic parsers, which can record it in error messages. (We don't do it for foldMap because it's pure.)

Instances

Instances details
GenericTraverse EmptyRec0 Source #

traverse over types where all fields map to their respective mempty.

Can result in type errors lacking context: a field missing a Monoid instance will type error with a regular "no instance for" message, without telling you the surrounding type.

Maybe silly.

Instance details

Defined in Generic.Data.Function.Traverse.Constructor

Associated Types

type GenericTraverseC EmptyRec0 a Source #

GenericTraverse NoRec0 Source #

traverse over types with no fields in any constructor.

Instance details

Defined in Generic.Data.Function.Traverse.Constructor

Associated Types

type GenericTraverseC NoRec0 a Source #

class GTraverseC cd cc (si :: Natural) f f' where Source #

Methods

gTraverseC :: f (f' p) Source #

Instances

Instances details
Applicative f => GTraverseC (cd :: k1) (cc :: k2) 0 (f :: Type -> Type) (U1 :: k3 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.Constructor

Methods

gTraverseC :: forall (p :: k). f (U1 p) Source #

(Applicative f, GTraverseC cd cc si f l, GTraverseC cd cc (si + ProdArity r) f r) => GTraverseC (cd :: k1) (cc :: k2) si (f :: Type -> Type) (l :*: r :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.Constructor

Methods

gTraverseC :: forall (p :: k). f ((l :*: r) p) Source #

(GenericTraverse f, GenericTraverseC f a, Functor f, KnownNat si, Selector cs, Constructor cc, Datatype cd) => GTraverseC (cd :: k2) (cc :: k1) si (f :: Type -> Type) (S1 cs (Rec0 a) :: k3 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.Constructor

Methods

gTraverseC :: forall (p :: k). f (S1 cs (Rec0 a) p) Source #

type family ProdArity (f :: Type -> Type) :: Natural where ... Source #

Equations

ProdArity (S1 c f) = 1 
ProdArity (l :*: r) = ProdArity l + ProdArity r