generic-lens
Copyright(C) 2020 Csongor Kiss
LicenseBSD3
MaintainerCsongor Kiss <kiss.csongor.kiss@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Generics.Product.Types

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 #

Instances

Instances details
HasTypes Void a # 
Instance details

Defined in Data.Generics.Product.Internal.Types

Methods

types_ :: Traversal' Void a

HasTypes s Void # 
Instance details

Defined in Data.Generics.Product.Internal.Types

Methods

types_ :: Traversal' s Void

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

Defined in Data.Generics.Product.Internal.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 a :: [Type] #

Instances

Instances details
type Children ChGeneric a # 
Instance details

Defined in Data.Generics.Product.Internal.Types

type Children ChGeneric a = ChildrenDefault a

data ChGeneric #

Instances

Instances details
HasTypes b a => GHasTypes ChGeneric (Rec0 b :: k -> Type) (Rec0 b :: k -> Type) a a # 
Instance details

Defined in Data.Generics.Product.Internal.Types

Methods

gtypes_ :: forall (x :: k). Traversal (Rec0 b x) (Rec0 b x) a a

type Children ChGeneric a # 
Instance details

Defined in Data.Generics.Product.Internal.Types

type Children ChGeneric a = ChildrenDefault a

class HasTypesUsing ch s t a b #

Minimal complete definition

typesUsing_

Instances

Instances details
HasTypesUsing ch Void Void a b # 
Instance details

Defined in Data.Generics.Product.Internal.Types

Methods

typesUsing_ :: Traversal Void Void a b

HasTypesUsing ch a b a b # 
Instance details

Defined in Data.Generics.Product.Internal.Types

Methods

typesUsing_ :: Traversal a b a b

HasTypesUsing ch s s Void Void # 
Instance details

Defined in Data.Generics.Product.Internal.Types

Methods

typesUsing_ :: Traversal s s Void Void

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

Defined in Data.Generics.Product.Internal.Types

Methods

typesUsing_ :: Traversal s t a b

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

Since: 1.2.0.0

class HasTypesCustom ch s t a b where #

Methods

typesCustom :: Traversal s t a b #

Instances

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

Defined in Data.Generics.Product.Internal.Types

Methods

typesCustom :: Traversal s t a b #