Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- toLabelx :: EnsureLabel x y => x -> y
- dredge :: forall k1 k2 (vs1 :: [Type]) (ns1 :: [[Type]]) (vs :: [Type]) (ns :: [[Type]]) (xs :: [Type]) p v (fb :: k1) r (rft :: k1) (l :: k2) (ns2 :: [[Type]]) x. (SameLength' vs1 ns1, SameLength' vs ns, SameLength' ns1 vs1, SameLength' ns vs, LabelablePath xs (p v fb) (p r rft), MapFieldTree (TryCollectionListTF r) ns, MapFieldTreeVal r (TryCollectionListTF r) vs, FilterLastEq (Label l) ns ns ns1, FilterLastEq (Label l) ns vs vs1, FilterVEq1 v vs1 ns1 ns2, HGuardNonNull (NamesDontMatch r ns l) ns1, HSingleton (NonUnique r v l) (TypesDontMatch r ns1 vs1 v) ns2 xs, EnsureLabel x (Label l)) => x -> p v fb -> p r rft
- getSAfromOutputOptic :: (p a fb -> p rs rft) ~ stab => (Proxy (rs :: *) -> Proxy (a :: *) -> stab) -> stab
- dredge' :: forall k2 k (vs1 :: [Type]) (ns1 :: [[Type]]) (vs :: [Type]) (ns :: [[Type]]) (xs :: [Type]) p a (f :: Type -> k2) s (l :: k) (ns2 :: [[Type]]) x. (SameLength' vs1 ns1, SameLength' vs ns, SameLength' ns1 vs1, SameLength' ns vs, LabelablePath xs (p a (f a)) (p s (f s)), MapFieldTree (TryCollectionListTF s) ns, MapFieldTreeVal s (TryCollectionListTF s) vs, FilterLastEq (Label l) ns ns ns1, FilterLastEq (Label l) ns vs vs1, FilterVEq1 a vs1 ns1 ns2, HGuardNonNull (NamesDontMatch s ns l) ns1, HSingleton (NonUnique s a l) (TypesDontMatch s ns1 vs1 a) ns2 xs, EnsureLabel x (Label l)) => x -> p a (f a) -> p s (f s)
- dredgeND :: forall k1 k2 (xs :: [Type]) p a (fb :: k1) r (rft :: k1) (ns :: [[Type]]) (l :: k2) (ns' :: [[Type]]) x. (LabelablePath xs (p a fb) (p r rft), MapFieldTree (TryCollectionListTF r) ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' r l) (NamesDontMatch r ns l) ns' xs, EnsureLabel x (Label l)) => x -> p a fb -> p r rft
- dredgeND' :: forall k2 k (xs :: [Type]) p a (f :: Type -> k2) s (ns :: [[Type]]) (l :: k) (ns' :: [[Type]]) x. (LabelablePath xs (p a (f a)) (p s (f s)), MapFieldTree (TryCollectionListTF s) ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' s l) (NamesDontMatch s ns l) ns' xs, EnsureLabel x (Label l)) => x -> p a (f a) -> p s (f s)
- dredgeTI' :: forall k2 (xs :: [Type]) p a (f :: Type -> k2) s (ns :: [[Type]]) (ns' :: [[Type]]) q. (LabelablePath xs (p a (f a)) (p s (f s)), MapFieldTree (TryCollectionListTF s) ns, FilterLastEq (Label a) ns ns ns', HSingleton (NonUnique' s a) (NamesDontMatch s ns a) ns' xs) => q a -> p a (f a) -> p s (f s)
- class HSingleton (msgAmb :: m) (msgEmpty :: m2) (ns :: [k]) (p :: k) | ns -> p
- class HGuardNonNull emptymsg (xs :: [k])
- class ConsTrue (b :: Bool) (x :: k) (xs :: [k]) (r :: [k]) | b x xs -> r, r b -> xs, x xs r -> b
- class FilterLastEq (x :: k) (xs :: [[k]]) (ys :: [m]) (ys' :: [m]) | x xs ys -> ys'
- class FilterVEq (v :: *) (vs :: [*]) (ns :: [k]) (ns' :: [k]) | v vs ns -> ns'
- class FilterVEq1 (v :: *) (vs :: [*]) (ns :: [k]) (ns' :: [k]) | v vs ns -> ns'
- class LabelPathEndingWith (r :: *) (l :: k) (path :: [*]) | r l -> path where
- labelPathEndingWith :: proxy r -> Label l -> Label path
- labelPathEndingWithTD :: forall r l v path vs vs1 ns ns1 ns2. (SameLength ns vs, SameLength ns1 vs1, FieldTree r ns, FieldTreeVal r vs, FilterLastEq (Label l) ns ns ns1, FilterLastEq (Label l) ns vs vs1, FilterVEq1 v vs1 ns1 ns2, HGuardNonNull (NamesDontMatch r ns l) ns1, HSingleton (NonUnique r v l) (TypesDontMatch r ns1 vs1 v) ns2 path) => Proxy r -> Label l -> Proxy v -> Label path
- type NamesDontMatch r ns l = (ErrShowType r :$$: (ErrText "has paths" :<>: ErrShowType ns)) :$$: (ErrText "but none which end in the desired label" :<>: ErrShowType l)
- type NonUnique' r l = (ErrText "Path ending in label " :<>: ErrShowType l) :$$: (ErrText "is not unique in " :<>: ErrShowType r)
- type NonUnique r v l = NonUnique' r l :$$: (ErrText "also considering the v type " :<>: ErrShowType v)
- type TypesDontMatch r ns1 vs1 v = ((ErrShowType r :$$: (ErrText "has potential paths with the right labels" :<>: ErrShowType ns1)) :$$: ((ErrText "which point at types" :<>: ErrShowType vs1) :<>: ErrText "respectively")) :$$: (ErrText "but none of these match the desired type" :<>: ErrShowType v)
- hLookupByLabelDredge :: forall k (ls :: [Type]) r1 r2 v (ns :: [[Type]]) (l :: k) (ns' :: [[Type]]). (HasFieldPath 'False ls (r1 r2) v, MapFieldTree (TryCollectionListTF r2) ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' r2 l) (NamesDontMatch r2 ns l) ns' ls) => Label l -> r1 r2 -> v
- hLookupByLabelPath :: HasFieldPath False ls r v => Label ls -> r -> v
- class LabelablePath (xs :: [*]) apb spt | spt xs -> apb where
- hLens'Path :: Label xs -> apb -> spt
- class HasFieldPath (needJust :: Bool) (ls :: [*]) r v | needJust ls r -> v where
- hLookupByLabelPath1 :: Proxy needJust -> Label ls -> r -> v
- class FieldTreeVal (r :: *) (v :: [*]) | r -> v
- class MapFieldTreeVal (r :: *) (ns :: Maybe [*]) (vs :: [*]) | r ns -> vs
- class FieldTree (r :: *) (v :: [[*]]) | r -> v
- type family TryCollectionListTF (r :: *) :: Maybe [*] where ...
- type TryCollectionList r v = v ~ TryCollectionListTF r
- class MapFieldTree (ns :: Maybe [*]) (vs :: [[*]]) | ns -> vs
- class MapCons (x :: k) (xs :: [[k]]) (xxs :: [[k]]) | x xs -> xxs
Documentation
toLabelx :: EnsureLabel x y => x -> y Source #
dredge :: forall k1 k2 (vs1 :: [Type]) (ns1 :: [[Type]]) (vs :: [Type]) (ns :: [[Type]]) (xs :: [Type]) p v (fb :: k1) r (rft :: k1) (l :: k2) (ns2 :: [[Type]]) x. (SameLength' vs1 ns1, SameLength' vs ns, SameLength' ns1 vs1, SameLength' ns vs, LabelablePath xs (p v fb) (p r rft), MapFieldTree (TryCollectionListTF r) ns, MapFieldTreeVal r (TryCollectionListTF r) vs, FilterLastEq (Label l) ns ns ns1, FilterLastEq (Label l) ns vs vs1, FilterVEq1 v vs1 ns1 ns2, HGuardNonNull (NamesDontMatch r ns l) ns1, HSingleton (NonUnique r v l) (TypesDontMatch r ns1 vs1 v) ns2 xs, EnsureLabel x (Label l)) => x -> p v fb -> p r rft Source #
Using HListPP syntax for short hand, dredge `foo
expands out to
something like `path . `to . `foo
, with the restriction that
there is only one possible `path . `to
which leads to the
label foo
.
For example, if we have the following definitions,
type BVal a = Record '[Tagged "x" a, Tagged "a" Char] type R a = Record [Tagged "a" Int, Tagged "b" (BVal a)] type V a = Variant [Tagged "a" Int, Tagged "b" (BVal a)] lx = Label :: Label "x"
Then we have:
dredge `x :: Lens (R a) (R b) a b dredge lx :: Lens (R a) (R b) a b
dredge `x :: Traversal (V a) (V b) a b -- there were only variants along the path we'd get a Prism dredge lx :: Traversal (V a) (V b) a b
result-type directed operations are supported
There are two ways to access a field with tag a
in the R type
defined above, but they result in fields with different types
being looked up:
`a :: Lens' (R a) Char `b . `a :: Lens' (R a) Int
so provided that the result type is disambiguated by the context, the following two types can happen
dredge `a :: Lens' (R a) Char dredge `a :: Lens' (R a) Int
TIP & TIC
type indexed collections are allowed along those paths, but
as explained in the Labelable
instances, only simple optics
(Lens' Prism' Traversal' ) are produced. dredgeTI'
works better if the target is a TIP or TIC
getSAfromOutputOptic :: (p a fb -> p rs rft) ~ stab => (Proxy (rs :: *) -> Proxy (a :: *) -> stab) -> stab Source #
dredge' :: forall k2 k (vs1 :: [Type]) (ns1 :: [[Type]]) (vs :: [Type]) (ns :: [[Type]]) (xs :: [Type]) p a (f :: Type -> k2) s (l :: k) (ns2 :: [[Type]]) x. (SameLength' vs1 ns1, SameLength' vs ns, SameLength' ns1 vs1, SameLength' ns vs, LabelablePath xs (p a (f a)) (p s (f s)), MapFieldTree (TryCollectionListTF s) ns, MapFieldTreeVal s (TryCollectionListTF s) vs, FilterLastEq (Label l) ns ns ns1, FilterLastEq (Label l) ns vs vs1, FilterVEq1 a vs1 ns1 ns2, HGuardNonNull (NamesDontMatch s ns l) ns1, HSingleton (NonUnique s a l) (TypesDontMatch s ns1 vs1 a) ns2 xs, EnsureLabel x (Label l)) => x -> p a (f a) -> p s (f s) Source #
dredge
except a simple (s ~ t, a ~ b) optic is produced
dredgeND :: forall k1 k2 (xs :: [Type]) p a (fb :: k1) r (rft :: k1) (ns :: [[Type]]) (l :: k2) (ns' :: [[Type]]) x. (LabelablePath xs (p a fb) (p r rft), MapFieldTree (TryCollectionListTF r) ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' r l) (NamesDontMatch r ns l) ns' xs, EnsureLabel x (Label l)) => x -> p a fb -> p r rft Source #
dredgeND (named directed only) is the same as dredge
, except the
result type (a
) is not used when the label would otherwise
be ambiguous. dredgeND might give better type errors, but otherwise
there should be no reason to pick it over dredge
dredgeND' :: forall k2 k (xs :: [Type]) p a (f :: Type -> k2) s (ns :: [[Type]]) (l :: k) (ns' :: [[Type]]) x. (LabelablePath xs (p a (f a)) (p s (f s)), MapFieldTree (TryCollectionListTF s) ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' s l) (NamesDontMatch s ns l) ns' xs, EnsureLabel x (Label l)) => x -> p a (f a) -> p s (f s) Source #
dredgeND
except a simple (s ~ t, a ~ b) optic is produced
dredgeTI' :: forall k2 (xs :: [Type]) p a (f :: Type -> k2) s (ns :: [[Type]]) (ns' :: [[Type]]) q. (LabelablePath xs (p a (f a)) (p s (f s)), MapFieldTree (TryCollectionListTF s) ns, FilterLastEq (Label a) ns ns ns', HSingleton (NonUnique' s a) (NamesDontMatch s ns a) ns' xs) => q a -> p a (f a) -> p s (f s) Source #
The same as dredgeND', except intended for TIP/TICs because
the assumption is made that l ~ v
for the Tagged l v
elements.
In other words, ticPrism' and tipyLens'
could usually
be replaced by
dredgeTI' :: _ => Label a -> Lens' (TIP s) a dredgeTI' :: _ => Label a -> Prism' (TIC s) a
where we might have s ~ '[Tagged a a, Tagged b b]
class HSingleton (msgAmb :: m) (msgEmpty :: m2) (ns :: [k]) (p :: k) | ns -> p Source #
HSingleton msg xs x
is like '[x] ~ xs
if that constraint can hold,
otherwise it is Fail msg
. See comments on Fail
about how its kind
varies with ghc version.
Instances
(Fail m3, (Any :: k) ~ a) => HSingleton (m4 :: m) (m3 :: m1) ('[] :: [k]) (a :: k) Source # | |
Defined in Data.HList.Dredge | |
(Fail m3, (Any :: k) ~ a) => HSingleton (m3 :: m) (m4 :: m1) (n1 ': (n2 ': n3) :: [k]) (a :: k) Source # | |
Defined in Data.HList.Dredge | |
HSingleton (m3 :: m) (m4 :: m1) ('[n] :: [k]) (n :: k) Source # | |
Defined in Data.HList.Dredge |
class HGuardNonNull emptymsg (xs :: [k]) Source #
HGuardNonNull msg xs
is like when (null xs) (fail msg)
Instances
Fail msg => HGuardNonNull (msg :: k1) ('[] :: [k2]) Source # | |
Defined in Data.HList.Dredge | |
HGuardNonNull (msg :: k1) (x ': xs :: [k2]) Source # | |
Defined in Data.HList.Dredge |
class ConsTrue (b :: Bool) (x :: k) (xs :: [k]) (r :: [k]) | b x xs -> r, r b -> xs, x xs r -> b Source #
ConsTrue b x xs r
is like r = if b then x:xs else xs
Instances
ConsTrue 'False (x :: k) (xs :: [k]) (xs :: [k]) Source # | |
Defined in Data.HList.Dredge | |
ConsTrue 'True (x :: a) (xs :: [a]) (x ': xs :: [a]) Source # | |
Defined in Data.HList.Dredge |
class FilterLastEq (x :: k) (xs :: [[k]]) (ys :: [m]) (ys' :: [m]) | x xs ys -> ys' Source #
FilterLastEq x xs ys ys'
determines ys' such that it
contains all of the ys !! i
such that last (xs !! i) == x
.
In other words it is like
ys' = [ y | (xsElt, y) <- zip xs ys, last xsElt == x ]
Instances
FilterLastEq (y :: k) ('[] :: [[k]]) ('[] :: [m]) ('[] :: [m]) Source # | |
Defined in Data.HList.Dredge | |
(HReverse path (y' ': rest), HEq y y' b, ConsTrue b z r1 r, FilterLastEq y xs zs r1) => FilterLastEq (y :: Type) (path ': xs :: [[Type]]) (z ': zs :: [m]) (r :: [m]) Source # | |
Defined in Data.HList.Dredge |
class FilterVEq (v :: *) (vs :: [*]) (ns :: [k]) (ns' :: [k]) | v vs ns -> ns' Source #
The same as FilterLastEq
except id
is used instead of last
class FilterVEq1 (v :: *) (vs :: [*]) (ns :: [k]) (ns' :: [k]) | v vs ns -> ns' Source #
like FilterVEq
, except if there is
Instances
FilterVEq1 v ('[] :: [Type]) ('[] :: [k]) ('[] :: [k]) Source # | |
Defined in Data.HList.Dredge | |
FilterVEq v (a ': (b ': c)) ns ns' => FilterVEq1 v (a ': (b ': c)) (ns :: [k]) (ns' :: [k]) Source # | |
Defined in Data.HList.Dredge | |
v ~ v' => FilterVEq1 v '[v'] (ns :: [k]) (ns :: [k]) Source # | |
Defined in Data.HList.Dredge |
class LabelPathEndingWith (r :: *) (l :: k) (path :: [*]) | r l -> path where Source #
LabelPathEndingWith r l path
determines a unique path suitable for hLookupByLabelPath
(calling Fail
otherwise) through the
nested records/variants in r ending with l
Nothing
labelPathEndingWith :: proxy r -> Label l -> Label path Source #
Instances
(FieldTree r ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' r l) (NamesDontMatch r ns l) ns' path) => LabelPathEndingWith r (l :: k) path Source # | |
Defined in Data.HList.Dredge labelPathEndingWith :: proxy r -> Label l -> Label path Source # |
labelPathEndingWithTD :: forall r l v path vs vs1 ns ns1 ns2. (SameLength ns vs, SameLength ns1 vs1, FieldTree r ns, FieldTreeVal r vs, FilterLastEq (Label l) ns ns ns1, FilterLastEq (Label l) ns vs vs1, FilterVEq1 v vs1 ns1 ns2, HGuardNonNull (NamesDontMatch r ns l) ns1, HSingleton (NonUnique r v l) (TypesDontMatch r ns1 vs1 v) ns2 path) => Proxy r -> Label l -> Proxy v -> Label path Source #
type NamesDontMatch r ns l = (ErrShowType r :$$: (ErrText "has paths" :<>: ErrShowType ns)) :$$: (ErrText "but none which end in the desired label" :<>: ErrShowType l) Source #
type NonUnique' r l = (ErrText "Path ending in label " :<>: ErrShowType l) :$$: (ErrText "is not unique in " :<>: ErrShowType r) Source #
type NonUnique r v l = NonUnique' r l :$$: (ErrText "also considering the v type " :<>: ErrShowType v) Source #
type TypesDontMatch r ns1 vs1 v = ((ErrShowType r :$$: (ErrText "has potential paths with the right labels" :<>: ErrShowType ns1)) :$$: ((ErrText "which point at types" :<>: ErrShowType vs1) :<>: ErrText "respectively")) :$$: (ErrText "but none of these match the desired type" :<>: ErrShowType v) Source #
XXX
let x = 'x'; y = [pun| x |]; z = [pun| y |] z & dredge (Label :: Label "x") %~ (succ :: Int -> Int)
Should reference this type error, but for whatever reason it doesn't
hLookupByLabelDredge :: forall k (ls :: [Type]) r1 r2 v (ns :: [[Type]]) (l :: k) (ns' :: [[Type]]). (HasFieldPath 'False ls (r1 r2) v, MapFieldTree (TryCollectionListTF r2) ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' r2 l) (NamesDontMatch r2 ns l) ns' ls) => Label l -> r1 r2 -> v Source #
hLookupByLabelPath :: HasFieldPath False ls r v => Label ls -> r -> v Source #
lookup along a path
>>>
let v = mkVariant1 Label (mkVariant1 Label 'r') :: Variant '[Tagged "x" (Variant '[Tagged "y" Char])]
>>>
let r = hBuild (hBuild 'r') :: Record '[Tagged "x" (Record '[Tagged "y" Char])]
>>>
let p = Label :: Label [Label "x", Label "y"]
>>>
let lx = Label :: Label "y"
>>>
hLookupByLabelPath p v
Just 'r'
>>>
hLookupByLabelPath p r
'r'
>>>
hLookupByLabelDredge lx v
Just 'r'
>>>
hLookupByLabelDredge lx r
'r'
class LabelablePath (xs :: [*]) apb spt | spt xs -> apb where Source #
hLens'Path labc == hLens' la . hLens' lb . hLens' lc where la :: Label "a" lb :: Label "b" lc :: Label "c" labc :: Label '["a", "b", "c"]
hLens'Path :: Label xs -> apb -> spt Source #
Instances
x ~ x' => LabelablePath ('[] :: [Type]) x x' Source # | |
Defined in Data.HList.Dredge hLens'Path :: Label '[] -> x -> x' Source # | |
(Labelable x r s t a b, j ~ p a (f b), k2 ~ p (r s) (f (r t)), ty ~ LabelableTy r, LabeledOpticP ty p, LabeledOpticF ty f, LabeledOpticTo ty x ((->) :: Type -> Type -> Type), LabelablePath xs i j) => LabelablePath (Label x ': xs) i k2 Source # | |
Defined in Data.HList.Dredge hLens'Path :: Label (Label x ': xs) -> i -> k2 Source # |
class HasFieldPath (needJust :: Bool) (ls :: [*]) r v | needJust ls r -> v where Source #
hLookupByLabelPath1 :: Proxy needJust -> Label ls -> r -> v Source #
use hLookupByLabelPath
instead
Instances
HasFieldPath 'False ('[] :: [Type]) v v Source # | |
Defined in Data.HList.Dredge | |
HasFieldPath 'True ('[] :: [Type]) v (Maybe v) Source # | |
Defined in Data.HList.Dredge | |
(HasField l (Record r) u, HasFieldPath needJust ls u v) => HasFieldPath needJust (Label l ': ls) (Record r) v Source # | |
Defined in Data.HList.Dredge | |
(HasField l (Variant r) (Maybe u), HasFieldPath 'True ls u (Maybe v)) => HasFieldPath needJust (Label l ': ls) (Variant r) (Maybe v) Source # | |
Defined in Data.HList.Dredge |
class FieldTreeVal (r :: *) (v :: [*]) | r -> v Source #
(FieldTree r ns, FieldTreeVal r vs)
defines ns and vs such that looking up path (ns !! i) in r gives the type
(vs !! i). This is almost HasFieldPath False (ns !! i) (vs !! i)
, except
there is no additional Maybe when a Variant is encountered along the path
(and we don't have a type level !!
)
Instances
(TryCollectionList r ns, MapFieldTreeVal r ns v) => FieldTreeVal r v Source # | |
Defined in Data.HList.Dredge |
class MapFieldTreeVal (r :: *) (ns :: Maybe [*]) (vs :: [*]) | r ns -> vs Source #
Instances
MapFieldTreeVal r ('Nothing :: Maybe [Type]) ('[] :: [Type]) Source # | |
Defined in Data.HList.Dredge | |
(MapFieldTreeVal r ('Just xs) out2, FieldTreeVal v out1, (v ': HAppendListR out1 out2) ~ out) => MapFieldTreeVal r ('Just (Tagged n v ': xs)) out Source # | |
Defined in Data.HList.Dredge | |
MapFieldTreeVal r ('Just ('[] :: [Type])) ('[] :: [Type]) Source # | |
Defined in Data.HList.Dredge |
class FieldTree (r :: *) (v :: [[*]]) | r -> v Source #
list all paths through nested records or variants. An example instance would be
FieldTree r v
where
v ~ [[ Label "x", Label Dat ], '[Label "y"], '[Label "x"] ] r ~ Record [ Tagged "x" x, Tagged "y" String ] x ~ Variant '[ Tagged Dat Char ]
Instances
(TryCollectionList r ns, MapFieldTree ns vs) => FieldTree r vs Source # | the only instance |
Defined in Data.HList.Dredge |
type family TryCollectionListTF (r :: *) :: Maybe [*] where ... Source #
TryCollectionListTF (Record r) = Just r | |
TryCollectionListTF (Variant r) = Just r | |
TryCollectionListTF (TIC r) = Just r | |
TryCollectionListTF (TIP r) = Just r | |
TryCollectionListTF nothing = Nothing |
type TryCollectionList r v = v ~ TryCollectionListTF r Source #
class MapFieldTree (ns :: Maybe [*]) (vs :: [[*]]) | ns -> vs Source #
Instances
MapFieldTree ('Nothing :: Maybe [Type]) ('[] :: [[Type]]) Source # | |
Defined in Data.HList.Dredge | |
(MapFieldTree ('Just xs) vs3, FieldTree v vs1, MapCons (Label n) (('[] :: [Type]) ': vs1) vs2, HAppendListR vs2 vs3 ~ vs) => MapFieldTree ('Just (Tagged n v ': xs)) vs Source # | recursive case |
Defined in Data.HList.Dredge | |
MapFieldTree ('Just ('[] :: [Type])) ('[] :: [[Type]]) Source # | |
Defined in Data.HList.Dredge |
class MapCons (x :: k) (xs :: [[k]]) (xxs :: [[k]]) | x xs -> xxs Source #
MapCons x xs xxs is like xxs = map (x : ) xs
Instances
MapCons (x :: k) ('[] :: [[k]]) ('[] :: [[k]]) Source # | |
Defined in Data.HList.Dredge | |
MapCons x b r => MapCons (x :: a1) (a2 ': b :: [[a1]]) ((x ': a2) ': r :: [[a1]]) Source # | |
Defined in Data.HList.Dredge |