| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Generics.Product.Internal.Types
Synopsis
- type family Children ch a :: [Type]
- data ChGeneric
- type family ChildrenDefault a :: [Type] where ...
- type family ChildrenGeneric (f :: k -> Type) (cs :: [Type]) :: [Type] where ...
- type Interesting ch a t = Defined_list (Children ch t) (NoChildren ch t) (IsNothing (Interesting' ch a '[t] (Children ch t)))
- type family NoChildren ch a where ...
- type family Interesting' ch a (seen :: [Type]) (ts :: [Type]) :: Maybe [Type] where ...
- type family InterestingUnless ch a (seen :: [Type]) t (alreadySeen :: Bool) :: Maybe [Type] where ...
- type family InterestingOr ch a (seen' :: Maybe [Type]) (ts :: [Type]) :: Maybe [Type] where ...
- type family Elem (a1 :: a) (as :: [a]) :: Bool where ...
- type family IsNothing (a1 :: Maybe a) :: Bool where ...
- class HasTypes s a where
- types_ :: Traversal' s a
- data Void
- class HasTypesUsing ch s t a b where
- typesUsing_ :: Traversal s t a b
- class HasTypesCustom ch s t a b where
- typesCustom :: Traversal s t a b
- class HasTypesOpt ch (p :: Bool) s t a b where
- typesOpt :: Traversal s t a b
- class GHasTypes (ch :: k) (s :: k1 -> Type) (t :: k1 -> Type) a b where
- gtypes_ :: forall (x :: k1). Traversal (s x) (t x) a b
Documentation
type family Children ch a :: [Type] #
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 # | |
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 # | The default instance for |
Defined in Data.Generics.Product.Internal.Types | |
| type Children ChGeneric a # | |
Defined in Data.Generics.Product.Internal.Types | |
type family ChildrenDefault a :: [Type] where ... #
Equations
| ChildrenDefault Char = '[] :: [Type] | |
| ChildrenDefault Double = '[] :: [Type] | |
| ChildrenDefault Float = '[] :: [Type] | |
| ChildrenDefault Integer = '[] :: [Type] | |
| ChildrenDefault Int = '[] :: [Type] | |
| ChildrenDefault Int8 = '[] :: [Type] | |
| ChildrenDefault Int16 = '[] :: [Type] | |
| ChildrenDefault Int32 = '[] :: [Type] | |
| ChildrenDefault Int64 = '[] :: [Type] | |
| ChildrenDefault Word = '[] :: [Type] | |
| ChildrenDefault Word8 = '[] :: [Type] | |
| ChildrenDefault Word16 = '[] :: [Type] | |
| ChildrenDefault Word32 = '[] :: [Type] | |
| ChildrenDefault Word64 = '[] :: [Type] | |
| ChildrenDefault Text = '[] :: [Type] | |
| ChildrenDefault (Param n _1) = '[] :: [Type] | |
| 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])) |
type family ChildrenGeneric (f :: k -> Type) (cs :: [Type]) :: [Type] where ... #
Equations
| ChildrenGeneric (M1 _1 _2 f :: k -> Type) cs = ChildrenGeneric f cs | |
| ChildrenGeneric (l :*: r :: k -> Type) cs = ChildrenGeneric l (ChildrenGeneric r cs) | |
| ChildrenGeneric (l :+: r :: k -> Type) cs = ChildrenGeneric l (ChildrenGeneric r cs) | |
| ChildrenGeneric (Rec0 a :: k -> Type) cs = a ': cs | |
| ChildrenGeneric (_1 :: k -> Type) cs = cs |
type Interesting ch a t = Defined_list (Children ch t) (NoChildren ch t) (IsNothing (Interesting' ch a '[t] (Children ch t))) #
type family NoChildren ch a where ... #
Equations
| NoChildren ch a = PrettyError '['Text "No type family instance for " ':<>: QuoteType (Children ch a), 'Text "arising from a traversal over " ':<>: QuoteType a, 'Text "with custom strategy " ':<>: QuoteType ch] :: Constraint |
type family Interesting' ch a (seen :: [Type]) (ts :: [Type]) :: Maybe [Type] where ... #
Equations
| Interesting' ch _1 seen ('[] :: [Type]) = 'Just seen | |
| Interesting' ch a seen (t ': ts) = InterestingOr ch a (InterestingUnless ch a seen t (Elem t seen)) ts |
type family InterestingUnless ch a (seen :: [Type]) t (alreadySeen :: Bool) :: Maybe [Type] where ... #
Equations
| InterestingUnless ch a seen a _1 = 'Nothing :: Maybe [Type] | |
| 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 a (seen' :: Maybe [Type]) (ts :: [Type]) :: Maybe [Type] where ... #
Equations
| InterestingOr ch a ('Nothing :: Maybe [Type]) _1 = 'Nothing :: Maybe [Type] | |
| InterestingOr ch a ('Just seen) ts = Interesting' ch a seen ts |
Minimal complete definition
Nothing
Instances
| HasTypes Void a # | |
Defined in Data.Generics.Product.Internal.Types | |
| HasTypes s Void # | |
Defined in Data.Generics.Product.Internal.Types | |
| HasTypesUsing ChGeneric s s a a => HasTypes s a # | |
Defined in Data.Generics.Product.Internal.Types | |
Instances
| HasTypes Void a # | |
Defined in Data.Generics.Product.Internal.Types | |
| HasTypes s Void # | |
Defined in Data.Generics.Product.Internal.Types | |
| HasTypesUsing ch Void Void a b # | |
Defined in Data.Generics.Product.Internal.Types Methods typesUsing_ :: Traversal Void Void a b # | |
| HasTypesUsing ch s s Void Void # | |
Defined in Data.Generics.Product.Internal.Types Methods typesUsing_ :: Traversal s s Void Void # | |
class HasTypesUsing ch s t a b where #
Since: 1.2.0.0
Methods
typesUsing_ :: Traversal s t a b #
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 # | |
class HasTypesCustom ch s t a b where #
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
Methods
typesCustom :: Traversal s t a b #
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 # | |
Defined in Data.Generics.Product.Internal.Types Methods typesCustom :: Traversal s t a b # | |
class HasTypesOpt ch (p :: Bool) s t a b where #
Instances
| HasTypesOpt ch 'False s s a b # | |
Defined in Data.Generics.Product.Internal.Types | |
| HasTypesCustom ch s t a b => HasTypesOpt ch 'True s t a b # | |
Defined in Data.Generics.Product.Internal.Types | |
class GHasTypes (ch :: k) (s :: k1 -> Type) (t :: k1 -> Type) a b where #
Instances
| GHasTypes (ch :: k1) (U1 :: k2 -> Type) (U1 :: k2 -> Type) a b # | |
Defined in Data.Generics.Product.Internal.Types | |
| GHasTypes (ch :: k1) (V1 :: k2 -> Type) (V1 :: k2 -> Type) a b # | |
Defined in Data.Generics.Product.Internal.Types | |
| HasTypes b a => GHasTypes ChGeneric (Rec0 b :: k -> Type) (Rec0 b :: k -> Type) a a # | The default instance for |
Defined in Data.Generics.Product.Internal.Types | |
| HasTypesUsing ch s t a b => GHasTypes (ch :: Type) (Rec0 s :: k -> Type) (Rec0 t :: k -> Type) a b # | |
Defined in Data.Generics.Product.Internal.Types | |
| (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 # | |
Defined in Data.Generics.Product.Internal.Types | |
| (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 # | |
Defined in Data.Generics.Product.Internal.Types | |
| GHasTypes ch s t a b => GHasTypes (ch :: k1) (M1 m meta s :: k2 -> Type) (M1 m meta t :: k2 -> Type) a b # | |
Defined in Data.Generics.Product.Internal.Types | |