Safe Haskell | None |
---|---|
Language | Haskell2010 |
Main module of sop-core
Synopsis
- data NP :: (k -> Type) -> [k] -> Type where
- data NS :: (k -> Type) -> [k] -> Type where
- newtype SOP (f :: k -> Type) (xss :: [[k]]) = SOP (NS (NP f) xss)
- unSOP :: SOP f xss -> NS (NP f) xss
- newtype POP (f :: k -> Type) (xss :: [[k]]) = POP (NP (NP f) xss)
- unPOP :: POP f xss -> NP (NP f) xss
- class HPure (h :: (k -> Type) -> l -> Type) where
- hd :: NP f (x ': xs) -> f x
- tl :: NP f (x ': xs) -> NP f xs
- type Projection (f :: k -> Type) (xs :: [k]) = K (NP f xs) -.-> f
- projections :: forall xs f. SListI xs => NP (Projection f xs) xs
- shiftProjection :: Projection f xs a -> Projection f (x ': xs) a
- newtype (f -.-> g) a = Fn {
- apFn :: f a -> g a
- fn :: (f a -> f' a) -> (f -.-> f') a
- fn_2 :: (f a -> f' a -> f'' a) -> (f -.-> (f' -.-> f'')) a
- fn_3 :: (f a -> f' a -> f'' a -> f''' a) -> (f -.-> (f' -.-> (f'' -.-> f'''))) a
- fn_4 :: (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
- class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp (h :: (k -> Type) -> l -> Type) where
- hliftA :: (SListIN (Prod h) xs, HAp h) => (forall a. f a -> f' a) -> h f xs -> h f' xs
- hliftA2 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hliftA3 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs
- hcliftA :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs
- hcliftA2 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall a. c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hcliftA3 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall a. 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 :: (SListIN (Prod h) xs, HAp h) => (forall a. f a -> f' a) -> h f xs -> h f' xs
- hzipWith :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hzipWith3 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs
- hcmap :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs
- hczipWith :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall a. c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hczipWith3 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall a. 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 Injection (f :: k -> Type) (xs :: [k]) = f -.-> K (NS f xs)
- injections :: forall xs f. SListI xs => NP (Injection f xs) xs
- shift :: Injection f xs a -> Injection f (x ': xs) a
- shiftInjection :: Injection f xs a -> Injection f (x ': xs) a
- type family UnProd (h :: (k -> Type) -> l -> Type) :: (k -> Type) -> l -> Type
- class UnProd (Prod h) ~ h => HApInjs (h :: (k -> Type) -> l -> Type) where
- apInjs_NP :: SListI xs => NP f xs -> [NS f xs]
- apInjs_POP :: SListI xss => POP f xss -> [SOP f xss]
- unZ :: NS f '[x] -> f x
- class HIndex (h :: (k -> Type) -> l -> Type) where
- hcliftA' :: (All2 c xss, Prod h ~ NP, HAp h) => proxy c -> (forall xs. All c xs => f xs -> f' xs) -> h f xss -> h f' xss
- hcliftA2' :: (All2 c xss, Prod h ~ NP, HAp h) => proxy c -> (forall xs. All c xs => f xs -> f' xs -> f'' xs) -> Prod h f xss -> h f' xss -> h f'' xss
- hcliftA3' :: (All2 c xss, Prod h ~ NP, HAp h) => proxy c -> (forall xs. All c xs => f xs -> f' xs -> f'' xs -> f''' xs) -> Prod h f xss -> Prod h f' xss -> h f'' xss -> h f''' xss
- compare_NS :: forall r f g xs. r -> (forall x. f x -> g x -> r) -> r -> NS f xs -> NS g xs -> r
- ccompare_NS :: forall c proxy r f g xs. All c xs => proxy c -> r -> (forall x. c x => f x -> g x -> r) -> r -> NS f xs -> NS g xs -> r
- compare_SOP :: forall r f g xss. r -> (forall xs. NP f xs -> NP g xs -> r) -> r -> SOP f xss -> SOP g xss -> r
- ccompare_SOP :: forall c proxy r f g xss. All2 c xss => proxy c -> r -> (forall xs. All c xs => NP f xs -> NP g xs -> r) -> r -> SOP f xss -> SOP g xss -> r
- type family CollapseTo (h :: (k -> Type) -> l -> Type) (x :: Type) :: Type
- class HCollapse (h :: (k -> Type) -> l -> Type) where
- hcollapse :: SListIN h xs => h (K a) xs -> CollapseTo h a
- class HTraverse_ (h :: (k -> Type) -> l -> Type) where
- hctraverse_ :: (AllN h c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> h f xs -> g ()
- htraverse_ :: (SListIN h xs, Applicative g) => (forall a. f a -> g ()) -> h f xs -> g ()
- hcfoldMap :: (HTraverse_ h, AllN h c xs, Monoid m) => proxy c -> (forall a. c a => f a -> m) -> h f xs -> m
- hcfor_ :: (HTraverse_ h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall a. c a => f a -> g ()) -> g ()
- class HAp h => HSequence (h :: (k -> Type) -> l -> Type) where
- hsequence' :: (SListIN h xs, Applicative f) => h (f :.: g) xs -> f (h g xs)
- hctraverse' :: (AllN h c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> h f xs -> g (h f' xs)
- htraverse' :: (SListIN h xs, Applicative g) => (forall a. f a -> g (f' a)) -> h f xs -> g (h f' xs)
- hsequence :: (SListIN h xs, SListIN (Prod h) xs, HSequence h) => Applicative f => h f xs -> f (h I xs)
- hsequenceK :: (SListIN h xs, SListIN (Prod h) xs, Applicative f, HSequence h) => h (K (f a)) xs -> f (h (K a) xs)
- hctraverse :: (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 :: (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
- class (Same h1 ~ h2, Same h2 ~ h1) => HTrans (h1 :: (k1 -> Type) -> l1 -> Type) (h2 :: (k2 -> Type) -> l2 -> Type) where
- hfromI :: (AllZipN (Prod h1) (LiftedCoercible I f) xs ys, HTrans h1 h2) => h1 I xs -> h2 f ys
- htoI :: (AllZipN (Prod h1) (LiftedCoercible f I) xs ys, HTrans h1 h2) => h1 f xs -> h2 I ys
- fromList :: SListI xs => [a] -> Maybe (NP (K a) xs)
- newtype K (a :: Type) (b :: k) = K a
- unK :: K a b -> a
- newtype I (a :: Type) = I a
- unI :: I a -> a
- newtype ((f :: l -> Type) :.: (g :: k -> l)) (p :: k) = Comp (f (g p))
- unComp :: (f :.: g) p -> f (g p)
- mapII :: (a -> b) -> I a -> I b
- mapIK :: (a -> b) -> I a -> K b c
- mapKI :: (a -> b) -> K a c -> I b
- mapKK :: (a -> b) -> K a c -> K b d
- mapIII :: (a -> b -> c) -> I a -> I b -> I c
- mapIIK :: (a -> b -> c) -> I a -> I b -> K c d
- mapIKI :: (a -> b -> c) -> I a -> K b d -> I c
- mapIKK :: (a -> b -> c) -> I a -> K b d -> K c e
- mapKII :: (a -> b -> c) -> K a d -> I b -> I c
- mapKIK :: (a -> b -> c) -> K a d -> I b -> K c e
- mapKKI :: (a -> b -> c) -> K a d -> K b e -> I c
- mapKKK :: (a -> b -> c) -> K a d -> K b e -> K c f
- class (AllF c xs, SListI xs) => All (c :: k -> Constraint) (xs :: [k])
- type All2 c = All (All c)
- cpara_SList :: All c xs => proxy c -> r '[] -> (forall y ys. (c y, All c ys) => r ys -> r (y ': ys)) -> r xs
- ccase_SList :: All c xs => proxy c -> r '[] -> (forall y ys. (c y, All c ys) => r (y ': ys)) -> r xs
- class (SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b])
- class (AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 f xss yss
- type family AllN (h :: (k -> Type) -> l -> Type) (c :: k -> Constraint) :: l -> Constraint
- type family AllZipN (h :: (k -> Type) -> l -> Type) (c :: k1 -> k2 -> Constraint) :: l1 -> l2 -> Constraint
- class f (g x) => Compose f g x
- class (f x, g x) => And f g x
- class Top x
- class Coercible (f x) (g y) => LiftedCoercible f g x y
- type family SameShapeAs (xs :: [a]) (ys :: [b]) :: Constraint where ...
- data SList :: [k] -> Type where
- type SListI = All Top
- type SListI2 = All SListI
- sList :: SListI xs => SList xs
- para_SList :: SListI xs => r '[] -> (forall y ys. SListI ys => r ys -> r (y ': ys)) -> r xs
- case_SList :: SListI xs => r '[] -> (forall y ys. SListI ys => r (y ': ys)) -> r xs
- data Shape :: [k] -> Type where
- shape :: forall k (xs :: [k]). SListI xs => Shape xs
- lengthSList :: forall k (xs :: [k]) proxy. SListI xs => proxy xs -> Int
- data Proxy (t :: k) = Proxy
n-ary datatypes
data NP :: (k -> Type) -> [k] -> Type where Source #
An n-ary product.
The product is parameterized by a type constructor f
and
indexed by a type-level list xs
. The length of the list
determines the number of elements in the product, and if the
i
-th element of the list is of type x
, then the i
-th
element of the product is of type f x
.
The constructor names are chosen to resemble the names of the list constructors.
Two common instantiations of f
are the identity functor I
and the constant functor K
. For I
, the product becomes a
heterogeneous list, where the type-level list describes the
types of its components. For
, the product becomes a
homogeneous list, where the contents of the type-level list are
ignored, but its length still specifies the number of elements.K
a
In the context of the SOP approach to generic programming, an n-ary product describes the structure of the arguments of a single data constructor.
Examples:
I 'x' :* I True :* Nil :: NP I '[ Char, Bool ] K 0 :* K 1 :* Nil :: NP (K Int) '[ Char, Bool ] Just 'x' :* Nothing :* Nil :: NP Maybe '[ Char, Bool ]
Instances
HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) Source # | |
Defined in Data.SOP.NP htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys Source # hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod NP) (LiftedCoercible f g) xs ys => NP f xs -> NP g ys Source # | |
HSequence (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) Source # hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) Source # htraverse' :: forall (xs :: l) g f f'. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) Source # | |
HTraverse_ (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () Source # htraverse_ :: forall (xs :: l) g f. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () Source # | |
HCollapse (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP | |
HAp (NP :: (k -> Type) -> [k] -> Type) Source # | |
HPure (NP :: (k -> Type) -> [k] -> Type) Source # | |
All (Compose Eq f) xs => Eq (NP f xs) Source # | |
(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NP f xs) Source # | |
All (Compose Show f) xs => Show (NP f xs) Source # | |
All (Compose Semigroup f) xs => Semigroup (NP f xs) Source # | Since: 0.4.0.0 |
(All (Compose Monoid f) xs, All (Compose Semigroup f) xs) => Monoid (NP f xs) Source # | Since: 0.4.0.0 |
All (Compose NFData f) xs => NFData (NP f xs) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.NP | |
type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) Source # | |
Defined in Data.SOP.NP | |
type Same (NP :: (k1 -> Type) -> [k1] -> Type) Source # | |
type SListIN (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP | |
type UnProd (NP :: (k -> Type) -> [k] -> Type) Source # | |
type Prod (NP :: (k -> Type) -> [k] -> Type) Source # | |
type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NP | |
type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a Source # | |
Defined in Data.SOP.NP |
data NS :: (k -> Type) -> [k] -> Type where Source #
An n-ary sum.
The sum is parameterized by a type constructor f
and
indexed by a type-level list xs
. The length of the list
determines the number of choices in the sum and if the
i
-th element of the list is of type x
, then the i
-th
choice of the sum is of type f x
.
The constructor names are chosen to resemble Peano-style
natural numbers, i.e., Z
is for "zero", and S
is for
"successor". Chaining S
and Z
chooses the corresponding
component of the sum.
Examples:
Z :: f x -> NS f (x ': xs) S . Z :: f y -> NS f (x ': y ': xs) S . S . Z :: f z -> NS f (x ': y ': z ': xs) ...
Note that empty sums (indexed by an empty list) have no non-bottom elements.
Two common instantiations of f
are the identity functor I
and the constant functor K
. For I
, the sum becomes a
direct generalization of the Either
type to arbitrarily many
choices. For
, the result is a homogeneous choice type,
where the contents of the type-level list are ignored, but its
length specifies the number of options.K
a
In the context of the SOP approach to generic programming, an n-ary sum describes the top-level structure of a datatype, which is a choice between all of its constructors.
Examples:
Z (I 'x') :: NS I '[ Char, Bool ] S (Z (I True)) :: NS I '[ Char, Bool ] S (Z (K 1)) :: NS (K Int) '[ Char, Bool ]
Instances
HTrans (NS :: (k1 -> Type) -> [k1] -> Type) (NS :: (k2 -> Type) -> [k2] -> Type) Source # | |
Defined in Data.SOP.NS htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NS) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys Source # hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod NS) (LiftedCoercible f g) xs ys => NS f xs -> NS g ys Source # | |
HExpand (NS :: (k -> Type) -> [k] -> Type) Source # | |
HApInjs (NS :: (k -> Type) -> [k] -> Type) Source # | |
HIndex (NS :: (k -> Type) -> [k] -> Type) Source # | |
HSequence (NS :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NS hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) Source # hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) Source # htraverse' :: forall (xs :: l) g f f'. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) Source # | |
HTraverse_ (NS :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NS hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () Source # htraverse_ :: forall (xs :: l) g f. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NS f xs -> g () Source # | |
HCollapse (NS :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NS | |
HAp (NS :: (k -> Type) -> [k] -> Type) Source # | |
All (Compose Eq f) xs => Eq (NS f xs) Source # | |
(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NS f xs) Source # | |
All (Compose Show f) xs => Show (NS f xs) Source # | |
All (Compose NFData f) xs => NFData (NS f xs) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.NS | |
type Same (NS :: (k1 -> Type) -> [k1] -> Type) Source # | |
type SListIN (NS :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NS | |
type Prod (NS :: (k -> Type) -> [k] -> Type) Source # | |
type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NS | |
type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a Source # | |
Defined in Data.SOP.NS |
newtype SOP (f :: k -> Type) (xss :: [[k]]) Source #
A sum of products.
This is a 'newtype' for an NS
of an NP
. The elements of the
(inner) products are applications of the parameter f
. The type
SOP
is indexed by the list of lists that determines the sizes
of both the (outer) sum and all the (inner) products, as well as
the types of all the elements of the inner products.
A
reflects the structure of a normal Haskell datatype.
The sum structure represents the choice between the different
constructors, the product structure represents the arguments of
each constructor.SOP
I
Instances
HTrans (SOP :: (k1 -> Type) -> [[k1]] -> Type) (SOP :: (k2 -> Type) -> [[k2]] -> Type) Source # | |
Defined in Data.SOP.NS htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod SOP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> SOP f xs -> SOP g ys Source # hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod SOP) (LiftedCoercible f g) xs ys => SOP f xs -> SOP g ys Source # | |
HExpand (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
HApInjs (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
HIndex (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
HSequence (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NS hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN SOP xs, Applicative f) => SOP (f :.: g) xs -> f (SOP g xs) Source # hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) Source # htraverse' :: forall (xs :: l) g f f'. (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) Source # | |
HTraverse_ (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NS hctraverse_ :: forall c (xs :: l) g proxy f. (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> SOP f xs -> g () Source # htraverse_ :: forall (xs :: l) g f. (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> SOP f xs -> g () Source # | |
HCollapse (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NS | |
HAp (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
Eq (NS (NP f) xss) => Eq (SOP f xss) Source # | |
Ord (NS (NP f) xss) => Ord (SOP f xss) Source # | |
Defined in Data.SOP.NS | |
Show (NS (NP f) xss) => Show (SOP f xss) Source # | |
NFData (NS (NP f) xss) => NFData (SOP f xss) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.NS | |
type Same (SOP :: (k1 -> Type) -> [[k1]] -> Type) Source # | |
type SListIN (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NS | |
type Prod (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
type AllN (SOP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NS | |
type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a Source # | |
Defined in Data.SOP.NS |
newtype POP (f :: k -> Type) (xss :: [[k]]) Source #
A product of products.
This is a 'newtype' for an NP
of an NP
. The elements of the
inner products are applications of the parameter f
. The type
POP
is indexed by the list of lists that determines the lengths
of both the outer and all the inner products, as well as the types
of all the elements of the inner products.
A POP
is reminiscent of a two-dimensional table (but the inner
lists can all be of different length). In the context of the SOP
approach to generic programming, a POP
is useful to represent
information that is available for all arguments of all constructors
of a datatype.
Instances
HTrans (POP :: (k1 -> Type) -> [[k1]] -> Type) (POP :: (k2 -> Type) -> [[k2]] -> Type) Source # | |
Defined in Data.SOP.NP htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod POP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> POP f xs -> POP g ys Source # hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod POP) (LiftedCoercible f g) xs ys => POP f xs -> POP g ys Source # | |
HSequence (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN POP xs, Applicative f) => POP (f :.: g) xs -> f (POP g xs) Source # hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> POP f xs -> g (POP f' xs) Source # htraverse' :: forall (xs :: l) g f f'. (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> POP f xs -> g (POP f' xs) Source # | |
HTraverse_ (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP hctraverse_ :: forall c (xs :: l) g proxy f. (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> POP f xs -> g () Source # htraverse_ :: forall (xs :: l) g f. (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> POP f xs -> g () Source # | |
HCollapse (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP | |
HAp (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
HPure (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Eq (NP (NP f) xss) => Eq (POP f xss) Source # | |
Ord (NP (NP f) xss) => Ord (POP f xss) Source # | |
Defined in Data.SOP.NP | |
Show (NP (NP f) xss) => Show (POP f xss) Source # | |
Semigroup (NP (NP f) xss) => Semigroup (POP f xss) Source # | Since: 0.4.0.0 |
Monoid (NP (NP f) xss) => Monoid (POP f xss) Source # | Since: 0.4.0.0 |
NFData (NP (NP f) xss) => NFData (POP f xss) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.NP | |
type AllZipN (POP :: (k -> Type) -> [[k]] -> Type) (c :: a -> b -> Constraint) Source # | |
Defined in Data.SOP.NP | |
type Same (POP :: (k1 -> Type) -> [[k1]] -> Type) Source # | |
type SListIN (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP | |
type UnProd (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
type Prod (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
type AllN (POP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NP | |
type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a Source # | |
Defined in Data.SOP.NP |
Combinators
Constructing products
class HPure (h :: (k -> Type) -> l -> Type) where Source #
hpure :: SListIN h xs => (forall a. f a) -> h f xs Source #
Corresponds to pure
directly.
Instances:
hpure
,pure_NP
::SListI
xs => (forall a. f a) ->NP
f xshpure
,pure_POP
::SListI2
xss => (forall a. f a) ->POP
f xss
hcpure :: AllN h c xs => proxy c -> (forall a. c a => f a) -> h f xs Source #
A variant of hpure
that allows passing in a constrained
argument.
Calling
where hcpure
f ss :: h f xs
causes f
to be
applied at all the types that are contained in xs
. Therefore,
the constraint c
has to be satisfied for all elements of xs
,
which is what
states.AllN
h c xs
Instances:
hcpure
,cpure_NP
:: (All
c xs ) => proxy c -> (forall a. c a => f a) ->NP
f xshcpure
,cpure_POP
:: (All2
c xss) => proxy c -> (forall a. c a => f a) ->POP
f xss
Destructing products
type Projection (f :: k -> Type) (xs :: [k]) = K (NP f xs) -.-> f Source #
The type of projections from an n-ary product.
A projection is a function from the n-ary product to a single element.
projections :: forall xs f. SListI xs => NP (Projection f xs) xs Source #
Compute all projections from an n-ary product.
Each element of the resulting product contains one of the projections.
shiftProjection :: Projection f xs a -> Projection f (x ': xs) a Source #
Application
fn :: (f a -> f' a) -> (f -.-> f') a Source #
Construct a lifted function.
Same as Fn
. Only available for uniformity with the
higher-arity versions.
fn_2 :: (f a -> f' a -> f'' a) -> (f -.-> (f' -.-> f'')) a Source #
Construct a binary lifted function.
fn_3 :: (f a -> f' a -> f'' a -> f''' a) -> (f -.-> (f' -.-> (f'' -.-> f'''))) a Source #
Construct a ternary lifted function.
fn_4 :: (f a -> f' a -> f'' a -> f''' a -> f'''' a) -> (f -.-> (f' -.-> (f'' -.-> (f''' -.-> f'''')))) a Source #
Construct a quarternary lifted function.
type family Prod (h :: (k -> Type) -> l -> Type) :: (k -> Type) -> l -> Type Source #
Maps a structure containing sums to the corresponding product structure.
class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp (h :: (k -> Type) -> l -> Type) where Source #
A generalization of <*>
.
hap :: Prod h (f -.-> g) xs -> h f xs -> h g xs Source #
Corresponds to <*>
.
For products (NP
) as well as products of products
(POP
), the correspondence is rather direct. We combine
a structure containing (lifted) functions and a compatible structure
containing corresponding arguments into a compatible structure
containing results.
The same combinator can also be used to combine a product structure of functions with a sum structure of arguments, which then results in another sum structure of results. The sum structure determines which part of the product structure will be used.
Instances:
hap
,ap_NP
::NP
(f -.-> g) xs ->NP
f xs ->NP
g xshap
,ap_NS
::NP
(f -.-> g) xs ->NS
f xs ->NS
g xshap
,ap_POP
::POP
(f -.-> g) xss ->POP
f xss ->POP
g xsshap
,ap_SOP
::POP
(f -.-> g) xss ->SOP
f xss ->SOP
g xss
Lifting / mapping
hliftA :: (SListIN (Prod h) xs, HAp h) => (forall a. f a -> f' a) -> h f xs -> h f' xs Source #
A generalized form of liftA
,
which in turn is a generalized map
.
Takes a lifted function and applies it to every element of a structure while preserving its shape.
Specification:
hliftA
f xs =hpure
(fn
f) `hap
` xs
Instances:
hliftA
,liftA_NP
::SListI
xs => (forall a. f a -> f' a) ->NP
f xs ->NP
f' xshliftA
,liftA_NS
::SListI
xs => (forall a. f a -> f' a) ->NS
f xs ->NS
f' xshliftA
,liftA_POP
::SListI2
xss => (forall a. f a -> f' a) ->POP
f xss ->POP
f' xsshliftA
,liftA_SOP
::SListI2
xss => (forall a. f a -> f' a) ->SOP
f xss ->SOP
f' xss
hliftA2 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs Source #
A generalized form of liftA2
,
which in turn is a generalized zipWith
.
Takes a lifted binary function and uses it to combine two structures of equal shape into a single structure.
It either takes two product structures to a product structure, or one product and one sum structure to a sum structure.
Specification:
hliftA2
f xs ys =hpure
(fn_2
f) `hap
` xs `hap
` ys
Instances:
hliftA2
,liftA2_NP
::SListI
xs => (forall a. f a -> f' a -> f'' a) ->NP
f xs ->NP
f' xs ->NP
f'' xshliftA2
,liftA2_NS
::SListI
xs => (forall a. f a -> f' a -> f'' a) ->NP
f xs ->NS
f' xs ->NS
f'' xshliftA2
,liftA2_POP
::SListI2
xss => (forall a. f a -> f' a -> f'' a) ->POP
f xss ->POP
f' xss ->POP
f'' xsshliftA2
,liftA2_SOP
::SListI2
xss => (forall a. f a -> f' a -> f'' a) ->POP
f xss ->SOP
f' xss ->SOP
f'' xss
hliftA3 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs Source #
A generalized form of liftA3
,
which in turn is a generalized zipWith3
.
Takes a lifted ternary function and uses it to combine three structures of equal shape into a single structure.
It either takes three product structures to a product structure, or two product structures and one sum structure to a sum structure.
Specification:
hliftA3
f xs ys zs =hpure
(fn_3
f) `hap
` xs `hap
` ys `hap
` zs
Instances:
hliftA3
,liftA3_NP
::SListI
xs => (forall a. f a -> f' a -> f'' a -> f''' a) ->NP
f xs ->NP
f' xs ->NP
f'' xs ->NP
f''' xshliftA3
,liftA3_NS
::SListI
xs => (forall a. f a -> f' a -> f'' a -> f''' a) ->NP
f xs ->NP
f' xs ->NS
f'' xs ->NS
f''' xshliftA3
,liftA3_POP
::SListI2
xss => (forall a. f a -> f' a -> f'' a -> f''' a) ->POP
f xss ->POP
f' xss ->POP
f'' xss ->POP
f''' xshliftA3
,liftA3_SOP
::SListI2
xss => (forall a. f a -> f' a -> f'' a -> f''' a) ->POP
f xss ->POP
f' xss ->SOP
f'' xss ->SOP
f''' xs
hcliftA :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs Source #
hcliftA2 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall a. c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs Source #
hcliftA3 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall a. c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs Source #
hmap :: (SListIN (Prod h) xs, HAp h) => (forall a. f a -> f' a) -> h f xs -> h f' xs Source #
Another name for hliftA
.
Since: 0.2
hzipWith :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs Source #
Another name for hliftA2
.
Since: 0.2
hzipWith3 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs Source #
Another name for hliftA3
.
Since: 0.2
hcmap :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs Source #
Another name for hcliftA
.
Since: 0.2
hczipWith :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall a. c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs Source #
Another name for hcliftA2
.
Since: 0.2
hczipWith3 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall a. c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs Source #
Another name for hcliftA3
.
Since: 0.2
Constructing sums
type Injection (f :: k -> Type) (xs :: [k]) = f -.-> K (NS f xs) Source #
The type of injections into an n-ary sum.
If you expand the type synonyms and newtypes involved, you get
Injection f xs a = (f -.-> K (NS f xs)) a ~= f a -> K (NS f xs) a ~= f a -> NS f xs
If we pick a
to be an element of xs
, this indeed corresponds to an
injection into the sum.
injections :: forall xs f. SListI xs => NP (Injection f xs) xs Source #
Compute all injections into an n-ary sum.
Each element of the resulting product contains one of the injections.
shift :: Injection f xs a -> Injection f (x ': xs) a Source #
Deprecated: Use shiftInjection
instead.
Shift an injection.
Given an injection, return an injection into a sum that is one component larger.
shiftInjection :: Injection f xs a -> Injection f (x ': xs) a Source #
Shift an injection.
Given an injection, return an injection into a sum that is one component larger.
type family UnProd (h :: (k -> Type) -> l -> Type) :: (k -> Type) -> l -> Type Source #
Maps a structure containing products to the corresponding sum structure.
Since: 0.2.4.0
class UnProd (Prod h) ~ h => HApInjs (h :: (k -> Type) -> l -> Type) where Source #
A class for applying all injections corresponding to a sum-like structure to a table containing suitable arguments.
hapInjs :: SListIN h xs => Prod h f xs -> [h f xs] Source #
For a given table (product-like structure), produce a list where each element corresponds to the application of an injection function into the corresponding sum-like structure.
Instances:
hapInjs
,apInjs_NP
::SListI
xs =>NP
f xs -> [NS
f xs ]hapInjs
,apInjs_SOP
::SListI2
xss =>POP
f xs -> [SOP
f xss]
Examples:
>>>
hapInjs (I 'x' :* I True :* I 2 :* Nil) :: [NS I '[Char, Bool, Int]]
[Z (I 'x'),S (Z (I True)),S (S (Z (I 2)))]
>>>
hapInjs (POP ((I 'x' :* Nil) :* (I True :* I 2 :* Nil) :* Nil)) :: [SOP I '[ '[Char], '[Bool, Int]]]
[SOP (Z (I 'x' :* Nil)),SOP (S (Z (I True :* I 2 :* Nil)))]
Unfortunately the type-signatures are required in GHC-7.10 and older.
Since: 0.2.4.0
apInjs_NP :: SListI xs => NP f xs -> [NS f xs] Source #
Apply injections to a product.
Given a product containing all possible choices, produce a list of sums by applying each injection to the appropriate element.
Example:
>>>
apInjs_NP (I 'x' :* I True :* I 2 :* Nil)
[Z (I 'x'),S (Z (I True)),S (S (Z (I 2)))]
apInjs_POP :: SListI xss => POP f xss -> [SOP f xss] Source #
Apply injections to a product of product.
This operates on the outer product only. Given a product containing all possible choices (that are products), produce a list of sums (of products) by applying each injection to the appropriate element.
Example:
>>>
apInjs_POP (POP ((I 'x' :* Nil) :* (I True :* I 2 :* Nil) :* Nil))
[SOP (Z (I 'x' :* Nil)),SOP (S (Z (I True :* I 2 :* Nil)))]
Destructing sums
unZ :: NS f '[x] -> f x Source #
Extract the payload from a unary sum.
For larger sums, this function would be partial, so it is only provided with a rather restrictive type.
Example:
>>>
unZ (Z (I 'x'))
I 'x'
Since: 0.2.2.0
class HIndex (h :: (k -> Type) -> l -> Type) where Source #
A class for determining which choice in a sum-like structure a value represents.
hindex :: h f xs -> Int Source #
If h
is a sum-like structure representing a choice
between n
different options, and x
is a value of
type h f xs
, then
returns a number between
hindex
x0
and n - 1
representing the index of the choice
made by x
.
Instances:
hindex
,index_NS
::NS
f xs -> Inthindex
,index_SOP
::SOP
f xs -> Int
Examples:
>>>
hindex (S (S (Z (I False))))
2>>>
hindex (Z (K ()))
0>>>
hindex (SOP (S (Z (I True :* I 'x' :* Nil))))
1
Since: 0.2.4.0
Instances
Dealing with All
c
All
chcliftA' :: (All2 c xss, Prod h ~ NP, HAp h) => proxy c -> (forall xs. All c xs => f xs -> f' xs) -> h f xss -> h f' xss Source #
Lift a constrained function operating on a list-indexed structure to a function on a list-of-list-indexed structure.
This is a variant of hcliftA
.
Specification:
hcliftA'
p f xs =hpure
(fn_2
$ \AllDictC
-> f) `hap
`allDict_NP
p `hap
` xs
Instances:
hcliftA'
::All2
c xss => proxy c -> (forall xs.All
c xs => f xs -> f' xs) ->NP
f xss ->NP
f' xsshcliftA'
::All2
c xss => proxy c -> (forall xs.All
c xs => f xs -> f' xs) ->NS
f xss ->NS
f' xss
hcliftA2' :: (All2 c xss, Prod h ~ NP, HAp h) => proxy c -> (forall xs. All c xs => f xs -> f' xs -> f'' xs) -> Prod h f xss -> h f' xss -> h f'' xss Source #
hcliftA3' :: (All2 c xss, Prod h ~ NP, HAp h) => proxy c -> (forall xs. All c xs => f xs -> f' xs -> f'' xs -> f''' xs) -> Prod h f xss -> Prod h f' xss -> h f'' xss -> h f''' xss Source #
Deprecated: Use hcliftA3
or hczipWith3
instead.
Like hcliftA'
, but for ternary functions.
Comparison
:: forall r f g xs. r | what to do if first is smaller |
-> (forall x. f x -> g x -> r) | what to do if both are equal |
-> r | what to do if first is larger |
-> NS f xs | |
-> NS g xs | |
-> r |
Compare two sums with respect to the choice they are making.
A value that chooses the first option is considered smaller than one that chooses the second option.
If the choices are different, then either the first (if the first is smaller than the second) or the third (if the first is larger than the second) argument are called. If both choices are equal, then the second argument is called, which has access to the elements contained in the sums.
Since: 0.3.2.0
:: forall c proxy r f g xs. All c xs | |
=> proxy c | |
-> r | what to do if first is smaller |
-> (forall x. c x => f x -> g x -> r) | what to do if both are equal |
-> r | what to do if first is larger |
-> NS f xs | |
-> NS g xs | |
-> r |
Constrained version of compare_NS
.
Since: 0.3.2.0
:: forall r f g xss. r | what to do if first is smaller |
-> (forall xs. NP f xs -> NP g xs -> r) | what to do if both are equal |
-> r | what to do if first is larger |
-> SOP f xss | |
-> SOP g xss | |
-> r |
Compare two sums of products with respect to the choice in the sum they are making.
Only the sum structure is used for comparison.
This is a small wrapper around ccompare_NS
for
a common special case.
Since: 0.3.2.0
:: forall c proxy r f g xss. All2 c xss | |
=> proxy c | |
-> r | what to do if first is smaller |
-> (forall xs. All c xs => NP f xs -> NP g xs -> r) | what to do if both are equal |
-> r | what to do if first is larger |
-> SOP f xss | |
-> SOP g xss | |
-> r |
Constrained version of compare_SOP
.
Since: 0.3.2.0
Collapsing
type family CollapseTo (h :: (k -> Type) -> l -> Type) (x :: Type) :: Type Source #
Maps products to lists, and sums to identities.
Instances
type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a Source # | |
Defined in Data.SOP.NP | |
type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a Source # | |
Defined in Data.SOP.NP | |
type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a Source # | |
Defined in Data.SOP.NS | |
type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a Source # | |
Defined in Data.SOP.NS |
class HCollapse (h :: (k -> Type) -> l -> Type) where Source #
A class for collapsing a heterogeneous structure into a homogeneous one.
hcollapse :: SListIN h xs => h (K a) xs -> CollapseTo h a Source #
Collapse a heterogeneous structure with homogeneous elements into a homogeneous structure.
If a heterogeneous structure is instantiated to the constant
functor K
, then it is in fact homogeneous. This function
maps such a value to a simpler Haskell datatype reflecting that.
An
contains a single NS
(K
a)a
, and an
contains
a list of NP
(K
a)a
s.
Instances:
hcollapse
,collapse_NP
::NP
(K
a) xs -> [a]hcollapse
,collapse_NS
::NS
(K
a) xs -> ahcollapse
,collapse_POP
::POP
(K
a) xss -> [[a]]hcollapse
,collapse_SOP
::SOP
(K
a) xss -> [a]
Instances
HCollapse (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP | |
HCollapse (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP | |
HCollapse (NS :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NS | |
HCollapse (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NS |
Folding and sequencing
class HTraverse_ (h :: (k -> Type) -> l -> Type) where Source #
hctraverse_ :: (AllN h c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> h f xs -> g () Source #
Corresponds to traverse_
.
Instances:
hctraverse_
,ctraverse__NP
:: (All
c xs ,Applicative
g) => proxy c -> (forall a. c a => f a -> g ()) ->NP
f xs -> g ()hctraverse_
,ctraverse__NS
:: (All2
c xs ,Applicative
g) => proxy c -> (forall a. c a => f a -> g ()) ->NS
f xs -> g ()hctraverse_
,ctraverse__POP
:: (All
c xss,Applicative
g) => proxy c -> (forall a. c a => f a -> g ()) ->POP
f xss -> g ()hctraverse_
,ctraverse__SOP
:: (All2
c xss,Applicative
g) => proxy c -> (forall a. c a => f a -> g ()) ->SOP
f xss -> g ()
Since: 0.3.2.0
htraverse_ :: (SListIN h xs, Applicative g) => (forall a. f a -> g ()) -> h f xs -> g () Source #
Unconstrained version of hctraverse_
.
Instances:
traverse_
,traverse__NP
:: (SListI
xs ,Applicative
g) => (forall a. f a -> g ()) ->NP
f xs -> g ()traverse_
,traverse__NS
:: (SListI
xs ,Applicative
g) => (forall a. f a -> g ()) ->NS
f xs -> g ()traverse_
,traverse__POP
:: (SListI2
xss,Applicative
g) => (forall a. f a -> g ()) ->POP
f xss -> g ()traverse_
,traverse__SOP
:: (SListI2
xss,Applicative
g) => (forall a. f a -> g ()) ->SOP
f xss -> g ()
Since: 0.3.2.0
Instances
HTraverse_ (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () Source # htraverse_ :: forall (xs :: l) g f. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () Source # | |
HTraverse_ (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP hctraverse_ :: forall c (xs :: l) g proxy f. (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> POP f xs -> g () Source # htraverse_ :: forall (xs :: l) g f. (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> POP f xs -> g () Source # | |
HTraverse_ (NS :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NS hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () Source # htraverse_ :: forall (xs :: l) g f. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NS f xs -> g () Source # | |
HTraverse_ (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NS hctraverse_ :: forall c (xs :: l) g proxy f. (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> SOP f xs -> g () Source # htraverse_ :: forall (xs :: l) g f. (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> SOP f xs -> g () Source # |
hcfoldMap :: (HTraverse_ h, AllN h c xs, Monoid m) => proxy c -> (forall a. c a => f a -> m) -> h f xs -> m Source #
Special case of hctraverse_
.
Since: 0.3.2.0
hcfor_ :: (HTraverse_ h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall a. c a => f a -> g ()) -> g () Source #
Flipped version of hctraverse_
.
Since: 0.3.2.0
class HAp h => HSequence (h :: (k -> Type) -> l -> Type) where Source #
A generalization of sequenceA
.
hsequence' :: (SListIN h xs, Applicative f) => h (f :.: g) xs -> f (h g xs) Source #
Corresponds to sequenceA
.
Lifts an applicative functor out of a structure.
Instances:
hsequence'
,sequence'_NP
:: (SListI
xs ,Applicative
f) =>NP
(f:.:
g) xs -> f (NP
g xs )hsequence'
,sequence'_NS
:: (SListI
xs ,Applicative
f) =>NS
(f:.:
g) xs -> f (NS
g xs )hsequence'
,sequence'_POP
:: (SListI2
xss,Applicative
f) =>POP
(f:.:
g) xss -> f (POP
g xss)hsequence'
,sequence'_SOP
:: (SListI2
xss,Applicative
f) =>SOP
(f:.:
g) xss -> f (SOP
g xss)
hctraverse' :: (AllN h c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> h f xs -> g (h f' xs) Source #
Corresponds to traverse
.
Instances:
hctraverse'
,ctraverse'_NP
:: (All
c xs ,Applicative
g) => proxy c -> (forall a. c a => f a -> g (f' a)) ->NP
f xs -> g (NP
f' xs )hctraverse'
,ctraverse'_NS
:: (All2
c xs ,Applicative
g) => proxy c -> (forall a. c a => f a -> g (f' a)) ->NS
f xs -> g (NS
f' xs )hctraverse'
,ctraverse'_POP
:: (All
c xss,Applicative
g) => proxy c -> (forall a. c a => f a -> g (f' a)) ->POP
f xss -> g (POP
f' xss)hctraverse'
,ctraverse'_SOP
:: (All2
c xss,Applicative
g) => proxy c -> (forall a. c a => f a -> g (f' a)) ->SOP
f xss -> g (SOP
f' xss)
Since: 0.3.2.0
htraverse' :: (SListIN h xs, Applicative g) => (forall a. f a -> g (f' a)) -> h f xs -> g (h f' xs) Source #
Unconstrained variant of hctraverse
`.
Instances:
htraverse'
,traverse'_NP
:: (SListI
xs ,Applicative
g) => (forall a. c a => f a -> g (f' a)) ->NP
f xs -> g (NP
f' xs )htraverse'
,traverse'_NS
:: (SListI2
xs ,Applicative
g) => (forall a. c a => f a -> g (f' a)) ->NS
f xs -> g (NS
f' xs )htraverse'
,traverse'_POP
:: (SListI
xss,Applicative
g) => (forall a. c a => f a -> g (f' a)) ->POP
f xss -> g (POP
f' xss)htraverse'
,traverse'_SOP
:: (SListI2
xss,Applicative
g) => (forall a. c a => f a -> g (f' a)) ->SOP
f xss -> g (SOP
f' xss)
Since: 0.3.2.0
Instances
HSequence (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) Source # hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) Source # htraverse' :: forall (xs :: l) g f f'. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) Source # | |
HSequence (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN POP xs, Applicative f) => POP (f :.: g) xs -> f (POP g xs) Source # hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> POP f xs -> g (POP f' xs) Source # htraverse' :: forall (xs :: l) g f f'. (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> POP f xs -> g (POP f' xs) Source # | |
HSequence (NS :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NS hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) Source # hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) Source # htraverse' :: forall (xs :: l) g f f'. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) Source # | |
HSequence (SOP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NS hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN SOP xs, Applicative f) => SOP (f :.: g) xs -> f (SOP g xs) Source # hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) Source # htraverse' :: forall (xs :: l) g f f'. (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) Source # |
hsequence :: (SListIN h xs, SListIN (Prod h) xs, HSequence h) => Applicative f => h f xs -> f (h I xs) Source #
Special case of hsequence'
where g =
.I
hsequenceK :: (SListIN h xs, SListIN (Prod h) xs, Applicative f, HSequence h) => h (K (f a)) xs -> f (h (K a) xs) Source #
Special case of hsequence'
where g =
.K
a
hctraverse :: (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) Source #
Special case of hctraverse'
where f' =
.I
Since: 0.3.2.0
hcfor :: (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) Source #
Flipped version of hctraverse
.
Since: 0.3.2.0
Expanding sums to products
class HExpand (h :: (k -> Type) -> l -> Type) where Source #
A class for expanding sum structures into corresponding product structures, filling in the slots not targeted by the sum with default values.
Since: 0.2.5.0
hexpand :: SListIN (Prod h) xs => (forall x. f x) -> h f xs -> Prod h f xs Source #
Expand a given sum structure into a corresponding product structure by placing the value contained in the sum into the corresponding position in the product, and using the given default value for all other positions.
Instances:
hexpand
,expand_NS
::SListI
xs => (forall x . f x) ->NS
f xs ->NP
f xshexpand
,expand_SOP
::SListI2
xss => (forall x . f x) ->SOP
f xss ->POP
f xss
Examples:
>>>
hexpand Nothing (S (Z (Just 3))) :: NP Maybe '[Char, Int, Bool]
Nothing :* Just 3 :* Nothing :* Nil>>>
hexpand [] (SOP (S (Z ([1,2] :* "xyz" :* Nil)))) :: POP [] '[ '[Bool], '[Int, Char] ]
POP (([] :* Nil) :* ([1,2] :* "xyz" :* Nil) :* Nil)
Since: 0.2.5.0
hcexpand :: AllN (Prod h) c xs => proxy c -> (forall x. c x => f x) -> h f xs -> Prod h f xs Source #
Variant of hexpand
that allows passing a constrained default.
Instances:
hcexpand
,cexpand_NS
::All
c xs => proxy c -> (forall x . c x => f x) ->NS
f xs ->NP
f xshcexpand
,cexpand_SOP
::All2
c xss => proxy c -> (forall x . c x => f x) ->SOP
f xss ->POP
f xss
Examples:
>>>
hcexpand (Proxy :: Proxy Bounded) (I minBound) (S (Z (I 20))) :: NP I '[Bool, Int, Ordering]
I False :* I 20 :* I LT :* Nil>>>
hcexpand (Proxy :: Proxy Num) (I 0) (SOP (S (Z (I 1 :* I 2 :* Nil)))) :: POP I '[ '[Double], '[Int, Int] ]
POP ((I 0.0 :* Nil) :* (I 1 :* I 2 :* Nil) :* Nil)
Since: 0.2.5.0
Transformation of index lists and coercions
class (Same h1 ~ h2, Same h2 ~ h1) => HTrans (h1 :: (k1 -> Type) -> l1 -> Type) (h2 :: (k2 -> Type) -> l2 -> Type) where Source #
A class for transforming structures into related structures with a different index list, as long as the index lists have the same shape and the elements and interpretation functions are suitably related.
Since: 0.3.1.0
htrans :: AllZipN (Prod h1) c xs ys => proxy c -> (forall x y. c x y => f x -> g y) -> h1 f xs -> h2 g ys Source #
Transform a structure into a related structure given a conversion function for the elements.
Since: 0.3.1.0
hcoerce :: AllZipN (Prod h1) (LiftedCoercible f g) xs ys => h1 f xs -> h2 g ys Source #
Safely coerce a structure into a representationally equal structure.
This is a special case of htrans
, but can be implemented more efficiently;
for example in terms of unsafeCoerce
.
Examples:
>>>
hcoerce (I (Just LT) :* I (Just 'x') :* I (Just True) :* Nil) :: NP Maybe '[Ordering, Char, Bool]
Just LT :* Just 'x' :* Just True :* Nil>>>
hcoerce (SOP (Z (K True :* K False :* Nil))) :: SOP I '[ '[Bool, Bool], '[Bool] ]
SOP (Z (I True :* I False :* Nil))
Since: 0.3.1.0
Instances
HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) Source # | |
Defined in Data.SOP.NP htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys Source # hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod NP) (LiftedCoercible f g) xs ys => NP f xs -> NP g ys Source # | |
HTrans (POP :: (k1 -> Type) -> [[k1]] -> Type) (POP :: (k2 -> Type) -> [[k2]] -> Type) Source # | |
Defined in Data.SOP.NP htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod POP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> POP f xs -> POP g ys Source # hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod POP) (LiftedCoercible f g) xs ys => POP f xs -> POP g ys Source # | |
HTrans (NS :: (k1 -> Type) -> [k1] -> Type) (NS :: (k2 -> Type) -> [k2] -> Type) Source # | |
Defined in Data.SOP.NS htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NS) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys Source # hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod NS) (LiftedCoercible f g) xs ys => NS f xs -> NS g ys Source # | |
HTrans (SOP :: (k1 -> Type) -> [[k1]] -> Type) (SOP :: (k2 -> Type) -> [[k2]] -> Type) Source # | |
Defined in Data.SOP.NS htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod SOP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> SOP f xs -> SOP g ys Source # hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod SOP) (LiftedCoercible f g) xs ys => SOP f xs -> SOP g ys Source # |
hfromI :: (AllZipN (Prod h1) (LiftedCoercible I f) xs ys, HTrans h1 h2) => h1 I xs -> h2 f ys Source #
Specialization of hcoerce
.
Since: 0.3.1.0
htoI :: (AllZipN (Prod h1) (LiftedCoercible f I) xs ys, HTrans h1 h2) => h1 f xs -> h2 I ys Source #
Specialization of hcoerce
.
Since: 0.3.1.0
Partial operations
fromList :: SListI xs => [a] -> Maybe (NP (K a) xs) Source #
Construct a homogeneous n-ary product from a normal Haskell list.
Returns Nothing
if the length of the list does not exactly match the
expected size of the product.
Utilities
Basic functors
newtype K (a :: Type) (b :: k) Source #
The constant type functor.
Like Constant
, but kind-polymorphic
in its second argument and with a shorter name.
K a |
Instances
Eq2 (K :: Type -> Type -> Type) Source # | Since: 0.2.4.0 |
Ord2 (K :: Type -> Type -> Type) Source # | Since: 0.2.4.0 |
Defined in Data.SOP.BasicFunctors | |
Read2 (K :: Type -> Type -> Type) Source # | Since: 0.2.4.0 |
Defined in Data.SOP.BasicFunctors liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (K a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [K a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (K a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [K a b] # | |
Show2 (K :: Type -> Type -> Type) Source # | Since: 0.2.4.0 |
NFData2 (K :: Type -> Type -> Type) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
Functor (K a :: Type -> Type) Source # | |
Monoid a => Applicative (K a :: Type -> Type) Source # | |
Foldable (K a :: Type -> Type) Source # | |
Defined in Data.SOP.BasicFunctors fold :: Monoid m => K a m -> m # foldMap :: Monoid m => (a0 -> m) -> K a a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> K a a0 -> m # foldr :: (a0 -> b -> b) -> b -> K a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> K a a0 -> b # foldl :: (b -> a0 -> b) -> b -> K a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> K a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 # elem :: Eq a0 => a0 -> K a a0 -> Bool # maximum :: Ord a0 => K a a0 -> a0 # minimum :: Ord a0 => K a a0 -> a0 # | |
Traversable (K a :: Type -> Type) Source # | |
Eq a => Eq1 (K a :: Type -> Type) Source # | Since: 0.2.4.0 |
Ord a => Ord1 (K a :: Type -> Type) Source # | Since: 0.2.4.0 |
Defined in Data.SOP.BasicFunctors | |
Read a => Read1 (K a :: Type -> Type) Source # | Since: 0.2.4.0 |
Defined in Data.SOP.BasicFunctors | |
Show a => Show1 (K a :: Type -> Type) Source # | Since: 0.2.4.0 |
NFData a => NFData1 (K a :: Type -> Type) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
Eq a => Eq (K a b) Source # | |
Ord a => Ord (K a b) Source # | |
Read a => Read (K a b) Source # | |
Show a => Show (K a b) Source # | |
Generic (K a b) Source # | |
Semigroup a => Semigroup (K a b) Source # | Since: 0.4.0.0 |
Monoid a => Monoid (K a b) Source # | Since: 0.4.0.0 |
NFData a => NFData (K a b) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
type Rep (K a b) Source # | |
Defined in Data.SOP.BasicFunctors |
newtype I (a :: Type) Source #
The identity type functor.
Like Identity
, but with a shorter name.
I a |
Instances
Monad I Source # | |
Functor I Source # | |
Applicative I Source # | |
Foldable I Source # | |
Defined in Data.SOP.BasicFunctors fold :: Monoid m => I m -> m # foldMap :: Monoid m => (a -> m) -> I a -> m # foldMap' :: Monoid m => (a -> m) -> I a -> m # foldr :: (a -> b -> b) -> b -> I a -> b # foldr' :: (a -> b -> b) -> b -> I a -> b # foldl :: (b -> a -> b) -> b -> I a -> b # foldl' :: (b -> a -> b) -> b -> I a -> b # foldr1 :: (a -> a -> a) -> I a -> a # foldl1 :: (a -> a -> a) -> I a -> a # elem :: Eq a => a -> I a -> Bool # maximum :: Ord a => I a -> a # | |
Traversable I Source # | |
Eq1 I Source # | Since: 0.2.4.0 |
Ord1 I Source # | Since: 0.2.4.0 |
Defined in Data.SOP.BasicFunctors | |
Read1 I Source # | Since: 0.2.4.0 |
Show1 I Source # | Since: 0.2.4.0 |
NFData1 I Source # | Since: 0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
Eq a => Eq (I a) Source # | |
Ord a => Ord (I a) Source # | |
Read a => Read (I a) Source # | |
Show a => Show (I a) Source # | |
Generic (I a) Source # | |
Semigroup a => Semigroup (I a) Source # | Since: 0.4.0.0 |
Monoid a => Monoid (I a) Source # | Since: 0.4.0.0 |
NFData a => NFData (I a) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
type Rep (I a) Source # | |
Defined in Data.SOP.BasicFunctors |
newtype ((f :: l -> Type) :.: (g :: k -> l)) (p :: k) infixr 7 Source #
Composition of functors.
Like Compose
, but kind-polymorphic
and with a shorter name.
Comp (f (g p)) |
Instances
(Functor f, Functor g) => Functor (f :.: g) Source # | |
(Applicative f, Applicative g) => Applicative (f :.: g) Source # | Since: 0.2.5.0 |
(Foldable f, Foldable g) => Foldable (f :.: g) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.BasicFunctors fold :: Monoid m => (f :.: g) m -> m # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m # foldMap' :: Monoid m => (a -> m) -> (f :.: g) a -> m # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a # toList :: (f :.: g) a -> [a] # length :: (f :.: g) a -> Int # elem :: Eq a => a -> (f :.: g) a -> Bool # maximum :: Ord a => (f :.: g) a -> a # minimum :: Ord a => (f :.: g) a -> a # | |
(Traversable f, Traversable g) => Traversable (f :.: g) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
(Eq1 f, Eq1 g) => Eq1 (f :.: g) Source # | Since: 0.2.4.0 |
(Ord1 f, Ord1 g) => Ord1 (f :.: g) Source # | Since: 0.2.4.0 |
Defined in Data.SOP.BasicFunctors | |
(Read1 f, Read1 g) => Read1 (f :.: g) Source # | Since: 0.2.4.0 |
Defined in Data.SOP.BasicFunctors | |
(Show1 f, Show1 g) => Show1 (f :.: g) Source # | Since: 0.2.4.0 |
(NFData1 f, NFData1 g) => NFData1 (f :.: g) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
(Eq1 f, Eq1 g, Eq a) => Eq ((f :.: g) a) Source # | |
(Ord1 f, Ord1 g, Ord a) => Ord ((f :.: g) a) Source # | |
Defined in Data.SOP.BasicFunctors | |
(Read1 f, Read1 g, Read a) => Read ((f :.: g) a) Source # | |
(Show1 f, Show1 g, Show a) => Show ((f :.: g) a) Source # | |
Generic ((f :.: g) p) Source # | |
Semigroup (f (g x)) => Semigroup ((f :.: g) x) Source # | Since: 0.4.0.0 |
Monoid (f (g x)) => Monoid ((f :.: g) x) Source # | Since: 0.4.0.0 |
NFData (f (g a)) => NFData ((f :.: g) a) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
type Rep ((f :.: g) p) Source # | |
Defined in Data.SOP.BasicFunctors |
Mapping functions
Mapping constraints
class (AllF c xs, SListI xs) => All (c :: k -> Constraint) (xs :: [k]) Source #
Require a constraint for every element of a list.
If you have a datatype that is indexed over a type-level
list, then you can use All
to indicate that all elements
of that type-level list must satisfy a given constraint.
Example: The constraint
All Eq '[ Int, Bool, Char ]
is equivalent to the constraint
(Eq Int, Eq Bool, Eq Char)
Example: A type signature such as
f :: All Eq xs => NP I xs -> ...
means that f
can assume that all elements of the n-ary
product satisfy Eq
.
Note on superclasses: ghc cannot deduce superclasses from All
constraints.
You might expect the following to compile
class (Eq a) => MyClass a foo :: (All Eq xs) => NP f xs -> z foo = [..] bar :: (All MyClass xs) => NP f xs -> x bar = foo
but it will fail with an error saying that it was unable to
deduce the class constraint
(or similar) in the
definition of AllF
Eq
xsbar
.
In cases like this you can use Dict
from Data.SOP.Dict
to prove conversions between constraints.
See this answer on SO for more details.
Instances
All (c :: k -> Constraint) ('[] :: [k]) Source # | |
Defined in Data.SOP.Constraint cpara_SList :: proxy c -> r '[] -> (forall (y :: k0) (ys :: [k0]). (c y, All c ys) => r ys -> r (y ': ys)) -> r '[] Source # | |
(c x, All c xs) => All (c :: a -> Constraint) (x ': xs :: [a]) Source # | |
Defined in Data.SOP.Constraint cpara_SList :: proxy c -> r '[] -> (forall (y :: k) (ys :: [k]). (c y, All c ys) => r ys -> r (y ': ys)) -> r (x ': xs) Source # |
type All2 c = All (All c) Source #
Require a constraint for every element of a list of lists.
If you have a datatype that is indexed over a type-level
list of lists, then you can use All2
to indicate that all
elements of the inner lists must satisfy a given constraint.
Example: The constraint
All2 Eq '[ '[ Int ], '[ Bool, Char ] ]
is equivalent to the constraint
(Eq Int, Eq Bool, Eq Char)
Example: A type signature such as
f :: All2 Eq xss => SOP I xs -> ...
means that f
can assume that all elements of the sum
of product satisfy Eq
.
Since 0.4.0.0, this is merely a synonym for 'All (All c)'.
Since: 0.4.0.0
cpara_SList :: All c xs => proxy c -> r '[] -> (forall y ys. (c y, All c ys) => r ys -> r (y ': ys)) -> r xs Source #
Constrained paramorphism for a type-level list.
The advantage of writing functions in terms of cpara_SList
is that
they are then typically not recursive, and can be unfolded statically if
the type-level list is statically known.
Since: 0.4.0.0
ccase_SList :: All c xs => proxy c -> r '[] -> (forall y ys. (c y, All c ys) => r (y ': ys)) -> r xs Source #
Constrained case distinction on a type-level list.
Since: 0.4.0.0
class (SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b]) Source #
Require a constraint pointwise for every pair of elements from two lists.
Example: The constraint
AllZip (~) '[ Int, Bool, Char ] '[ a, b, c ]
is equivalent to the constraint
(Int ~ a, Bool ~ b, Char ~ c)
Since: 0.3.1.0
Instances
(SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b]) Source # | |
Defined in Data.SOP.Constraint |
class (AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 f xss yss Source #
Require a constraint pointwise for every pair of elements from two lists of lists.
Instances
(AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 (f :: a -> b -> Constraint) (xss :: [[a]]) (yss :: [[b]]) Source # | |
Defined in Data.SOP.Constraint |
type family AllN (h :: (k -> Type) -> l -> Type) (c :: k -> Constraint) :: l -> Constraint Source #
A generalization of All
and All2
.
The family AllN
expands to All
or All2
depending on whether
the argument is indexed by a list or a list of lists.
Instances
type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NP | |
type AllN (POP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NP | |
type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NS | |
type AllN (SOP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NS |
type family AllZipN (h :: (k -> Type) -> l -> Type) (c :: k1 -> k2 -> Constraint) :: l1 -> l2 -> Constraint Source #
A generalization of AllZip
and AllZip2
.
The family AllZipN
expands to AllZip
or AllZip2
depending on
whther the argument is indexed by a list or a list of lists.
Instances
type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) Source # | |
Defined in Data.SOP.NP | |
type AllZipN (POP :: (k -> Type) -> [[k]] -> Type) (c :: a -> b -> Constraint) Source # | |
Defined in Data.SOP.NP |
Other constraints
class f (g x) => Compose f g x infixr 9 Source #
Composition of constraints.
Note that the result of the composition must be a constraint,
and therefore, in
, the kind of Compose
f gf
is k ->
.
The kind of Constraint
g
, however, is l -> k
and can thus be a normal
type constructor.
A typical use case is in connection with All
on an NP
or an
NS
. For example, in order to denote that all elements on an
satisfy NP
f xsShow
, we can say
.All
(Compose
Show
f) xs
Since: 0.2
Instances
f (g x) => Compose (f :: k1 -> Constraint) (g :: k2 -> k1) (x :: k2) Source # | |
Defined in Data.SOP.Constraint |
class (f x, g x) => And f g x infixl 7 Source #
Pairing of constraints.
Since: 0.2
Instances
(f x, g x) => And (f :: k -> Constraint) (g :: k -> Constraint) (x :: k) Source # | |
Defined in Data.SOP.Constraint |
A constraint that can always be satisfied.
Since: 0.2
Instances
Top (x :: k) Source # | |
Defined in Data.SOP.Constraint |
class Coercible (f x) (g y) => LiftedCoercible f g x y Source #
The constraint
is equivalent
to LiftedCoercible
f g x y
.Coercible
(f x) (g y)
Since: 0.3.1.0
Instances
Coercible (f x) (g y) => LiftedCoercible (f :: k1 -> k2) (g :: k3 -> k2) (x :: k1) (y :: k3) Source # | |
Defined in Data.SOP.Constraint |
type family SameShapeAs (xs :: [a]) (ys :: [b]) :: Constraint where ... Source #
Type family that forces a type-level list to be of the same shape as the given type-level list.
Since 0.5.0.0, this only tests the top-level structure of
the list, and is intended to be used in conjunction with
a separate construct (such as the AllZip
, AllZipF
combination to tie the recursive knot). The reason is that
making SameShapeAs
directly recursive leads to quadratic
compile times.
The main use of this constraint is to help type inference to learn something about otherwise unknown type-level lists.
Since: 0.5.0.0
SameShapeAs '[] ys = ys ~ '[] | |
SameShapeAs (x ': xs) ys = ys ~ (Head ys ': Tail ys) |
Singletons
data SList :: [k] -> Type where Source #
Explicit singleton list.
A singleton list can be used to reveal the structure of
a type-level list argument that the function is quantified
over. For every type-level list xs
, there is one non-bottom
value of type
.SList
xs
Note that these singleton lists are polymorphic in the list elements; we do not require a singleton representation for them.
Since: 0.2
type SListI = All Top Source #
Implicit singleton list.
A singleton list can be used to reveal the structure of a type-level list argument that the function is quantified over.
Since 0.4.0.0, this is now defined in terms of All
.
A singleton list provides a witness for a type-level list
where the elements need not satisfy any additional
constraints.
Since: 0.4.0.0
sList :: SListI xs => SList xs Source #
Get hold of an explicit singleton (that one can then pattern match on) for a type-level list
para_SList :: SListI xs => r '[] -> (forall y ys. SListI ys => r ys -> r (y ': ys)) -> r xs Source #
Paramorphism for a type-level list.
Since: 0.4.0.0
case_SList :: SListI xs => r '[] -> (forall y ys. SListI ys => r (y ': ys)) -> r xs Source #
Case distinction on a type-level list.
Since: 0.4.0.0
Shape of type-level lists
data Shape :: [k] -> Type where Source #
Occasionally it is useful to have an explicit, term-level, representation of type-level lists (esp because of https://ghc.haskell.org/trac/ghc/ticket/9108 )
lengthSList :: forall k (xs :: [k]) proxy. SListI xs => proxy xs -> Int Source #
The length of a type-level list.
Since: 0.2
Re-exports
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a
idiom.undefined
:: a
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Instances
Generic1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
NFData1 (Proxy :: Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Ord (Proxy s) | Since: base-4.7.0.0 |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
Generic (Proxy t) | Since: base-4.6.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
NFData (Proxy a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
type Rep1 (Proxy :: k -> Type) | |
type Rep (Proxy t) | |