Safe Haskell | None |
---|---|
Language | Haskell2010 |
Generics.SOP.Classes
Documentation
class HPure (h :: (k -> Type) -> l -> Type) where #
Methods
hpure :: forall (xs :: l) f. SListIN h xs => (forall (a :: k). f a) -> h f xs #
hcpure :: forall c (xs :: l) proxy f. AllN h c xs => proxy c -> (forall (a :: k). c a => f a) -> h f xs #
newtype ((f :: k -> Type) -.-> (g :: k -> Type)) (a :: k) #
Instances
Generic ((f -.-> g) a) Source # | |||||
HasDatatypeInfo ((f -.-> g) a) Source # | |||||
Defined in Generics.SOP.Instances Associated Types
Methods datatypeInfo :: proxy ((f -.-> g) a) -> DatatypeInfo (Code ((f -.-> g) a)) Source # | |||||
type Code ((f -.-> g) a) Source # | |||||
Defined in Generics.SOP.Instances | |||||
type DatatypeInfoOf ((f -.-> g) a) Source # | |||||
Defined in Generics.SOP.Instances type DatatypeInfoOf ((f -.-> g) a) = 'Newtype "Data.SOP.Classes" "-.->" ('Record "Fn" '['FieldInfo "apFn"]) |
fn_3 :: forall {k} f (a :: k) f' f'' f'''. (f a -> f' a -> f'' a -> f''' a) -> (f -.-> (f' -.-> (f'' -.-> f'''))) a #
fn_4 :: forall {k} f (a :: k) f' f'' f''' f''''. (f a -> f' a -> f'' a -> f''' a -> f'''' a) -> (f -.-> (f' -.-> (f'' -.-> (f''' -.-> f'''')))) a #
type family Prod (h :: (k -> Type) -> l -> Type) :: (k -> Type) -> l -> Type #
Instances
type Prod (POP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NP | |
type Prod (SOP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS | |
type Prod (NP :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NP | |
type Prod (NS :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS |
class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp (h :: (k -> Type) -> l -> Type) where #
Methods
hap :: forall (f :: k -> Type) (g :: k -> Type) (xs :: l). Prod h (f -.-> g) xs -> h f xs -> h g xs #
hliftA :: forall {k} {l} h (xs :: l) f f'. (SListIN (Prod h) xs, HAp h) => (forall (a :: k). f a -> f' a) -> h f xs -> h f' xs #
hliftA2 :: forall {k} {l} h (xs :: l) f f' f''. (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #
hliftA3 :: forall {k} {l} h (xs :: l) f f' f'' f'''. (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #
hcliftA :: forall {k} {l} h c (xs :: l) proxy f f'. (AllN (Prod h) c xs, HAp h) => proxy c -> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs #
hcliftA2 :: forall {k} {l} h c (xs :: l) proxy f f' f''. (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #
hcliftA3 :: forall {k} {l} h c (xs :: l) proxy f f' f'' f'''. (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #
hmap :: forall {k} {l} h (xs :: l) f f'. (SListIN (Prod h) xs, HAp h) => (forall (a :: k). f a -> f' a) -> h f xs -> h f' xs #
hzipWith :: forall {k} {l} h (xs :: l) f f' f''. (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #
hzipWith3 :: forall {k} {l} h (xs :: l) f f' f'' f'''. (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #
hcmap :: forall {k} {l} h c (xs :: l) proxy f f'. (AllN (Prod h) c xs, HAp h) => proxy c -> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs #
hczipWith :: forall {k} {l} h c (xs :: l) proxy f f' f''. (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #
hczipWith3 :: forall {k} {l} h c (xs :: l) proxy f f' f'' f'''. (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #
type family UnProd (h :: (k -> Type) -> l -> Type) :: (k -> Type) -> l -> Type #
Instances
type UnProd (POP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS | |
type UnProd (NP :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS |
class UnProd (Prod h) ~ h => HApInjs (h :: (k -> Type) -> l -> Type) where #
type family CollapseTo (h :: (k -> Type) -> l -> Type) x #
Instances
type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a | |
Defined in Data.SOP.NP | |
type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a | |
Defined in Data.SOP.NS | |
type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a | |
Defined in Data.SOP.NP | |
type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a | |
Defined in Data.SOP.NS |
class HCollapse (h :: (k -> Type) -> l -> Type) where #
Methods
hcollapse :: forall (xs :: l) a. SListIN h xs => h (K a :: k -> Type) xs -> CollapseTo h a #
Instances
HCollapse (POP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NP | |
HCollapse (SOP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NS | |
HCollapse (NP :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NP | |
HCollapse (NS :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NS |
class HTraverse_ (h :: (k -> Type) -> l -> Type) where #
Methods
hctraverse_ :: forall c (xs :: l) g proxy f. (AllN h c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> h f xs -> g () #
htraverse_ :: forall (xs :: l) g f. (SListIN h xs, Applicative g) => (forall (a :: k). f a -> g ()) -> h f xs -> g () #
Instances
HTraverse_ (POP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NP Methods hctraverse_ :: forall c (xs :: [[k]]) g proxy f. (AllN (POP :: (k -> Type) -> [[k]] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> POP f xs -> g () # htraverse_ :: forall (xs :: [[k]]) g f. (SListIN (POP :: (k -> Type) -> [[k]] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g ()) -> POP f xs -> g () # | |
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 () # | |
HTraverse_ (NP :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NP Methods hctraverse_ :: forall c (xs :: [k]) g proxy f. (AllN (NP :: (k -> Type) -> [k] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> NP f xs -> g () # htraverse_ :: forall (xs :: [k]) g f. (SListIN (NP :: (k -> Type) -> [k] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g ()) -> NP f xs -> g () # | |
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 () # |
hcfoldMap :: forall {k} {l} h c (xs :: l) m proxy f. (HTraverse_ h, AllN h c xs, Monoid m) => proxy c -> (forall (a :: k). c a => f a -> m) -> h f xs -> m #
hcfor_ :: forall {k} {l} h c (xs :: l) g proxy f. (HTraverse_ h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall (a :: k). c a => f a -> g ()) -> g () #
class HAp h => HSequence (h :: (k -> Type) -> l -> Type) where #
Methods
hsequence' :: forall (xs :: l) f (g :: k -> Type). (SListIN h xs, Applicative f) => h (f :.: g) xs -> f (h g xs) #
hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN h c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> h f xs -> g (h f' xs) #
htraverse' :: forall (xs :: l) g f f'. (SListIN h xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> h f xs -> g (h f' xs) #
Instances
HSequence (POP :: (k -> Type) -> [[k]] -> Type) | |
Defined in Data.SOP.NP Methods hsequence' :: forall (xs :: [[k]]) f (g :: k -> Type). (SListIN (POP :: (k -> Type) -> [[k]] -> Type) xs, Applicative f) => POP (f :.: g) xs -> f (POP g xs) # hctraverse' :: forall c (xs :: [[k]]) g proxy f f'. (AllN (POP :: (k -> Type) -> [[k]] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> POP f xs -> g (POP f' xs) # htraverse' :: forall (xs :: [[k]]) g f f'. (SListIN (POP :: (k -> Type) -> [[k]] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> POP f xs -> g (POP f' xs) # | |
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) # | |
HSequence (NP :: (k -> Type) -> [k] -> Type) | |
Defined in Data.SOP.NP Methods hsequence' :: forall (xs :: [k]) f (g :: k -> Type). (SListIN (NP :: (k -> Type) -> [k] -> Type) xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) # hctraverse' :: forall c (xs :: [k]) g proxy f f'. (AllN (NP :: (k -> Type) -> [k] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) # htraverse' :: forall (xs :: [k]) g f f'. (SListIN (NP :: (k -> Type) -> [k] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) # | |
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) # |
hsequence :: forall {l} h (xs :: l) f. (SListIN h xs, SListIN (Prod h) xs, HSequence h, Applicative f) => h f xs -> f (h I xs) #
hsequenceK :: forall {k} {l} h (xs :: l) f a. (SListIN h xs, SListIN (Prod h) xs, Applicative f, HSequence h) => h (K (f a) :: k -> Type) xs -> f (h (K a :: k -> Type) xs) #
hctraverse :: forall {l} h c (xs :: l) g proxy f. (HSequence h, AllN h c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> h f xs -> g (h I xs) #
hcfor :: forall {l} h c (xs :: l) g proxy f. (HSequence h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall a. c a => f a -> g a) -> g (h I xs) #
class HExpand (h :: (k -> Type) -> l -> Type) where #
Methods
hexpand :: forall (xs :: l) f. SListIN (Prod h) xs => (forall (x :: k). f x) -> h f xs -> Prod h f xs #
hcexpand :: forall c (xs :: l) proxy f. AllN (Prod h) c xs => proxy c -> (forall (x :: k). c x => f x) -> h f xs -> Prod h f xs #
Instances
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 # | |
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 # |
class ((Same h1 :: (k2 -> Type) -> l2 -> Type) ~ h2, (Same h2 :: (k1 -> Type) -> l1 -> Type) ~ h1) => HTrans (h1 :: (k1 -> Type) -> l1 -> Type) (h2 :: (k2 -> Type) -> l2 -> Type) where #
Methods
htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod h1) c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> h1 f xs -> h2 g ys #
hcoerce :: forall (f :: k1 -> Type) (g :: k2 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod h1) (LiftedCoercible f g) xs ys => h1 f xs -> h2 g ys #
Instances
HTrans (POP :: (k1 -> Type) -> [[k1]] -> Type) (POP :: (k2 -> Type) -> [[k2]] -> Type) | |
Defined in Data.SOP.NP Methods htrans :: forall c (xs :: [[k1]]) (ys :: [[k2]]) proxy f g. AllZipN (Prod (POP :: (k1 -> Type) -> [[k1]] -> Type)) c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> POP f xs -> POP g ys # hcoerce :: forall (f :: k1 -> Type) (g :: k2 -> Type) (xs :: [[k1]]) (ys :: [[k2]]). AllZipN (Prod (POP :: (k1 -> Type) -> [[k1]] -> Type)) (LiftedCoercible f g) xs ys => POP f xs -> POP g ys # | |
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 # | |
HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) | |
Defined in Data.SOP.NP Methods htrans :: forall c (xs :: [k1]) (ys :: [k2]) proxy f g. AllZipN (Prod (NP :: (k1 -> Type) -> [k1] -> Type)) c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> NP f xs -> NP g ys # hcoerce :: forall (f :: k1 -> Type) (g :: k2 -> Type) (xs :: [k1]) (ys :: [k2]). AllZipN (Prod (NP :: (k1 -> Type) -> [k1] -> Type)) (LiftedCoercible f g) xs ys => NP f xs -> NP g ys # | |
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 # |
hfromI :: forall {l1} {k2} {l2} h1 (f :: k2 -> Type) (xs :: l1) (ys :: l2) h2. (AllZipN (Prod h1) (LiftedCoercible I f) xs ys, HTrans h1 h2) => h1 I xs -> h2 f ys #
htoI :: forall {k1} {l1} {l2} h1 (f :: k1 -> Type) (xs :: l1) (ys :: l2) h2. (AllZipN (Prod h1) (LiftedCoercible f I) xs ys, HTrans h1 h2) => h1 f xs -> h2 I ys #
type family Same (h :: (k1 -> Type) -> l1 -> Type) :: (k2 -> Type) -> l2 -> Type #
Instances
type Same (POP :: (k1 -> Type) -> [[k1]] -> Type) | |
Defined in Data.SOP.NP | |
type Same (SOP :: (k1 -> Type) -> [[k1]] -> Type) | |
Defined in Data.SOP.NS | |
type Same (NP :: (k1 -> Type) -> [k1] -> Type) | |
Defined in Data.SOP.NP | |
type Same (NS :: (k1 -> Type) -> [k1] -> Type) | |
Defined in Data.SOP.NS |