sop-core-0.5.0.1: True Sums of Products

Safe HaskellNone
LanguageHaskell2010

Data.SOP.Classes

Contents

Description

Classes for generalized combinators on SOP types.

In the SOP approach to generic programming, we're predominantly concerned with four structured datatypes:

  NP  :: (k -> Type) -> ( [k]  -> Type)   -- n-ary product
  NS  :: (k -> Type) -> ( [k]  -> Type)   -- n-ary sum
  POP :: (k -> Type) -> ([[k]] -> Type)   -- product of products
  SOP :: (k -> Type) -> ([[k]] -> Type)   -- sum of products

All of these have a kind that fits the following pattern:

  (k -> Type) -> (l -> Type)

These four types support similar interfaces. In order to allow reusing the same combinator names for all of these types, we define various classes in this module that allow the necessary generalization.

The classes typically lift concepts that exist for kinds Type or Type -> Type to datatypes of kind (k -> Type) -> (l -> Type). This module also derives a number of derived combinators.

The actual instances are defined in Data.SOP.NP and Data.SOP.NS.

Synopsis

Generalized applicative functor structure

Generalized pure

class HPure (h :: (k -> Type) -> l -> Type) where Source #

A generalization of pure or return to higher kinds.

Methods

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 xs
hpure, 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 hcpure f s where s :: 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 AllN h c xs states.

Instances:

hcpure, cpure_NP  :: (All  c xs ) => proxy c -> (forall a. c a => f a) -> NP  f xs
hcpure, cpure_POP :: (All2 c xss) => proxy c -> (forall a. c a => f a) -> POP f xss
Instances
HPure (NP :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

Methods

hpure :: SListIN NP xs => (forall (a :: k0). f a) -> NP f xs Source #

hcpure :: AllN NP c xs => proxy c -> (forall (a :: k0). c a => f a) -> NP f xs Source #

HPure (POP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

Methods

hpure :: SListIN POP xs => (forall (a :: k0). f a) -> POP f xs Source #

hcpure :: AllN POP c xs => proxy c -> (forall (a :: k0). c a => f a) -> POP f xs Source #

Generalized <*>

newtype (f -.-> g) a infixr 1 Source #

Lifted functions.

Constructors

Fn 

Fields

  • apFn :: f a -> g a
     

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 Same (h :: (k1 -> Type) -> l1 -> Type) :: (k2 -> Type) -> l2 -> Type Source #

Maps a structure to the same structure.

Instances
type Same (NP :: (k1 -> Type) -> [k1] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

type Same (NP :: (k1 -> Type) -> [k1] -> Type) = (NP :: (k2 -> Type) -> [k2] -> Type)
type Same (POP :: (k1 -> Type) -> [[k1]] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

type Same (POP :: (k1 -> Type) -> [[k1]] -> Type) = (POP :: (k2 -> Type) -> [[k2]] -> Type)
type Same (NS :: (k1 -> Type) -> [k1] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

type Same (NS :: (k1 -> Type) -> [k1] -> Type) = (NS :: (k2 -> Type) -> [k2] -> Type)
type Same (SOP :: (k1 -> Type) -> [[k1]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

type Same (SOP :: (k1 -> Type) -> [[k1]] -> Type) = (SOP :: (k2 -> Type) -> [[k2]] -> Type)

type family Prod (h :: (k -> Type) -> l -> Type) :: (k -> Type) -> l -> Type Source #

Maps a structure containing sums to the corresponding product structure.

Instances
type Prod (NP :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

type Prod (NP :: (k -> Type) -> [k] -> Type) = (NP :: (k -> Type) -> [k] -> Type)
type Prod (POP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

type Prod (POP :: (k -> Type) -> [[k]] -> Type) = (POP :: (k -> Type) -> [[k]] -> Type)
type Prod (NS :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

type Prod (NS :: (k -> Type) -> [k] -> Type) = (NP :: (k -> Type) -> [k] -> Type)
type Prod (SOP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

type Prod (SOP :: (k -> Type) -> [[k]] -> Type) = (POP :: (k -> Type) -> [[k]] -> Type)

class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp (h :: (k -> Type) -> l -> Type) where Source #

A generalization of <*>.

Methods

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 xs
hap, ap_NS  :: NP  (f -.-> g) xs  -> NS  f xs  -> NS  g xs
hap, ap_POP :: POP (f -.-> g) xss -> POP f xss -> POP g xss
hap, ap_SOP :: POP (f -.-> g) xss -> SOP f xss -> SOP g xss
Instances
HAp (NP :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

Methods

hap :: Prod NP (f -.-> g) xs -> NP f xs -> NP g xs Source #

HAp (POP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

Methods

hap :: Prod POP (f -.-> g) xs -> POP f xs -> POP g xs Source #

HAp (NS :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hap :: Prod NS (f -.-> g) xs -> NS f xs -> NS g xs Source #

HAp (SOP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hap :: Prod SOP (f -.-> g) xs -> SOP f xs -> SOP g xs Source #

Derived functions

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' xs
hliftA, liftA_NS  :: SListI  xs  => (forall a. f a -> f' a) -> NS  f xs  -> NS  f' xs
hliftA, liftA_POP :: SListI2 xss => (forall a. f a -> f' a) -> POP f xss -> POP f' xss
hliftA, 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'' xs
hliftA2, liftA2_NS  :: SListI  xs  => (forall a. f a -> f' a -> f'' a) -> NP  f xs  -> NS  f' xs  -> NS  f'' xs
hliftA2, liftA2_POP :: SListI2 xss => (forall a. f a -> f' a -> f'' a) -> POP f xss -> POP f' xss -> POP f'' xss
hliftA2, 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''' xs
hliftA3, 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''' xs
hliftA3, 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''' xs
hliftA3, 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

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

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 #

Variant of hliftA that takes a constrained function.

Specification:

hcliftA p f xs = hcpure p (fn f) ` hap ` 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 Source #

Variant of hcliftA2 that takes a constrained function.

Specification:

hcliftA2 p f xs ys = hcpure p (fn_2 f) ` hap ` xs ` hap ` ys

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 #

Variant of hcliftA3 that takes a constrained function.

Specification:

hcliftA3 p f xs ys zs = hcpure p (fn_3 f) ` hap ` xs ` hap ` ys ` hap ` zs

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

Collapsing homogeneous structures

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 # 
Instance details

Defined in Data.SOP.NP

type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a = [a]
type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a Source # 
Instance details

Defined in Data.SOP.NP

type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a = [[a]]
type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a Source # 
Instance details

Defined in Data.SOP.NS

type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a = a
type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a Source # 
Instance details

Defined in Data.SOP.NS

type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a = [a]

class HCollapse (h :: (k -> Type) -> l -> Type) where Source #

A class for collapsing a heterogeneous structure into a homogeneous one.

Methods

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 NS (K a) contains a single a, and an NP (K a) contains a list of as.

Instances:

hcollapse, collapse_NP  :: NP  (K a) xs  ->  [a]
hcollapse, collapse_NS  :: NS  (K a) xs  ->   a
hcollapse, collapse_POP :: POP (K a) xss -> [[a]]
hcollapse, collapse_SOP :: SOP (K a) xss ->  [a]
Instances
HCollapse (NP :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: SListIN NP xs => NP (K a) xs -> CollapseTo NP a Source #

HCollapse (POP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: SListIN POP xs => POP (K a) xs -> CollapseTo POP a Source #

HCollapse (NS :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: SListIN NS xs => NS (K a) xs -> CollapseTo NS a Source #

HCollapse (SOP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: SListIN SOP xs => SOP (K a) xs -> CollapseTo SOP a Source #

Folding and sequencing

class HTraverse_ (h :: (k -> Type) -> l -> Type) where Source #

A generalization of traverse_ or foldMap.

Since: 0.3.2.0

Methods

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 # 
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () Source #

htraverse_ :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () Source #

HTraverse_ (POP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> POP f xs -> g () Source #

htraverse_ :: (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> POP f xs -> g () Source #

HTraverse_ (NS :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () Source #

htraverse_ :: (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NS f xs -> g () Source #

HTraverse_ (SOP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> SOP f xs -> g () Source #

htraverse_ :: (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> SOP f xs -> g () Source #

class HAp h => HSequence (h :: (k -> Type) -> l -> Type) where Source #

A generalization of sequenceA.

Methods

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 htraverse'.

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 # 
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) Source #

hctraverse' :: (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' :: (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 # 
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: (SListIN POP xs, Applicative f) => POP (f :.: g) xs -> f (POP g xs) Source #

hctraverse' :: (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' :: (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 # 
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: (SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) Source #

hctraverse' :: (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' :: (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 # 
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: (SListIN SOP xs, Applicative f) => SOP (f :.: g) xs -> f (SOP g xs) Source #

hctraverse' :: (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' :: (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) Source #

Derived functions

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

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

Indexing into sums

class HIndex (h :: (k -> Type) -> l -> Type) where Source #

A class for determining which choice in a sum-like structure a value represents.

Methods

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 hindex x returns a number between 0 and n - 1 representing the index of the choice made by x.

Instances:

hindex, index_NS  :: NS  f xs -> Int
hindex, 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
HIndex (NS :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hindex :: NS f xs -> Int Source #

HIndex (SOP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hindex :: SOP f xs -> Int Source #

Applying all injections

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

Instances
type UnProd (NP :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

type UnProd (NP :: (k -> Type) -> [k] -> Type) = (NS :: (k -> Type) -> [k] -> Type)
type UnProd (POP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

type UnProd (POP :: (k -> Type) -> [[k]] -> Type) = (SOP :: (k -> Type) -> [[k]] -> Type)

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.

Methods

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

Instances
HApInjs (NS :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: SListIN NS xs => Prod NS f xs -> [NS f xs] Source #

HApInjs (SOP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: SListIN SOP xs => Prod SOP f xs -> [SOP f xs] Source #

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

Methods

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 xs
hexpand, 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 xs
hcexpand, 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

Instances
HExpand (NS :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: SListIN (Prod NS) xs => (forall (x :: k0). f x) -> NS f xs -> Prod NS f xs Source #

hcexpand :: AllN (Prod NS) c xs => proxy c -> (forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs Source #

HExpand (SOP :: (k -> Type) -> [[k]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: SListIN (Prod SOP) xs => (forall (x :: k0). f x) -> SOP f xs -> Prod SOP f xs Source #

hcexpand :: AllN (Prod SOP) c xs => proxy c -> (forall (x :: k0). c x => f x) -> SOP f xs -> Prod SOP f xs Source #

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

Methods

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 # 
Instance details

Defined in Data.SOP.NP

Methods

htrans :: 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 :: 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 # 
Instance details

Defined in Data.SOP.NP

Methods

htrans :: 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 :: 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 # 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: 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 :: 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 # 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: 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 :: 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