Copyright | (C) 2019 Csongor Kiss |
---|---|
License | BSD3 |
Maintainer | Csongor Kiss <kiss.csongor.kiss@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe |
Language | Haskell2010 |
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 :: Type) (a :: Type) :: [Type]
- data ChGeneric
- class HasTypesUsing (ch :: Type) s a
- typesUsing :: forall ch a s. HasTypesUsing ch s a => Traversal' s a
- class HasTypesCustom (ch :: Type) s a where
- typesCustom :: Traversal' s a
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
HasTypesUsing ChGeneric s a => HasTypes s a Source # | |
Defined in Data.Generics.Product.Types 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.
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
class HasTypesUsing (ch :: Type) s a Source #
Since: 1.2.0.0
typesUsing_
Instances
HasTypesUsing ch a a Source # | |
Defined in Data.Generics.Product.Types typesUsing_ :: Traversal' a a | |
HasTypesOpt ch (Interesting ch a s) s a => HasTypesUsing ch s a Source # | |
Defined in Data.Generics.Product.Types 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
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 # | |
Defined in Data.Generics.Product.Types typesCustom :: Traversal' s a Source # |