Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type family Children (ch :: Type) (a :: Type) :: [Type]
- data ChGeneric
- type family ChildrenDefault (a :: Type) :: [Type] where ...
- type family ChildrenGeneric (f :: k -> Type) (cs :: [Type]) :: [Type] where ...
- type Interesting (ch :: Type) (a :: Type) (t :: Type) = Defined_list (Children ch t) (NoChildren ch t) (IsNothing (Interesting' ch a '[t] (Children ch t)))
- type family NoChildren (ch :: Type) (a :: Type) :: Constraint where ...
- type family Interesting' (ch :: Type) (a :: Type) (seen :: [Type]) (ts :: [Type]) :: Maybe [Type] where ...
- type family InterestingUnless (ch :: Type) (a :: Type) (seen :: [Type]) (t :: Type) (alreadySeen :: Bool) :: Maybe [Type] where ...
- type family InterestingOr (ch :: Type) (a :: Type) (seen' :: Maybe [Type]) (ts :: [Type]) :: Maybe [Type] where ...
- type family Elem a as where ...
- type family IsNothing a where ...
- class HasTypes s a where
- types_ :: Traversal' s a
- data Void
- class HasTypesUsing (ch :: Type) s t a b where
- typesUsing_ :: Traversal s t a b
- class HasTypesCustom (ch :: Type) s t a b where
- typesCustom :: Traversal s t a b
- class HasTypesOpt (ch :: Type) (p :: Bool) s t a b where
- typesOpt :: Traversal s t a b
- class GHasTypes ch s t a b where
- gtypes_ :: Traversal (s x) (t x) a b
Documentation
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 # | |
Defined in Data.Generics.Product.Internal.Types |
The default definition of Children
.
Primitive types from core libraries have no children, and other types are
assumed to be Generic
.
Instances
HasTypes b a => GHasTypes ChGeneric (Rec0 b :: k -> Type) (Rec0 b :: k -> Type) a a Source # | The default instance for |
type Children ChGeneric a Source # | |
Defined in Data.Generics.Product.Internal.Types |
type family ChildrenDefault (a :: Type) :: [Type] where ... Source #
ChildrenDefault Char = '[] | |
ChildrenDefault Double = '[] | |
ChildrenDefault Float = '[] | |
ChildrenDefault Integer = '[] | |
ChildrenDefault Int = '[] | |
ChildrenDefault Int8 = '[] | |
ChildrenDefault Int16 = '[] | |
ChildrenDefault Int32 = '[] | |
ChildrenDefault Int64 = '[] | |
ChildrenDefault Word = '[] | |
ChildrenDefault Word8 = '[] | |
ChildrenDefault Word16 = '[] | |
ChildrenDefault Word32 = '[] | |
ChildrenDefault Word64 = '[] | |
ChildrenDefault Text = '[] | |
ChildrenDefault (Param n _) = '[] | |
ChildrenDefault a = Defined (Rep a) (NoGeneric a '['Text "arising from a generic traversal.", 'Text "Either derive the instance, or define a custom traversal using HasTypesCustom"]) (ChildrenGeneric (Rep a) '[]) |
type family ChildrenGeneric (f :: k -> Type) (cs :: [Type]) :: [Type] where ... Source #
ChildrenGeneric (M1 _ _ f) cs = ChildrenGeneric f cs | |
ChildrenGeneric (l :*: r) cs = ChildrenGeneric l (ChildrenGeneric r cs) | |
ChildrenGeneric (l :+: r) cs = ChildrenGeneric l (ChildrenGeneric r cs) | |
ChildrenGeneric (Rec0 a) cs = a ': cs | |
ChildrenGeneric _ cs = cs |
type Interesting (ch :: Type) (a :: Type) (t :: Type) = Defined_list (Children ch t) (NoChildren ch t) (IsNothing (Interesting' ch a '[t] (Children ch t))) Source #
type family NoChildren (ch :: Type) (a :: Type) :: Constraint where ... Source #
type family Interesting' (ch :: Type) (a :: Type) (seen :: [Type]) (ts :: [Type]) :: Maybe [Type] where ... Source #
Interesting' ch _ seen '[] = 'Just seen | |
Interesting' ch a seen (t ': ts) = InterestingOr ch a (InterestingUnless ch a seen t (Elem t seen)) ts |
type family InterestingUnless (ch :: Type) (a :: Type) (seen :: [Type]) (t :: Type) (alreadySeen :: Bool) :: Maybe [Type] where ... Source #
InterestingUnless ch a seen a _ = 'Nothing | |
InterestingUnless ch a seen t 'True = 'Just seen | |
InterestingUnless ch a seen t 'False = Defined_list (Children ch t) (NoChildren ch t) (Interesting' ch a (t ': seen) (Children ch t)) |
type family InterestingOr (ch :: Type) (a :: Type) (seen' :: Maybe [Type]) (ts :: [Type]) :: Maybe [Type] where ... Source #
InterestingOr ch a 'Nothing _ = 'Nothing | |
InterestingOr ch a ('Just seen) ts = Interesting' ch a seen ts |
class HasTypes s a where Source #
Nothing
Instances
HasTypes Void a Source # | |
Defined in Data.Generics.Product.Internal.Types | |
HasTypes s Void Source # | |
Defined in Data.Generics.Product.Internal.Types | |
HasTypesUsing ChGeneric s s a a => HasTypes s a Source # | |
Defined in Data.Generics.Product.Internal.Types |
Instances
HasTypes Void a Source # | |
Defined in Data.Generics.Product.Internal.Types | |
HasTypes s Void Source # | |
Defined in Data.Generics.Product.Internal.Types | |
HasTypesUsing ch Void Void a b Source # | |
Defined in Data.Generics.Product.Internal.Types typesUsing_ :: Traversal Void Void a b Source # | |
HasTypesUsing ch s s Void Void Source # | |
Defined in Data.Generics.Product.Internal.Types typesUsing_ :: Traversal s s Void Void Source # |
class HasTypesUsing (ch :: Type) s t a b where Source #
Since: 1.2.0.0
typesUsing_ :: Traversal s t a b Source #
Instances
HasTypesUsing ch Void Void a b Source # | |
Defined in Data.Generics.Product.Internal.Types typesUsing_ :: Traversal Void Void a b Source # | |
HasTypesUsing ch a b a b Source # | |
Defined in Data.Generics.Product.Internal.Types typesUsing_ :: Traversal a b a b Source # | |
HasTypesUsing ch s s Void Void Source # | |
Defined in Data.Generics.Product.Internal.Types typesUsing_ :: Traversal s s Void Void Source # | |
HasTypesOpt ch (Interesting ch a s) s t a b => HasTypesUsing ch s t a b Source # | |
Defined in Data.Generics.Product.Internal.Types typesUsing_ :: Traversal s t a b Source # |
class HasTypesCustom (ch :: Type) s t a b 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 Opaque String String where typesCustom f (Opaque str) = Opaque $ f str
Since: 1.2.0.0
typesCustom :: Traversal s t a b 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) (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 Source # | |
Defined in Data.Generics.Product.Internal.Types typesCustom :: Traversal s t a b Source # |
class HasTypesOpt (ch :: Type) (p :: Bool) s t a b where Source #
Instances
HasTypesOpt ch 'False s s a b Source # | |
Defined in Data.Generics.Product.Internal.Types | |
HasTypesCustom ch s t a b => HasTypesOpt ch 'True s t a b Source # | |
Defined in Data.Generics.Product.Internal.Types |
class GHasTypes ch s t a b where Source #
Instances
GHasTypes (ch :: k1) (U1 :: k2 -> Type) (U1 :: k2 -> Type) a b Source # | |
GHasTypes (ch :: k1) (V1 :: k2 -> Type) (V1 :: k2 -> Type) a b Source # | |
HasTypes b a => GHasTypes ChGeneric (Rec0 b :: k -> Type) (Rec0 b :: k -> Type) a a Source # | The default instance for |
HasTypesUsing ch s t a b => GHasTypes (ch :: Type) (Rec0 s :: k -> Type) (Rec0 t :: k -> Type) a b Source # | |
(GHasTypes ch l l' a b, GHasTypes ch r r' a b) => GHasTypes (ch :: k1) (l :*: r :: k2 -> Type) (l' :*: r' :: k2 -> Type) a b Source # | |
(GHasTypes ch l l' a b, GHasTypes ch r r' a b) => GHasTypes (ch :: k1) (l :+: r :: k2 -> Type) (l' :+: r' :: k2 -> Type) a b Source # | |
GHasTypes ch s t a b => GHasTypes (ch :: k1) (M1 m meta s :: k2 -> Type) (M1 m meta t :: k2 -> Type) a b Source # | |