generic-data-functions-0.5.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 tag where Source #

Implementation enumeration type class for generic traverse.

The type variable is uninstantiated, used purely as a tag. Good types include the type class used inside (providing you define the type class/it's not an orphan instance), or a custom void data type. See the binrep library on Hackage for an example.

Minimal complete definition

genericTraverseAction

Associated Types

type GenericTraverseF tag :: Type -> Type Source #

The target Applicative to traverse to.

type GenericTraverseC tag a :: Constraint Source #

The type class providing the action in traverse for permitted types.

Methods

genericTraverseAction Source #

Arguments

:: GenericTraverseC tag a 
=> String

data type name

-> String

constructor name

-> Maybe String

record name (if present)

-> Natural

field index

-> GenericTraverseF tag 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.)

genericTraverseV1 :: GenericTraverseF tag (V1 p) Source #

Action to run when trying to parse a V1 (void data type).

Defaults to error, but you may wrap it in your functor if it pleases.

Instances

Instances details
GenericTraverse (EmptyRec0 f :: Type) Source #

traverse over types where all fields are replaced with the functor's empty.

Note that one may write a valid instance using a Monoid on as instead. I don't think you should. But I can't explain why.

Instance details

Defined in Generic.Data.Function.Traverse.Constructor

Associated Types

type GenericTraverseF (EmptyRec0 f) :: Type -> Type Source #

type GenericTraverseC (EmptyRec0 f) a Source #

GenericTraverse (NoRec0 f :: Type) Source #

traverse over types with no fields in any constructor.

Instance details

Defined in Generic.Data.Function.Traverse.Constructor

Associated Types

type GenericTraverseF (NoRec0 f) :: Type -> Type Source #

type GenericTraverseC (NoRec0 f) a Source #

genericTraverseNonSum :: forall {k} (tag :: k) a. (Generic a, Functor (GenericTraverseF tag), GTraverseNonSum tag (Rep a)) => GenericTraverseF tag a Source #

Generic traverse over a term of non-sum data type f a, where f is set by the tag you pass.

class GTraverseNonSum tag gf Source #

Minimal complete definition

gTraverseNonSum

Instances

Instances details
(Functor (GenericTraverseF tag), GTraverseNonSumD tag cd gf) => GTraverseNonSum (tag :: k1) (D1 cd gf :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.NonSum

Methods

gTraverseNonSum :: forall (p :: k10). GenericTraverseF tag (D1 cd gf p) Source #

class GenericTraverse tag => GenericTraverseSum tag where Source #

Sum type monads that can be generically traversed.

Methods

genericTraverseSumPfxTagAction Source #

Arguments

:: GenericTraverseC tag pt 
=> String

data type name

-> GenericTraverseF tag 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

-> GenericTraverseF tag 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 {k} (tag :: k) a pt. (Generic a, Functor (GenericTraverseF tag), GTraverseSum tag (Rep a), GenericTraverseC tag pt) => PfxTagCfg pt -> GenericTraverseF tag a Source #

Generic traverse over a term of sum data type f a, where f is set by the tag you pass.

You must provide a configuration for how to handle constructors.

class GTraverseSum tag gf Source #

Minimal complete definition

gTraverseSum

Instances

Instances details
GenericTraverse tag => GTraverseSum (tag :: k1) (V1 :: k2 -> Type) Source # 
Instance details

Defined in Generic.Data.Function.Traverse.Sum

Methods

gTraverseSum :: forall pt (p :: k10). GenericTraverseC tag pt => PfxTagCfg pt -> GenericTraverseF tag (V1 p) Source #

(Alternative (GenericTraverseF tag), Monad (GenericTraverseF tag), GenericTraverseSum tag, GTraverseCSum tag cd gf, Datatype cd, KnownSymbols (CstrNames gf)) => GTraverseSum (tag :: k1) (D1 cd gf :: k2 -> Type) Source #

Test all constructors of the given non-void data type; if they all fail, run a failure action and pass it all the constructors names in the type.

Instance details

Defined in Generic.Data.Function.Traverse.Sum

Methods

gTraverseSum :: forall pt (p :: k10). GenericTraverseC tag pt => PfxTagCfg pt -> GenericTraverseF tag (D1 cd gf 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.