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

Generic.Data.Function.Traverse

Description

traverse for generic data types.

TODO This is harder to conceptualize than generic foldMap. No nice clean explanation yet.

This function can provide generic support for simple parser-esque types.

Synopsis

Documentation

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 #

genericTraverseNonSum :: forall f a. (Generic a, GTraverseNonSum f (Rep a), Functor f) => f a Source #

Generic traverse over a term of non-sum data type f a.

f a must have exactly one constructor.

class GTraverseNonSum f f' Source #

Minimal complete definition

gTraverseNonSum

Instances

Instances details
(Functor f, GTraverseNonSum' cd f f') => GTraverseNonSum (f :: Type -> Type) (D1 cd f' :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.NonSum

Methods

gTraverseNonSum :: forall (p :: k0). f (D1 cd f' p) Source #

class (GenericTraverse f, Alternative f, Monad f) => GenericTraverseSum f where Source #

Sum type monads that can be generically traversed.

For sum types, we require a monad with choice to differentiate constructors.

Methods

genericTraverseSumPfxTagAction Source #

Arguments

:: GenericTraverseC f pt 
=> String

data type name

-> f pt 

Try to parse a prefix tag of type pt.

Relevant metadata is provided as arguments.

genericTraverseSumNoMatchingCstrAction Source #

Arguments

:: String

data type name

-> [String]

non-matching constructor names

-> Text

prefix tag, prettified

-> f a 

Parse error due to no constructor matching the parsed prefix tag.

Relevant metadata is provided as arguments.

data PfxTagCfg a Source #

How to use a type as a prefix tag in a generic sum type parser.

Constructors

PfxTagCfg 

Fields

  • pfxTagCfgFromCstr :: String -> a

    How to turn a constructor name into a prefix tag.

  • pfxTagCfgEq :: a -> a -> Bool

    How to compare prefix tags for equality.

    By shoving this into our generic derivation config, we can avoid adding an insidious Eq constraint. In general, you will want to set this to (==).

  • pfxTagCfgShow :: a -> Text

    Make a prefix tag human-readable. show is often appropriate.

genericTraverseSum :: forall f a pt. (Generic a, GTraverseSum f (Rep a), GenericTraverseC f pt, Functor f) => PfxTagCfg pt -> f a Source #

Generic traverse over a term of sum data type f a.

f a must have at least two constructors.

You must provide a configuration for how to handle constructors.

class GTraverseSum f f' Source #

Minimal complete definition

gTraverseSum

Instances

Instances details
(Functor f, GTraverseSum' cd f f') => GTraverseSum f (D1 cd f' :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.Sum

Methods

gTraverseSum :: forall pt (p :: k0). GenericTraverseC f pt => PfxTagCfg pt -> f (D1 cd f' p) Source #

eqShowPfxTagCfg :: (Eq a, Show a) => (String -> a) -> PfxTagCfg a Source #

Construct a prefix tag config using existing Eq and Show instances.

The user only needs to provide the constructor name parser.