Copyright | (C) 2020 Csongor Kiss |
---|---|
License | BSD3 |
Maintainer | Csongor Kiss <kiss.csongor.kiss@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Data.Generics.Product.Types
Description
Derive traversals of a given type in a product.
Synopsis
- class HasTypes s a
- types :: forall a s. HasTypes s a => Traversal' s a
- type family Children ch a :: [Type]
- data ChGeneric
- class HasTypesUsing ch s t a b
- typesUsing :: forall ch a s. HasTypesUsing ch s s a a => Traversal' s a
- class HasTypesCustom ch s t a b where
- typesCustom :: Traversal s t a b
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) :}
Instances
HasTypes Void a # | |
Defined in Data.Generics.Product.Internal.Types Methods types_ :: Traversal' Void a | |
HasTypes s Void # | |
Defined in Data.Generics.Product.Internal.Types Methods types_ :: Traversal' s Void | |
HasTypesUsing ChGeneric s s a a => HasTypes s a # | |
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 String
s 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.
class HasTypesUsing ch s t a b #
Minimal complete definition
typesUsing_
Instances
HasTypesUsing ch Void Void a b # | |
Defined in Data.Generics.Product.Internal.Types Methods typesUsing_ :: Traversal Void Void a b | |
HasTypesUsing ch a b a b # | |
Defined in Data.Generics.Product.Internal.Types Methods typesUsing_ :: Traversal a b a b | |
HasTypesUsing ch s s Void Void # | |
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 # | |
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
(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 # | |
Defined in Data.Generics.Product.Internal.Types Methods typesCustom :: Traversal s t a b # |