generic-lens-1.2.0.1: Generically derive traversals, lenses and prisms.

Copyright(C) 2019 Csongor Kiss
LicenseBSD3
MaintainerCsongor Kiss <kiss.csongor.kiss@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Data.Generics.Product.Types

Contents

Description

Derive traversals of a given type in a product.

Synopsis

Traversals

Running example:

>>> :set -XTypeApplications
>>> :set -XDeriveGeneric
>>> :set -XScopedTypeVariables
>>> import GHC.Generics
>>> :m +Data.Generics.Internal.VL.Traversal
>>> :m +Data.Generics.Internal.VL.Lens
>>> :{
data WTree a w
  = Leaf a
  | Fork (WTree a w) (WTree a w)
  | WithWeight (WTree a w) w
  deriving (Generic, Show)
:}

class HasTypes s a Source #

Instances
HasTypesUsing ChGeneric s a => HasTypes s a Source # 
Instance details

Defined in Data.Generics.Product.Types

Methods

types_ :: Traversal' s a

types :: forall a s. HasTypes s a => Traversal' s a Source #

Traverse all types in the given structure.

For example, to update all Strings in a WTree (Maybe String) String, we can write

>>> myTree = WithWeight (Fork (Leaf (Just "hello")) (Leaf Nothing)) "world"
>>> over (types @String) (++ "!") myTree
WithWeight (Fork (Leaf (Just "hello!")) (Leaf Nothing)) "world!"

The traversal is deep, which means that not just the immediate children are visited, but all nested values too.

Custom traversal strategies

The default traversal strategy types recurses into each node of the type using the Generic instance for the nodes. However, in general not all nodes will have a Generic instance. For example:

>>> data Opaque = Opaque String deriving Show
>>> myTree = WithWeight (Fork (Leaf (Opaque "foo")) (Leaf (Opaque "bar"))) False
>>> over (types @String) (++ "!") myTree
...
... | No instance for ‘Generic Opaque’
... |   arising from a generic traversal.
... |   Either derive the instance, or define a custom traversal using ‘HasTypesCustom’
...

In these cases, we can define a custom traversal strategy to override the generic behaviour for certain types. For a self-contained example, see the CustomChildren module in the tests directory.

type family Children (ch :: Type) (a :: Type) :: [Type] Source #

The children of a type are the types of its fields. The Children type family maps a type a to its set of children.

This type family is parameterized by a symbol ch (that can be declared as an empty data type). The symbol ChGeneric provides a default definition. You can create new symbols to override the set of children of abstract, non-generic types.

The following example declares a Custom symbol to redefine Children for some abstract types from the time library.

data Custom
type instance Children Custom a = ChildrenCustom a

type family ChildrenCustom (a :: Type) where
  ChildrenCustom DiffTime        = '[]
  ChildrenCustom NominalDiffTime = '[]
  -- Add more custom mappings here.

  ChildrenCustom a = Children ChGeneric a

To use this definition, replace types with typesUsing @Custom.

Instances
type Children ChGeneric a Source # 
Instance details

Defined in Data.Generics.Product.Types

data ChGeneric Source #

The default definition of Children. Primitive types from core libraries have no children, and other types are assumed to be Generic.

Instances
type Children ChGeneric a Source # 
Instance details

Defined in Data.Generics.Product.Types

class HasTypesUsing (ch :: Type) s a Source #

Since: 1.2.0.0

Minimal complete definition

typesUsing_

Instances
HasTypesUsing ch a a Source # 
Instance details

Defined in Data.Generics.Product.Types

Methods

typesUsing_ :: Traversal' a a

HasTypesOpt ch (Interesting ch a s) s a => HasTypesUsing ch s a Source # 
Instance details

Defined in Data.Generics.Product.Types

Methods

typesUsing_ :: Traversal' s a

typesUsing :: forall ch a s. HasTypesUsing ch s a => Traversal' s a Source #

Since: 1.2.0.0

class HasTypesCustom (ch :: Type) s a where Source #

By adding instances to this class, we can override the default behaviour in an ad-hoc manner. For example:

instance HasTypesCustom Custom Opaque String where
  typesCustom f (Opaque str) = Opaque $ f str

Since: 1.2.0.0

Methods

typesCustom :: Traversal' s a Source #

This function should never be used directly, only to override the default traversal behaviour. To actually use the custom traversal strategy, see typesUsing. This is because typesUsing does additional optimisations, like ensuring that nodes with no relevant members will not be traversed at runtime.

Instances
(GHasTypes ch (Rep s) a, Generic s, Defined (Rep s) (PrettyError ((Text "No instance " :<>: QuoteType (HasTypesCustom ch s a)) ': ([] :: [ErrorMessage])) :: Constraint) ()) => HasTypesCustom ch s a Source # 
Instance details

Defined in Data.Generics.Product.Types