Safe Haskell | None |
---|---|
Language | Haskell2010 |
Generics.SOP.NS
Documentation
newtype SOP (f :: k -> Type) (xss :: [[k]]) #
Instances
HTrans (SOP :: (k1 -> Type) -> [[k1]] -> Type) (SOP :: (k2 -> Type) -> [[k2]] -> Type) | |
Defined in Data.SOP.NS Methods htrans :: forall c (xs :: [[k1]]) (ys :: [[k2]]) proxy f g. AllZipN (Prod (SOP :: (k1 -> Type) -> [[k1]] -> Type)) c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> SOP f xs -> SOP g ys # hcoerce :: forall (f :: k1 -> Type) (g :: k2 -> Type) (xs :: [[k1]]) (ys :: [[k2]]). AllZipN (Prod (SOP :: (k1 -> Type) -> [[k1]] -> Type)) (LiftedCoercible f g) xs ys => SOP f xs -> SOP g ys # | |
HAp (SOP :: (k -> Type) -> [[k]] -> Type) | |
HApInjs (SOP :: (k -> Type) -> [[k]] -> Type) | |
HCollapse (SOP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS | |
HExpand (SOP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS Methods hexpand :: forall (xs :: [[k]]) f. SListIN (Prod (SOP :: (k -> Type) -> [[k]] -> Type)) xs => (forall (x :: k). f x) -> SOP f xs -> Prod (SOP :: (k -> Type) -> [[k]] -> Type) f xs # hcexpand :: forall c (xs :: [[k]]) proxy f. AllN (Prod (SOP :: (k -> Type) -> [[k]] -> Type)) c xs => proxy c -> (forall (x :: k). c x => f x) -> SOP f xs -> Prod (SOP :: (k -> Type) -> [[k]] -> Type) f xs # | |
HIndex (SOP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS | |
HSequence (SOP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS Methods hsequence' :: forall (xs :: [[k]]) f (g :: k -> Type). (SListIN (SOP :: (k -> Type) -> [[k]] -> Type) xs, Applicative f) => SOP (f :.: g) xs -> f (SOP g xs) # hctraverse' :: forall c (xs :: [[k]]) g proxy f f'. (AllN (SOP :: (k -> Type) -> [[k]] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) # htraverse' :: forall (xs :: [[k]]) g f f'. (SListIN (SOP :: (k -> Type) -> [[k]] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) # | |
HTraverse_ (SOP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS Methods hctraverse_ :: forall c (xs :: [[k]]) g proxy f. (AllN (SOP :: (k -> Type) -> [[k]] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> SOP f xs -> g () # htraverse_ :: forall (xs :: [[k]]) g f. (SListIN (SOP :: (k -> Type) -> [[k]] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g ()) -> SOP f xs -> g () # | |
NFData (NS (NP f) xss) => NFData (SOP f xss) | |
Defined in Data.SOP.NS | |
Show (NS (NP f) xss) => Show (SOP f xss) | |
Eq (NS (NP f) xss) => Eq (SOP f xss) | |
Ord (NS (NP f) xss) => Ord (SOP f xss) | |
Defined in Data.SOP.NS | |
type Same (SOP :: (k1 -> Type) -> [[k1]] -> Type) | |
Defined in Data.SOP.NS | |
type Prod (SOP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS | |
type SListIN (SOP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS | |
type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a | |
Defined in Data.SOP.NS | |
type AllN (SOP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) | |
Defined in Data.SOP.NS |
data NS (a :: k -> Type) (b :: [k]) where #
Constructors
Z :: forall {k} (a :: k -> Type) (x :: k) (xs :: [k]). a x -> NS a (x ': xs) | |
S :: forall {k} (a :: k -> Type) (xs :: [k]) (x :: k). NS a xs -> NS a (x ': xs) |
Instances
HTrans (NS :: (k1 -> Type) -> [k1] -> Type) (NS :: (k2 -> Type) -> [k2] -> Type) | |
Defined in Data.SOP.NS Methods htrans :: forall c (xs :: [k1]) (ys :: [k2]) proxy f g. AllZipN (Prod (NS :: (k1 -> Type) -> [k1] -> Type)) c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> NS f xs -> NS g ys # hcoerce :: forall (f :: k1 -> Type) (g :: k2 -> Type) (xs :: [k1]) (ys :: [k2]). AllZipN (Prod (NS :: (k1 -> Type) -> [k1] -> Type)) (LiftedCoercible f g) xs ys => NS f xs -> NS g ys # | |
HAp (NS :: (k -> Type) -> [k] -> Type) | |
HApInjs (NS :: (k -> Type) -> [k] -> Type) | |
HCollapse (NS :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS | |
HExpand (NS :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS Methods hexpand :: forall (xs :: [k]) f. SListIN (Prod (NS :: (k -> Type) -> [k] -> Type)) xs => (forall (x :: k). f x) -> NS f xs -> Prod (NS :: (k -> Type) -> [k] -> Type) f xs # hcexpand :: forall c (xs :: [k]) proxy f. AllN (Prod (NS :: (k -> Type) -> [k] -> Type)) c xs => proxy c -> (forall (x :: k). c x => f x) -> NS f xs -> Prod (NS :: (k -> Type) -> [k] -> Type) f xs # | |
HIndex (NS :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS | |
HSequence (NS :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS Methods hsequence' :: forall (xs :: [k]) f (g :: k -> Type). (SListIN (NS :: (k -> Type) -> [k] -> Type) xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) # hctraverse' :: forall c (xs :: [k]) g proxy f f'. (AllN (NS :: (k -> Type) -> [k] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) # htraverse' :: forall (xs :: [k]) g f f'. (SListIN (NS :: (k -> Type) -> [k] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) # | |
HTraverse_ (NS :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS Methods hctraverse_ :: forall c (xs :: [k]) g proxy f. (AllN (NS :: (k -> Type) -> [k] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> NS f xs -> g () # htraverse_ :: forall (xs :: [k]) g f. (SListIN (NS :: (k -> Type) -> [k] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g ()) -> NS f xs -> g () # | |
All (Compose NFData f) xs => NFData (NS f xs) | |
Defined in Data.SOP.NS | |
All (Compose Show f) xs => Show (NS f xs) | |
All (Compose Eq f) xs => Eq (NS f xs) | |
(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NS f xs) | |
type Same (NS :: (k1 -> Type) -> [k1] -> Type) | |
Defined in Data.SOP.NS | |
type Prod (NS :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS | |
type SListIN (NS :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS | |
type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a | |
Defined in Data.SOP.NS | |
type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) | |
Defined in Data.SOP.NS |
injections :: forall {k} (xs :: [k]) (f :: k -> Type). SListI xs => NP (Injection f xs) xs #
shift :: forall {a1} (f :: a1 -> Type) (xs :: [a1]) (a2 :: a1) (x :: a1). Injection f xs a2 -> Injection f (x ': xs) a2 #
shiftInjection :: forall {a1} (f :: a1 -> Type) (xs :: [a1]) (a2 :: a1) (x :: a1). Injection f xs a2 -> Injection f (x ': xs) a2 #
apInjs_POP :: forall {k} (xss :: [[k]]) (f :: k -> Type). SListI xss => POP f xss -> [SOP f xss] #
shiftEjection :: forall {a1} (f :: a1 -> Type) (x :: a1) (xs :: [a1]) (a2 :: a1). Ejection f xs a2 -> Ejection f (x ': xs) a2 #
compare_NS :: forall {k} r f g (xs :: [k]). r -> (forall (x :: k). f x -> g x -> r) -> r -> NS f xs -> NS g xs -> r #
ccompare_NS :: forall {k} c proxy r f g (xs :: [k]). All c xs => proxy c -> r -> (forall (x :: k). c x => f x -> g x -> r) -> r -> NS f xs -> NS g xs -> r #
compare_SOP :: forall {k} r (f :: k -> Type) (g :: k -> Type) (xss :: [[k]]). r -> (forall (xs :: [k]). NP f xs -> NP g xs -> r) -> r -> SOP f xss -> SOP g xss -> r #
ccompare_SOP :: forall {k} (c :: k -> Constraint) proxy r (f :: k -> Type) (g :: k -> Type) (xss :: [[k]]). All2 c xss => proxy c -> r -> (forall (xs :: [k]). All c xs => NP f xs -> NP g xs -> r) -> r -> SOP f xss -> SOP g xss -> r #
cliftA2'_NS :: forall {k} (c :: k -> Constraint) (xss :: [[k]]) proxy f g h. All2 c xss => proxy c -> (forall (xs :: [k]). All c xs => f xs -> g xs -> h xs) -> NP f xss -> NS g xss -> NS h xss #
ana_NS :: forall {k} s f (xs :: [k]). SListI xs => (forall r. s ('[] :: [k]) -> r) -> (forall (y :: k) (ys :: [k]). s (y ': ys) -> Either (f y) (s ys)) -> s xs -> NS f xs #
apInjs'_NP :: forall {k} (xs :: [k]) (f :: k -> Type). SListI xs => NP f xs -> NP (K (NS f xs) :: k -> Type) xs #
apInjs'_POP :: forall {k} (xss :: [[k]]) (f :: k -> Type). SListI xss => POP f xss -> NP (K (SOP f xss) :: [k] -> Type) xss #
ap_NS :: forall {k} (f :: k -> Type) (g :: k -> Type) (xs :: [k]). NP (f -.-> g) xs -> NS f xs -> NS g xs #
ap_SOP :: forall {k} (f :: k -> Type) (g :: k -> Type) (xss :: [[k]]). POP (f -.-> g) xss -> SOP f xss -> SOP g xss #
cana_NS :: forall {k} c proxy s f (xs :: [k]). All c xs => proxy c -> (forall r. s ('[] :: [k]) -> r) -> (forall (y :: k) (ys :: [k]). c y => s (y ': ys) -> Either (f y) (s ys)) -> s xs -> NS f xs #
cata_NS :: forall {k} r f (xs :: [k]). (forall (y :: k) (ys :: [k]). f y -> r (y ': ys)) -> (forall (y :: k) (ys :: [k]). r ys -> r (y ': ys)) -> NS f xs -> r xs #
ccata_NS :: forall {k} c proxy r f (xs :: [k]). All c xs => proxy c -> (forall (y :: k) (ys :: [k]). c y => f y -> r (y ': ys)) -> (forall (y :: k) (ys :: [k]). c y => r ys -> r (y ': ys)) -> NS f xs -> r xs #
cexpand_NS :: forall {k} c proxy f (xs :: [k]). All c xs => proxy c -> (forall (x :: k). c x => f x) -> NS f xs -> NP f xs #
cexpand_SOP :: forall {k} c proxy f (xss :: [[k]]). All2 c xss => proxy c -> (forall (x :: k). c x => f x) -> SOP f xss -> POP f xss #
cfoldMap_NS :: forall {k} c proxy f (xs :: [k]) m. All c xs => proxy c -> (forall (a :: k). c a => f a -> m) -> NS f xs -> m #
cfoldMap_SOP :: forall {k} c (xs :: [[k]]) m proxy f. (All2 c xs, Monoid m) => proxy c -> (forall (a :: k). c a => f a -> m) -> SOP f xs -> m #
cliftA2_NS :: forall {k} c (xs :: [k]) proxy f g h. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> NP f xs -> NS g xs -> NS h xs #
cliftA2_SOP :: forall {k} c (xss :: [[k]]) proxy f g h. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> POP f xss -> SOP g xss -> SOP h xss #
cliftA_NS :: forall {k} c (xs :: [k]) proxy f g. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a) -> NS f xs -> NS g xs #
cliftA_SOP :: forall {k} c (xss :: [[k]]) proxy f g. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a) -> SOP f xss -> SOP g xss #
cmap_NS :: forall {k} c (xs :: [k]) proxy f g. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a) -> NS f xs -> NS g xs #
cmap_SOP :: forall {k} c (xss :: [[k]]) proxy f g. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a) -> SOP f xss -> SOP g xss #
coerce_NS :: forall {k1} {k2} (f :: k1 -> Type) (g :: k2 -> Type) (xs :: [k1]) (ys :: [k2]). AllZip (LiftedCoercible f g) xs ys => NS f xs -> NS g ys #
coerce_SOP :: forall {k1} {k2} (f :: k1 -> Type) (g :: k2 -> Type) (xss :: [[k1]]) (yss :: [[k2]]). AllZip2 (LiftedCoercible f g) xss yss => SOP f xss -> SOP g yss #
collapse_NS :: forall {k} a (xs :: [k]). NS (K a :: k -> Type) xs -> a #
collapse_SOP :: forall {k} (xss :: [[k]]) a. SListI xss => SOP (K a :: k -> Type) xss -> [a] #
ctraverse'_NS :: forall {k} c proxy (xs :: [k]) f f' g. (All c xs, Functor g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #
ctraverse'_SOP :: forall {k} c (xss :: [[k]]) g proxy f f'. (All2 c xss, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> SOP f xss -> g (SOP f' xss) #
ctraverse_NS :: forall c (xs :: [Type]) g proxy f. (All c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> NP f xs -> g (NP I xs) #
ctraverse_SOP :: forall c (xs :: [[Type]]) g proxy f. (All2 c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> POP f xs -> g (POP I xs) #
ctraverse__NS :: forall {k} c proxy (xs :: [k]) f g. All c xs => proxy c -> (forall (a :: k). c a => f a -> g ()) -> NS f xs -> g () #
ctraverse__SOP :: forall {k} c proxy (xss :: [[k]]) f g. (All2 c xss, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> SOP f xss -> g () #
expand_SOP :: forall {k} f (xss :: [[k]]). All (SListI :: [k] -> Constraint) xss => (forall (x :: k). f x) -> SOP f xss -> POP f xss #
fromI_NS :: forall {k} (f :: k -> Type) (xs :: [Type]) (ys :: [k]). AllZip (LiftedCoercible I f) xs ys => NS I xs -> NS f ys #
fromI_SOP :: forall {k} (f :: k -> Type) (xss :: [[Type]]) (yss :: [[k]]). AllZip2 (LiftedCoercible I f) xss yss => SOP I xss -> SOP f yss #
liftA2_NS :: forall {k} (xs :: [k]) f g h. SListI xs => (forall (a :: k). f a -> g a -> h a) -> NP f xs -> NS g xs -> NS h xs #
liftA2_SOP :: forall {k} (xss :: [[k]]) f g h. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a -> h a) -> POP f xss -> SOP g xss -> SOP h xss #
liftA_NS :: forall {k} (xs :: [k]) f g. SListI xs => (forall (a :: k). f a -> g a) -> NS f xs -> NS g xs #
liftA_SOP :: forall {k} (xss :: [[k]]) f g. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a) -> SOP f xss -> SOP g xss #
map_NS :: forall {k} (xs :: [k]) f g. SListI xs => (forall (a :: k). f a -> g a) -> NS f xs -> NS g xs #
map_SOP :: forall {k} (xss :: [[k]]) f g. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a) -> SOP f xss -> SOP g xss #
sequence'_NS :: forall {k} f (g :: k -> Type) (xs :: [k]). Applicative f => NS (f :.: g) xs -> f (NS g xs) #
sequence'_SOP :: forall {k} (xss :: [[k]]) f (g :: k -> Type). (SListI xss, Applicative f) => SOP (f :.: g) xss -> f (SOP g xss) #
sequence_SOP :: forall (xss :: [[Type]]) f. (All (SListI :: [Type] -> Constraint) xss, Applicative f) => SOP f xss -> f (SOP I xss) #
toI_NS :: forall {k} (f :: k -> Type) (xs :: [k]) (ys :: [Type]). AllZip (LiftedCoercible f I) xs ys => NS f xs -> NS I ys #
toI_SOP :: forall {k} (f :: k -> Type) (xss :: [[k]]) (yss :: [[Type]]). AllZip2 (LiftedCoercible f I) xss yss => SOP f xss -> SOP I yss #
trans_NS :: forall {k1} {k2} c (xs :: [k1]) (ys :: [k2]) proxy f g. AllZip c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> NS f xs -> NS g ys #
trans_SOP :: forall {k1} {k2} c (xss :: [[k1]]) (yss :: [[k2]]) proxy f g. AllZip2 c xss yss => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> SOP f xss -> SOP g yss #
traverse'_NS :: forall {k} (xs :: [k]) f f' g. (SListI xs, Functor g) => (forall (a :: k). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #
traverse'_SOP :: forall {k} (xss :: [[k]]) g f f'. (SListI2 xss, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> SOP f xss -> g (SOP f' xss) #
traverse__NS :: forall {k} (xs :: [k]) f g. SListI xs => (forall (a :: k). f a -> g ()) -> NS f xs -> g () #
traverse__SOP :: forall {k} (xss :: [[k]]) f g. (SListI2 xss, Applicative g) => (forall (a :: k). f a -> g ()) -> SOP f xss -> g () #