functor-products-0.1.2.1: General functor products for various Foldable instances
Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Type.Functor.Product

Description

Generalized functor products based on lifted Foldables.

For example, Rec f '[a,b,c] from vinyl contains an f a, f b, and f c.

PMaybe f ('Just a) contains an f a and PMaybe f 'Nothing contains nothing.

Also provide data types for "indexing" into each foldable.

Synopsis

Classes

class (PFunctor f, SFunctor f, PFoldable f, SFoldable f) => FProd (f :: Type -> Type) where Source #

Unify different functor products over a Foldable f.

Associated Types

type Elem f = (i :: f k -> k -> Type) | i -> f Source #

type Prod f = (p :: (k -> Type) -> f k -> Type) | p -> f Source #

Methods

singProd :: Sing as -> Prod f Sing as Source #

You can convert a singleton of a foldable value into a foldable product of singletons. This essentially "breaks up" the singleton into its individual items. Should be an inverse with prodSing.

prodSing :: Prod f Sing as -> Sing as Source #

Collect a collection of singletons back into a single singleton. Should be an inverse with singProd.

withIndices :: Prod f g as -> Prod f (Elem f as :*: g) as Source #

Pair up each item in a foldable product with its index.

traverseProd :: forall g h as m. Applicative m => (forall a. g a -> m (h a)) -> Prod f g as -> m (Prod f h as) Source #

Traverse a foldable functor product with a RankN applicative function, mapping over each value and sequencing the effects.

This is the generalization of rtraverse.

zipWithProd :: (forall a. g a -> h a -> j a) -> Prod f g as -> Prod f h as -> Prod f j as Source #

Zip together two foldable functor products with a Rank-N function.

htraverse :: Applicative m => Sing ff -> (forall a. g a -> m (h (ff @@ a))) -> Prod f g as -> m (Prod f h (Fmap ff as)) Source #

Traverse a foldable functor product with a type-changing function.

ixProd :: Elem f as a -> Lens' (Prod f g as) (g a) Source #

A Lens into an item in a foldable functor product, given its index.

This roughly generalizes rlens.

toRec :: Prod f g as -> Rec g (ToList as) Source #

Fold a functor product into a Rec.

withPureProd :: Prod f g as -> (PureProd f as => r) -> r Source #

Get a PureProd instance from a foldable functor product providing its shape.

Instances

Instances details
FProd Identity Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Elem Identity = (i :: f k -> k -> Type) Source #

type Prod Identity = (p :: (k -> Type) -> f k -> Type) Source #

Methods

singProd :: forall {k} (as :: Identity k). Sing as -> Prod Identity Sing as Source #

prodSing :: forall {k} (as :: Identity k). Prod Identity Sing as -> Sing as Source #

withIndices :: forall {k} (g :: k -> Type) (as :: Identity k). Prod Identity g as -> Prod Identity (Elem Identity as :*: g) as Source #

traverseProd :: forall {k} g h (as :: Identity k) m. Applicative m => (forall (a :: k). g a -> m (h a)) -> Prod Identity g as -> m (Prod Identity h as) Source #

zipWithProd :: forall {k} g h j (as :: Identity k). (forall (a :: k). g a -> h a -> j a) -> Prod Identity g as -> Prod Identity h as -> Prod Identity j as Source #

htraverse :: forall {a} {k} m (ff :: a ~> k) g h (as :: Identity a). Applicative m => Sing ff -> (forall (a1 :: a). g a1 -> m (h (ff @@ a1))) -> Prod Identity g as -> m (Prod Identity h (Fmap ff as)) Source #

ixProd :: forall {k} (as :: Identity k) (a :: k) (g :: k -> Type). Elem Identity as a -> Lens' (Prod Identity g as) (g a) Source #

toRec :: forall {a} (g :: a -> Type) (as :: Identity a). Prod Identity g as -> Rec g (ToList as) Source #

withPureProd :: forall {k} (g :: k -> Type) (as :: Identity k) r. Prod Identity g as -> (PureProd Identity as => r) -> r Source #

FProd NonEmpty Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Elem NonEmpty = (i :: f k -> k -> Type) Source #

type Prod NonEmpty = (p :: (k -> Type) -> f k -> Type) Source #

Methods

singProd :: forall {k} (as :: NonEmpty k). Sing as -> Prod NonEmpty Sing as Source #

prodSing :: forall {k} (as :: NonEmpty k). Prod NonEmpty Sing as -> Sing as Source #

withIndices :: forall {k} (g :: k -> Type) (as :: NonEmpty k). Prod NonEmpty g as -> Prod NonEmpty (Elem NonEmpty as :*: g) as Source #

traverseProd :: forall {k} g h (as :: NonEmpty k) m. Applicative m => (forall (a :: k). g a -> m (h a)) -> Prod NonEmpty g as -> m (Prod NonEmpty h as) Source #

zipWithProd :: forall {k} g h j (as :: NonEmpty k). (forall (a :: k). g a -> h a -> j a) -> Prod NonEmpty g as -> Prod NonEmpty h as -> Prod NonEmpty j as Source #

htraverse :: forall {a} {k} m (ff :: a ~> k) g h (as :: NonEmpty a). Applicative m => Sing ff -> (forall (a1 :: a). g a1 -> m (h (ff @@ a1))) -> Prod NonEmpty g as -> m (Prod NonEmpty h (Fmap ff as)) Source #

ixProd :: forall {k} (as :: NonEmpty k) (a :: k) (g :: k -> Type). Elem NonEmpty as a -> Lens' (Prod NonEmpty g as) (g a) Source #

toRec :: forall {a} (g :: a -> Type) (as :: NonEmpty a). Prod NonEmpty g as -> Rec g (ToList as) Source #

withPureProd :: forall {k} (g :: k -> Type) (as :: NonEmpty k) r. Prod NonEmpty g as -> (PureProd NonEmpty as => r) -> r Source #

FProd Maybe Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Elem Maybe = (i :: f k -> k -> Type) Source #

type Prod Maybe = (p :: (k -> Type) -> f k -> Type) Source #

Methods

singProd :: forall {k} (as :: Maybe k). Sing as -> Prod Maybe Sing as Source #

prodSing :: forall {k} (as :: Maybe k). Prod Maybe Sing as -> Sing as Source #

withIndices :: forall {k} (g :: k -> Type) (as :: Maybe k). Prod Maybe g as -> Prod Maybe (Elem Maybe as :*: g) as Source #

traverseProd :: forall {k} g h (as :: Maybe k) m. Applicative m => (forall (a :: k). g a -> m (h a)) -> Prod Maybe g as -> m (Prod Maybe h as) Source #

zipWithProd :: forall {k} g h j (as :: Maybe k). (forall (a :: k). g a -> h a -> j a) -> Prod Maybe g as -> Prod Maybe h as -> Prod Maybe j as Source #

htraverse :: forall {a} {k} m (ff :: a ~> k) g h (as :: Maybe a). Applicative m => Sing ff -> (forall (a1 :: a). g a1 -> m (h (ff @@ a1))) -> Prod Maybe g as -> m (Prod Maybe h (Fmap ff as)) Source #

ixProd :: forall {k} (as :: Maybe k) (a :: k) (g :: k -> Type). Elem Maybe as a -> Lens' (Prod Maybe g as) (g a) Source #

toRec :: forall {a} (g :: a -> Type) (as :: Maybe a). Prod Maybe g as -> Rec g (ToList as) Source #

withPureProd :: forall {k} (g :: k -> Type) (as :: Maybe k) r. Prod Maybe g as -> (PureProd Maybe as => r) -> r Source #

FProd List Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Elem List = (i :: f k -> k -> Type) Source #

type Prod List = (p :: (k -> Type) -> f k -> Type) Source #

Methods

singProd :: forall {k} (as :: [k]). Sing as -> Prod List Sing as Source #

prodSing :: forall {k} (as :: [k]). Prod List Sing as -> Sing as Source #

withIndices :: forall {k} (g :: k -> Type) (as :: [k]). Prod List g as -> Prod List (Elem List as :*: g) as Source #

traverseProd :: forall {k} g h (as :: [k]) m. Applicative m => (forall (a :: k). g a -> m (h a)) -> Prod List g as -> m (Prod List h as) Source #

zipWithProd :: forall {k} g h j (as :: [k]). (forall (a :: k). g a -> h a -> j a) -> Prod List g as -> Prod List h as -> Prod List j as Source #

htraverse :: forall {a} {k} m (ff :: a ~> k) g h (as :: [a]). Applicative m => Sing ff -> (forall (a1 :: a). g a1 -> m (h (ff @@ a1))) -> Prod List g as -> m (Prod List h (Fmap ff as)) Source #

ixProd :: forall {k} (as :: [k]) (a :: k) (g :: k -> Type). Elem List as a -> Lens' (Prod List g as) (g a) Source #

toRec :: forall {a} (g :: a -> Type) (as :: [a]). Prod List g as -> Rec g (ToList as) Source #

withPureProd :: forall {k} (g :: k -> Type) (as :: [k]) r. Prod List g as -> (PureProd List as => r) -> r Source #

FProd (Either j) Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Elem (Either j) = (i :: f k -> k -> Type) Source #

type Prod (Either j) = (p :: (k -> Type) -> f k -> Type) Source #

Methods

singProd :: forall {k} (as :: Either j k). Sing as -> Prod (Either j) Sing as Source #

prodSing :: forall {k} (as :: Either j k). Prod (Either j) Sing as -> Sing as Source #

withIndices :: forall {k} (g :: k -> Type) (as :: Either j k). Prod (Either j) g as -> Prod (Either j) (Elem (Either j) as :*: g) as Source #

traverseProd :: forall {k} g h (as :: Either j k) m. Applicative m => (forall (a :: k). g a -> m (h a)) -> Prod (Either j) g as -> m (Prod (Either j) h as) Source #

zipWithProd :: forall {k} g h j0 (as :: Either j k). (forall (a :: k). g a -> h a -> j0 a) -> Prod (Either j) g as -> Prod (Either j) h as -> Prod (Either j) j0 as Source #

htraverse :: forall {a} {k} m (ff :: a ~> k) g h (as :: Either j a). Applicative m => Sing ff -> (forall (a1 :: a). g a1 -> m (h (ff @@ a1))) -> Prod (Either j) g as -> m (Prod (Either j) h (Fmap ff as)) Source #

ixProd :: forall {k} (as :: Either j k) (a :: k) (g :: k -> Type). Elem (Either j) as a -> Lens' (Prod (Either j) g as) (g a) Source #

toRec :: forall {a} (g :: a -> Type) (as :: Either j a). Prod (Either j) g as -> Rec g (ToList as) Source #

withPureProd :: forall {k} (g :: k -> Type) (as :: Either j k) r. Prod (Either j) g as -> (PureProd (Either j) as => r) -> r Source #

FProd ((,) j) Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Elem ((,) j) = (i :: f k -> k -> Type) Source #

type Prod ((,) j) = (p :: (k -> Type) -> f k -> Type) Source #

Methods

singProd :: forall {k} (as :: (j, k)). Sing as -> Prod ((,) j) Sing as Source #

prodSing :: forall {k} (as :: (j, k)). Prod ((,) j) Sing as -> Sing as Source #

withIndices :: forall {k} (g :: k -> Type) (as :: (j, k)). Prod ((,) j) g as -> Prod ((,) j) (Elem ((,) j) as :*: g) as Source #

traverseProd :: forall {k} g h (as :: (j, k)) m. Applicative m => (forall (a :: k). g a -> m (h a)) -> Prod ((,) j) g as -> m (Prod ((,) j) h as) Source #

zipWithProd :: forall {k} g h j0 (as :: (j, k)). (forall (a :: k). g a -> h a -> j0 a) -> Prod ((,) j) g as -> Prod ((,) j) h as -> Prod ((,) j) j0 as Source #

htraverse :: forall {a} {k} m (ff :: a ~> k) g h (as :: (j, a)). Applicative m => Sing ff -> (forall (a1 :: a). g a1 -> m (h (ff @@ a1))) -> Prod ((,) j) g as -> m (Prod ((,) j) h (Fmap ff as)) Source #

ixProd :: forall {k} (as :: (j, k)) (a :: k) (g :: k -> Type). Elem ((,) j) as a -> Lens' (Prod ((,) j) g as) (g a) Source #

toRec :: forall {a} (g :: a -> Type) (as :: (j, a)). Prod ((,) j) g as -> Rec g (ToList as) Source #

withPureProd :: forall {k} (g :: k -> Type) (as :: (j, k)) r. Prod ((,) j) g as -> (PureProd ((,) j) as => r) -> r Source #

type Shape f = Prod f Proxy :: f k -> Type Source #

Simply witness the shape of an argument (ie, Shape [] as witnesses the length of as, and Shape Maybe as witnesses whether or not as is Just or Nothing).

class PureProd f as where Source #

Create Prod f if you can give a g a for every slot.

Methods

pureProd :: (forall a. g a) -> Prod f g as Source #

Instances

Instances details
RecApplicative as => PureProd List (as :: [k]) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProd :: (forall (a :: k0). g a) -> Prod List g as Source #

PureProd Maybe ('Nothing :: Maybe k) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProd :: (forall (a :: k0). g a) -> Prod Maybe g 'Nothing Source #

PureProd Identity ('Identity a :: Identity k) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProd :: (forall (a0 :: k0). g a0) -> Prod Identity0 g ('Identity a) Source #

PureProd Maybe ('Just a :: Maybe k) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProd :: (forall (a0 :: k0). g a0) -> Prod Maybe g ('Just a) Source #

RecApplicative as => PureProd NonEmpty (a ':| as :: NonEmpty k) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProd :: (forall (a0 :: k0). g a0) -> Prod NonEmpty g (a ':| as) Source #

SingI e => PureProd (Either j) ('Left e :: Either j k) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProd :: (forall (a :: k0). g a) -> Prod (Either j) g ('Left e) Source #

PureProd (Either j) ('Right a :: Either j k) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProd :: (forall (a0 :: k0). g a0) -> Prod (Either j) g ('Right a) Source #

SingI w => PureProd ((,) j) ('(w, a) :: (j, k)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProd :: (forall (a0 :: k0). g a0) -> Prod ((,) j) g '(w, a) Source #

pureShape :: PureProd f as => Shape f as Source #

Create a Shape given an instance of PureProd.

class PureProdC f c as where Source #

Create Prod f if you can give a g a for every slot, given some constraint.

Methods

pureProdC :: (forall a. c a => g a) -> Prod f g as Source #

Instances

Instances details
RPureConstrained c as => PureProdC List (c :: k -> Constraint) (as :: [k]) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProdC :: (forall (a :: k0). c a => g a) -> Prod List g as Source #

PureProdC Maybe (c :: k -> Constraint) ('Nothing :: Maybe k) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProdC :: (forall (a :: k0). c a => g a) -> Prod Maybe g 'Nothing Source #

c a2 => PureProdC Identity (c :: a1 -> Constraint) ('Identity a2 :: Identity a1) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProdC :: (forall (a :: k). c a => g a) -> Prod Identity0 g ('Identity a2) Source #

c a2 => PureProdC Maybe (c :: a1 -> Constraint) ('Just a2 :: Maybe a1) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProdC :: (forall (a :: k). c a => g a) -> Prod Maybe g ('Just a2) Source #

(c a2, RPureConstrained c as) => PureProdC NonEmpty (c :: a1 -> Constraint) (a2 ':| as :: NonEmpty a1) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProdC :: (forall (a :: k). c a => g a) -> Prod NonEmpty g (a2 ':| as) Source #

c a => PureProdC (Either j) (c :: b -> Constraint) ('Right a :: Either j b) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProdC :: (forall (a0 :: k). c a0 => g a0) -> Prod (Either j) g ('Right a) Source #

SingI e => PureProdC (Either j) (c :: k -> Constraint) ('Left e :: Either j k) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProdC :: (forall (a :: k0). c a => g a) -> Prod (Either j) g ('Left e) Source #

(SingI w, c a) => PureProdC ((,) j) (c :: k -> Constraint) ('(w, a) :: (j, k)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

pureProdC :: (forall (a0 :: k0). c a0 => g a0) -> Prod ((,) j) g '(w, a) Source #

class ReifyConstraintProd f c g as where Source #

Pair up each item in a Prod f with a witness that f a satisfies some constraint.

Methods

reifyConstraintProd :: Prod f g as -> Prod f (Dict c :. g) as Source #

Instances

Instances details
ReifyConstraint c f as => ReifyConstraintProd List c (f :: k -> Type) (as :: [k]) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

reifyConstraintProd :: Prod List f as -> Prod List (Dict c :. f) as Source #

ReifyConstraintProd Maybe c (g :: k -> Type) ('Nothing :: Maybe k) Source # 
Instance details

Defined in Data.Type.Functor.Product

c (g a2) => ReifyConstraintProd Identity c (g :: a1 -> Type) ('Identity a2 :: Identity a1) Source # 
Instance details

Defined in Data.Type.Functor.Product

c (g a2) => ReifyConstraintProd Maybe c (g :: a1 -> Type) ('Just a2 :: Maybe a1) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

reifyConstraintProd :: Prod Maybe g ('Just a2) -> Prod Maybe (Dict c :. g) ('Just a2) Source #

(c (g a2), ReifyConstraint c g as) => ReifyConstraintProd NonEmpty c (g :: a1 -> Type) (a2 ':| as :: NonEmpty a1) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

reifyConstraintProd :: Prod NonEmpty g (a2 ':| as) -> Prod NonEmpty (Dict c :. g) (a2 ':| as) Source #

c (g a) => ReifyConstraintProd (Either j) c (g :: b -> Type) ('Right a :: Either j b) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

reifyConstraintProd :: Prod (Either j) g ('Right a) -> Prod (Either j) (Dict c :. g) ('Right a) Source #

ReifyConstraintProd (Either j) c (g :: k -> Type) ('Left e :: Either j k) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

reifyConstraintProd :: Prod (Either j) g ('Left e) -> Prod (Either j) (Dict c :. g) ('Left e) Source #

c (g a) => ReifyConstraintProd ((,) j) c (g :: k -> Type) ('(w, a) :: (j, k)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

reifyConstraintProd :: Prod ((,) j) g '(w, a) -> Prod ((,) j) (Dict c :. g) '(w, a) Source #

type AllConstrainedProd c as = AllConstrained c (ToList as) Source #

A convenient wrapper over AllConstrained that works for any Foldable f.

Functions

indexProd :: FProd f => Elem f as a -> Prod f g as -> g a Source #

Use an Elem to index a value out of a Prod.

mapProd :: FProd f => (forall a. g a -> h a) -> Prod f g as -> Prod f h as Source #

Map a RankN function over a Prod. The generalization of rmap.

foldMapProd :: (FProd f, Monoid m) => (forall a. g a -> m) -> Prod f g as -> m Source #

Map a RankN function over a Prod and collect the results as a Monoid.

hmap :: FProd f => Sing ff -> (forall a. g a -> h (ff @@ a)) -> Prod f g as -> Prod f h (Fmap ff as) Source #

Map a type-changing function over every item in a Prod.

zipProd :: FProd f => Prod f g as -> Prod f h as -> Prod f (g :*: h) as Source #

Zip together the values in two Prods.

imapProd :: FProd f => (forall a. Elem f as a -> g a -> h a) -> Prod f g as -> Prod f h as Source #

mapProd, but with access to the index at each element.

itraverseProd :: (FProd f, Applicative m) => (forall a. Elem f as a -> g a -> m (h a)) -> Prod f g as -> m (Prod f h as) Source #

traverseProd, but with access to the index at each element.

ifoldMapProd :: (FProd f, Monoid m) => (forall a. Elem f as a -> g a -> m) -> Prod f g as -> m Source #

foldMapProd, but with access to the index at each element.

generateProd :: (FProd f, PureProd f as) => (forall a. Elem f as a -> g a) -> Prod f g as Source #

Construct a Prod purely by providing a generating function for each index.

generateProdA :: (FProd f, PureProd f as, Applicative m) => (forall a. Elem f as a -> m (g a)) -> m (Prod f g as) Source #

Construct a Prod in an Applicative context by providing a generating function for each index.

selectProd :: FProd f => Prod f (Elem f as) bs -> Prod f g as -> Prod f g bs Source #

Rearrange or permute the items in a Prod based on a Prod of indices.

selectProd (IS IZ :& IZ :& RNil) ("hi" :& "bye" :& "ok" :& RNil)
     == "bye" :& "hi" :& RNil

indices :: (FProd f, PureProd f as) => Prod f (Elem f as) as Source #

Generate a Prod of indices for an as.

eqProd :: (FProd f, ReifyConstraintProd f Eq g as) => Prod f g as -> Prod f g as -> Bool Source #

An implementation of equality testing for all FProd instances, as long as each of the items are instances of Eq.

compareProd :: (FProd f, ReifyConstraintProd f Ord g as) => Prod f g as -> Prod f g as -> Ordering Source #

An implementation of order comparison for all FProd instances, as long as each of the items are instances of Ord.

Over singletons

indexSing Source #

Arguments

:: forall f as a. FProd f 
=> Elem f as a

Witness

-> Sing as

Collection

-> Sing a 

Extract the item from the container witnessed by the Elem

singShape :: FProd f => Sing as -> Shape f as Source #

Convert a Sing as into a Shape f as, witnessing the shape of of as but dropping all of its values.

foldMapSing :: forall f k (as :: f k) m. (FProd f, Monoid m) => (forall (a :: k). Sing a -> m) -> Sing as -> m Source #

A foldMap over all items in a collection.

ifoldMapSing :: forall f k (as :: f k) m. (FProd f, Monoid m) => (forall a. Elem f as a -> Sing a -> m) -> Sing as -> m Source #

foldMapSing but with access to the index.

Instances

data Rec (a :: u -> Type) (b :: [u]) where #

A record is parameterized by a universe u, an interpretation f and a list of rows rs. The labels or indices of the record are given by inhabitants of the kind u; the type of values at any label r :: u is given by its interpretation f r :: *.

Constructors

RNil :: forall {u} (a :: u -> Type). Rec a ('[] :: [u]) 
(:&) :: forall {u} (a :: u -> Type) (r :: u) (rs :: [u]). !(a r) -> !(Rec a rs) -> Rec a (r ': rs) infixr 7 

Instances

Instances details
RecSubset (Rec :: (k -> Type) -> [k] -> Type) ('[] :: [k]) (ss :: [k]) ('[] :: [Nat]) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f #

Methods

rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f '[] -> g (Rec f '[])) -> Rec f ss -> g (Rec f ss) #

rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f '[] #

rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f '[] -> Rec f ss -> Rec f ss #

(RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f #

Methods

rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) #

rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) #

rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss #

RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) 'Z 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (r ': rs) -> g (Rec f (r' ': rs)) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (r ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (r ': rs) -> Rec f (r' ': rs) #

(RIndex r (s ': rs) ~ 'S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) ('S i) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (s ': rs) -> g (Rec f (s ': rs')) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (s ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (s ': rs) -> Rec f (s ': rs') #

TestCoercion f => TestCoercion (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testCoercion :: forall (a :: k) (b :: k). Rec f a -> Rec f b -> Maybe (Coercion a b) #

TestEquality f => TestEquality (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testEquality :: forall (a :: k) (b :: k). Rec f a -> Rec f b -> Maybe (a :~: b) #

(Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f (r ': rs) -> Int #

alignment :: Rec f (r ': rs) -> Int #

peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) #

pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) #

pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () #

peek :: Ptr (Rec f (r ': rs)) -> IO (Rec f (r ': rs)) #

poke :: Ptr (Rec f (r ': rs)) -> Rec f (r ': rs) -> IO () #

Storable (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f '[] -> Int #

alignment :: Rec f '[] -> Int #

peekElemOff :: Ptr (Rec f '[]) -> Int -> IO (Rec f '[]) #

pokeElemOff :: Ptr (Rec f '[]) -> Int -> Rec f '[] -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f '[]) #

pokeByteOff :: Ptr b -> Int -> Rec f '[] -> IO () #

peek :: Ptr (Rec f '[]) -> IO (Rec f '[]) #

poke :: Ptr (Rec f '[]) -> Rec f '[] -> IO () #

(Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f (r ': rs) #

mappend :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

mconcat :: [Rec f (r ': rs)] -> Rec f (r ': rs) #

Monoid (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f '[] #

mappend :: Rec f '[] -> Rec f '[] -> Rec f '[] #

mconcat :: [Rec f '[]] -> Rec f '[] #

(Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

sconcat :: NonEmpty (Rec f (r ': rs)) -> Rec f (r ': rs) #

stimes :: Integral b => b -> Rec f (r ': rs) -> Rec f (r ': rs) #

Semigroup (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f '[] -> Rec f '[] -> Rec f '[] #

sconcat :: NonEmpty (Rec f '[]) -> Rec f '[] #

stimes :: Integral b => b -> Rec f '[] -> Rec f '[] #

Generic (Rec f rs) => Generic (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f (r ': rs)) :: Type -> Type #

Methods

from :: Rec f (r ': rs) -> Rep (Rec f (r ': rs)) x #

to :: Rep (Rec f (r ': rs)) x -> Rec f (r ': rs) #

Generic (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f '[]) :: Type -> Type #

Methods

from :: Rec f '[] -> Rep (Rec f '[]) x #

to :: Rep (Rec f '[]) x -> Rec f '[] #

(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Instance details

Defined in Data.Vinyl.Core

Methods

showsPrec :: Int -> Rec f rs -> ShowS #

show :: Rec f rs -> String #

showList :: [Rec f rs] -> ShowS #

ReifyConstraint NFData f xs => NFData (Rec f xs) 
Instance details

Defined in Data.Vinyl.Core

Methods

rnf :: Rec f xs -> () #

(Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(/=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

Eq (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f '[] -> Rec f '[] -> Bool #

(/=) :: Rec f '[] -> Rec f '[] -> Bool #

(Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering #

(<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

Ord (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f '[] -> Rec f '[] -> Ordering #

(<) :: Rec f '[] -> Rec f '[] -> Bool #

(<=) :: Rec f '[] -> Rec f '[] -> Bool #

(>) :: Rec f '[] -> Rec f '[] -> Bool #

(>=) :: Rec f '[] -> Rec f '[] -> Bool #

max :: Rec f '[] -> Rec f '[] -> Rec f '[] #

min :: Rec f '[] -> Rec f '[] -> Rec f '[] #

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type Rep (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

type Rep (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

data Index :: [k] -> k -> Type where Source #

Witness an item in a type-level list by providing its index.

The number of ISs correspond to the item's position in the list.

IZ         :: Index '[5,10,2] 5
IS IZ      :: Index '[5,10,2] 10
IS (IS IZ) :: Index '[5,10,2] 2

Constructors

IZ :: Index (a ': as) a 
IS :: Index bs a -> Index (b ': bs) a 

Instances

Instances details
Show (Index as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> Index as a -> ShowS #

show :: Index as a -> String #

showList :: [Index as a] -> ShowS #

Eq (Index as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: Index as a -> Index as a -> Bool #

(/=) :: Index as a -> Index as a -> Bool #

Ord (Index as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: Index as a -> Index as a -> Ordering #

(<) :: Index as a -> Index as a -> Bool #

(<=) :: Index as a -> Index as a -> Bool #

(>) :: Index as a -> Index as a -> Bool #

(>=) :: Index as a -> Index as a -> Bool #

max :: Index as a -> Index as a -> Index as a #

min :: Index as a -> Index as a -> Index as a #

SingKind (Index as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Demote (Index as a) = (r :: Type) #

Methods

fromSing :: forall (a0 :: Index as a). Sing a0 -> Demote (Index as a) #

toSing :: Demote (Index as a) -> SomeSing (Index as a) #

SDecide (Index as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(%~) :: forall (a0 :: Index as a) (b :: Index as a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

SingI ('IZ :: Index (a ': as) a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

sing :: Sing 'IZ #

SingI i => SingI ('IS i :: Index (b ': bs) a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

sing :: Sing ('IS i) #

type Demote (Index as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Demote (Index as a) = Index as a
type Sing Source # 
Instance details

Defined in Data.Type.Functor.Product

type Sing = SIndex as a

withPureProdList :: Rec f as -> ((RecApplicative as, PureProd List as) => r) -> r Source #

A stronger version of withPureProd for Rec, providing a RecApplicative instance as well.

data PMaybe :: (k -> Type) -> Maybe k -> Type where Source #

A PMaybe f 'Nothing contains nothing, and a PMaybe f ('Just a) contains an f a.

In practice this can be useful to write polymorphic functions/abstractions that contain an argument that can be "turned off" for different instances.

Constructors

PNothing :: PMaybe f 'Nothing 
PJust :: f a -> PMaybe f ('Just a) 

Instances

Instances details
ReifyConstraintProd Maybe Show f as => Show (PMaybe f as) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> PMaybe f as -> ShowS #

show :: PMaybe f as -> String #

showList :: [PMaybe f as] -> ShowS #

ReifyConstraintProd Maybe Eq f as => Eq (PMaybe f as) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: PMaybe f as -> PMaybe f as -> Bool #

(/=) :: PMaybe f as -> PMaybe f as -> Bool #

(ReifyConstraintProd Maybe Eq f as, ReifyConstraintProd Maybe Ord f as) => Ord (PMaybe f as) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: PMaybe f as -> PMaybe f as -> Ordering #

(<) :: PMaybe f as -> PMaybe f as -> Bool #

(<=) :: PMaybe f as -> PMaybe f as -> Bool #

(>) :: PMaybe f as -> PMaybe f as -> Bool #

(>=) :: PMaybe f as -> PMaybe f as -> Bool #

max :: PMaybe f as -> PMaybe f as -> PMaybe f as #

min :: PMaybe f as -> PMaybe f as -> PMaybe f as #

data IJust :: Maybe k -> k -> Type where Source #

Witness an item in a type-level Maybe by proving the Maybe is Just.

Constructors

IJust :: IJust ('Just a) a 

Instances

Instances details
Read (IJust ('Just a) a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

readsPrec :: Int -> ReadS (IJust ('Just a) a) #

readList :: ReadS [IJust ('Just a) a] #

readPrec :: ReadPrec (IJust ('Just a) a) #

readListPrec :: ReadPrec [IJust ('Just a) a] #

Show (IJust as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> IJust as a -> ShowS #

show :: IJust as a -> String #

showList :: [IJust as a] -> ShowS #

Eq (IJust as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: IJust as a -> IJust as a -> Bool #

(/=) :: IJust as a -> IJust as a -> Bool #

Ord (IJust as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: IJust as a -> IJust as a -> Ordering #

(<) :: IJust as a -> IJust as a -> Bool #

(<=) :: IJust as a -> IJust as a -> Bool #

(>) :: IJust as a -> IJust as a -> Bool #

(>=) :: IJust as a -> IJust as a -> Bool #

max :: IJust as a -> IJust as a -> IJust as a #

min :: IJust as a -> IJust as a -> IJust as a #

SingKind (IJust as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Demote (IJust as a) = (r :: Type) #

Methods

fromSing :: forall (a0 :: IJust as a). Sing a0 -> Demote (IJust as a) #

toSing :: Demote (IJust as a) -> SomeSing (IJust as a) #

SDecide (IJust as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(%~) :: forall (a0 :: IJust as a) (b :: IJust as a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

SingI ('IJust :: IJust ('Just a) a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

sing :: Sing 'IJust #

type Demote (IJust as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Demote (IJust as a) = IJust as a
type Sing Source # 
Instance details

Defined in Data.Type.Functor.Product

type Sing = SIJust as a

data PEither :: (k -> Type) -> Either j k -> Type where Source #

A PEither f ('Left e) contains Sing e, and a PMaybe f ('Right a) contains an f a.

In practice this can be useful in the same situatinos that PMaybe can, but with an extra value in the case where value f is "turned off" with Left.

Constructors

PLeft :: Sing e -> PEither f ('Left e) 
PRight :: f a -> PEither f ('Right a) 

Instances

Instances details
(SShow j, ReifyConstraintProd (Either j) Show f as) => Show (PEither f as) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> PEither f as -> ShowS #

show :: PEither f as -> String #

showList :: [PEither f as] -> ShowS #

data IRight :: Either j k -> k -> Type where Source #

Witness an item in a type-level Either j by proving the Either is Right.

Constructors

IRight :: IRight ('Right a) a 

Instances

Instances details
Read (IRight ('Right a :: Either j k) a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Show (IRight as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> IRight as a -> ShowS #

show :: IRight as a -> String #

showList :: [IRight as a] -> ShowS #

Eq (IRight as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: IRight as a -> IRight as a -> Bool #

(/=) :: IRight as a -> IRight as a -> Bool #

Ord (IRight as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: IRight as a -> IRight as a -> Ordering #

(<) :: IRight as a -> IRight as a -> Bool #

(<=) :: IRight as a -> IRight as a -> Bool #

(>) :: IRight as a -> IRight as a -> Bool #

(>=) :: IRight as a -> IRight as a -> Bool #

max :: IRight as a -> IRight as a -> IRight as a #

min :: IRight as a -> IRight as a -> IRight as a #

SingKind (IRight as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Demote (IRight as a) = (r :: Type) #

Methods

fromSing :: forall (a0 :: IRight as a). Sing a0 -> Demote (IRight as a) #

toSing :: Demote (IRight as a) -> SomeSing (IRight as a) #

SDecide (IRight as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(%~) :: forall (a0 :: IRight as a) (b :: IRight as a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

SingI ('IRight :: IRight ('Right a :: Either j k) a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

sing :: Sing 'IRight #

type Demote (IRight as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Demote (IRight as a) = IRight as a
type Sing Source # 
Instance details

Defined in Data.Type.Functor.Product

type Sing = SIRight as a

data NERec :: (k -> Type) -> NonEmpty k -> Type where Source #

A non-empty version of Rec.

Constructors

(:&|) :: f a -> Rec f as -> NERec f (a ':| as) infixr 5 

Instances

Instances details
(Show (f a2), RMap as, ReifyConstraint Show f as, RecordToList as) => Show (NERec f (a2 ':| as)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> NERec f (a2 ':| as) -> ShowS #

show :: NERec f (a2 ':| as) -> String #

showList :: [NERec f (a2 ':| as)] -> ShowS #

(Eq (f a2), Eq (Rec f as)) => Eq (NERec f (a2 ':| as)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: NERec f (a2 ':| as) -> NERec f (a2 ':| as) -> Bool #

(/=) :: NERec f (a2 ':| as) -> NERec f (a2 ':| as) -> Bool #

(Ord (f a2), Ord (Rec f as)) => Ord (NERec f (a2 ':| as)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: NERec f (a2 ':| as) -> NERec f (a2 ':| as) -> Ordering #

(<) :: NERec f (a2 ':| as) -> NERec f (a2 ':| as) -> Bool #

(<=) :: NERec f (a2 ':| as) -> NERec f (a2 ':| as) -> Bool #

(>) :: NERec f (a2 ':| as) -> NERec f (a2 ':| as) -> Bool #

(>=) :: NERec f (a2 ':| as) -> NERec f (a2 ':| as) -> Bool #

max :: NERec f (a2 ':| as) -> NERec f (a2 ':| as) -> NERec f (a2 ':| as) #

min :: NERec f (a2 ':| as) -> NERec f (a2 ':| as) -> NERec f (a2 ':| as) #

data NEIndex :: NonEmpty k -> k -> Type where Source #

Witness an item in a type-level NonEmpty by either indicating that it is the "head", or by providing an index in the "tail".

Constructors

NEHead :: NEIndex (a ':| as) a 
NETail :: Index as a -> NEIndex (b ':| as) a 

Instances

Instances details
Show (NEIndex as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> NEIndex as a -> ShowS #

show :: NEIndex as a -> String #

showList :: [NEIndex as a] -> ShowS #

Eq (NEIndex as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: NEIndex as a -> NEIndex as a -> Bool #

(/=) :: NEIndex as a -> NEIndex as a -> Bool #

Ord (NEIndex as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: NEIndex as a -> NEIndex as a -> Ordering #

(<) :: NEIndex as a -> NEIndex as a -> Bool #

(<=) :: NEIndex as a -> NEIndex as a -> Bool #

(>) :: NEIndex as a -> NEIndex as a -> Bool #

(>=) :: NEIndex as a -> NEIndex as a -> Bool #

max :: NEIndex as a -> NEIndex as a -> NEIndex as a #

min :: NEIndex as a -> NEIndex as a -> NEIndex as a #

SingKind (NEIndex as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Demote (NEIndex as a) = (r :: Type) #

Methods

fromSing :: forall (a0 :: NEIndex as a). Sing a0 -> Demote (NEIndex as a) #

toSing :: Demote (NEIndex as a) -> SomeSing (NEIndex as a) #

SDecide (NEIndex as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(%~) :: forall (a0 :: NEIndex as a) (b :: NEIndex as a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

SingI ('NEHead :: NEIndex (a ':| as) a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

sing :: Sing 'NEHead #

SingI i => SingI ('NETail i :: NEIndex (b ':| as) a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

sing :: Sing ('NETail i) #

type Demote (NEIndex as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Demote (NEIndex as a) = NEIndex as a
type Sing Source # 
Instance details

Defined in Data.Type.Functor.Product

type Sing = SNEIndex as a

withPureProdNE :: f a -> Rec f as -> ((RecApplicative as, PureProd NonEmpty (a ':| as)) => r) -> r Source #

A stronger version of withPureProd for NERec, providing a RecApplicative instance as well.

data PTup :: (k -> Type) -> (j, k) -> Type where Source #

A PTup tuples up some singleton with some value; a PTup f '(w, a) contains a Sing w and an f a.

This can be useful for carrying along some witness aside a functor value.

Constructors

PTup :: Sing w -> f a -> PTup f '(w, a) 

Instances

Instances details
(Read (Sing w), Read (f a)) => Read (PTup f '(w, a)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

readsPrec :: Int -> ReadS (PTup f '(w, a)) #

readList :: ReadS [PTup f '(w, a)] #

readPrec :: ReadPrec (PTup f '(w, a)) #

readListPrec :: ReadPrec [PTup f '(w, a)] #

(Show (Sing w), Show (f a)) => Show (PTup f '(w, a)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> PTup f '(w, a) -> ShowS #

show :: PTup f '(w, a) -> String #

showList :: [PTup f '(w, a)] -> ShowS #

(Eq (Sing w), Eq (f a)) => Eq (PTup f '(w, a)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: PTup f '(w, a) -> PTup f '(w, a) -> Bool #

(/=) :: PTup f '(w, a) -> PTup f '(w, a) -> Bool #

(Ord (Sing w), Ord (f a)) => Ord (PTup f '(w, a)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: PTup f '(w, a) -> PTup f '(w, a) -> Ordering #

(<) :: PTup f '(w, a) -> PTup f '(w, a) -> Bool #

(<=) :: PTup f '(w, a) -> PTup f '(w, a) -> Bool #

(>) :: PTup f '(w, a) -> PTup f '(w, a) -> Bool #

(>=) :: PTup f '(w, a) -> PTup f '(w, a) -> Bool #

max :: PTup f '(w, a) -> PTup f '(w, a) -> PTup f '(w, a) #

min :: PTup f '(w, a) -> PTup f '(w, a) -> PTup f '(w, a) #

data ISnd :: (j, k) -> k -> Type where Source #

Trivially witness an item in the second field of a type-level tuple.

Constructors

ISnd :: ISnd '(a, b) b 

Instances

Instances details
Read (ISnd '(a, b) b) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

readsPrec :: Int -> ReadS (ISnd '(a, b) b) #

readList :: ReadS [ISnd '(a, b) b] #

readPrec :: ReadPrec (ISnd '(a, b) b) #

readListPrec :: ReadPrec [ISnd '(a, b) b] #

Show (ISnd as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> ISnd as a -> ShowS #

show :: ISnd as a -> String #

showList :: [ISnd as a] -> ShowS #

Eq (ISnd as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: ISnd as a -> ISnd as a -> Bool #

(/=) :: ISnd as a -> ISnd as a -> Bool #

Ord (ISnd as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: ISnd as a -> ISnd as a -> Ordering #

(<) :: ISnd as a -> ISnd as a -> Bool #

(<=) :: ISnd as a -> ISnd as a -> Bool #

(>) :: ISnd as a -> ISnd as a -> Bool #

(>=) :: ISnd as a -> ISnd as a -> Bool #

max :: ISnd as a -> ISnd as a -> ISnd as a #

min :: ISnd as a -> ISnd as a -> ISnd as a #

SingKind (ISnd as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Demote (ISnd as a) = (r :: Type) #

Methods

fromSing :: forall (a0 :: ISnd as a). Sing a0 -> Demote (ISnd as a) #

toSing :: Demote (ISnd as a) -> SomeSing (ISnd as a) #

SDecide (ISnd as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(%~) :: forall (a0 :: ISnd as a) (b :: ISnd as a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

SingI ('ISnd :: ISnd '(a, b) b) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

sing :: Sing 'ISnd #

type Demote (ISnd as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Demote (ISnd as a) = ISnd as a
type Sing Source # 
Instance details

Defined in Data.Type.Functor.Product

type Sing = SISnd as a

data PIdentity :: (k -> Type) -> Identity k -> Type where Source #

A PIdentity is a trivial functor product; it is simply the functor, itself, alone. PIdentity f (Identity a) is simply f a. This may be useful in conjunction with other combinators.

Constructors

PIdentity :: f a -> PIdentity f ('Identity a) 

Instances

Instances details
Read (f a2) => Read (PIdentity f ('Identity a2)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Show (f a2) => Show (PIdentity f ('Identity a2)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> PIdentity f ('Identity a2) -> ShowS #

show :: PIdentity f ('Identity a2) -> String #

showList :: [PIdentity f ('Identity a2)] -> ShowS #

Eq (f a2) => Eq (PIdentity f ('Identity a2)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) -> Bool #

(/=) :: PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) -> Bool #

Ord (f a2) => Ord (PIdentity f ('Identity a2)) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) -> Ordering #

(<) :: PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) -> Bool #

(<=) :: PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) -> Bool #

(>) :: PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) -> Bool #

(>=) :: PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) -> Bool #

max :: PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) #

min :: PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) -> PIdentity f ('Identity a2) #

data IIdentity :: Identity k -> k -> Type where Source #

Trivially witness the item held in an Identity.

Since: 0.1.3.0

Constructors

IId :: IIdentity ('Identity x) x 

Instances

Instances details
Read (IIdentity ('Identity a) a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Show (IIdentity as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> IIdentity as a -> ShowS #

show :: IIdentity as a -> String #

showList :: [IIdentity as a] -> ShowS #

Eq (IIdentity as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(==) :: IIdentity as a -> IIdentity as a -> Bool #

(/=) :: IIdentity as a -> IIdentity as a -> Bool #

Ord (IIdentity as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

compare :: IIdentity as a -> IIdentity as a -> Ordering #

(<) :: IIdentity as a -> IIdentity as a -> Bool #

(<=) :: IIdentity as a -> IIdentity as a -> Bool #

(>) :: IIdentity as a -> IIdentity as a -> Bool #

(>=) :: IIdentity as a -> IIdentity as a -> Bool #

max :: IIdentity as a -> IIdentity as a -> IIdentity as a #

min :: IIdentity as a -> IIdentity as a -> IIdentity as a #

SingKind (IIdentity as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Associated Types

type Demote (IIdentity as a) = (r :: Type) #

Methods

fromSing :: forall (a0 :: IIdentity as a). Sing a0 -> Demote (IIdentity as a) #

toSing :: Demote (IIdentity as a) -> SomeSing (IIdentity as a) #

SDecide (IIdentity as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

(%~) :: forall (a0 :: IIdentity as a) (b :: IIdentity as a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

SingI ('IId :: IIdentity ('Identity x) x) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

sing :: Sing 'IId #

type Demote (IIdentity as a) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Demote (IIdentity as a) = IIdentity as a
type Sing Source # 
Instance details

Defined in Data.Type.Functor.Product

type Sing = SIIdentity as a

sameIndexVal :: Index as a -> Index as b -> Maybe (a :~: b) Source #

Test if two indices point to the same item in a list.

We have to return a Maybe here instead of a Decision, because it might be the case that the same item might be duplicated in a list. Therefore, even if two indices are different, we cannot prove that the values they point to are different.

sameNEIndexVal :: NEIndex as a -> NEIndex as b -> Maybe (a :~: b) Source #

Test if two indices point to the same item in a non-empty list.

We have to return a Maybe here instead of a Decision, because it might be the case that the same item might be duplicated in a list. Therefore, even if two indices are different, we cannot prove that the values they point to are different.

Interfacing with vinyl

rElemIndex :: forall r rs i. (RElem r rs i, PureProd List rs) => Index rs r Source #

Produce an Index from an RElem constraint.

indexRElem :: (SDecide k, SingI (a :: k), RecApplicative as, FoldRec as as) => Index as a -> (RElem a as (RIndex a as) => r) -> r Source #

If we have Index as a, we should also be able to create an item that would require RElem a as (RIndex as a). Along with rElemIndex, this essentially converts between the indexing system in this library and the indexing system of vinyl.

toCoRec :: forall k (as :: [k]) a f. (RecApplicative as, FoldRec as as) => Index as a -> f a -> CoRec f as Source #

Use an Index to inject an f a into a CoRec.

Singletons

data SIndex (as :: [k]) (a :: k) :: Index as a -> Type where Source #

Kind-indexed singleton for Index.

Constructors

SIZ :: SIndex (a ': as) a 'IZ 
SIS :: SIndex bs a i -> SIndex (b ': bs) a ('IS i) 

Instances

Instances details
Show (SIndex as a i) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> SIndex as a i -> ShowS #

show :: SIndex as a i -> String #

showList :: [SIndex as a i] -> ShowS #

data SIJust (as :: Maybe k) (a :: k) :: IJust as a -> Type where Source #

Kind-indexed singleton for IJust.

Constructors

SIJust :: SIJust ('Just a) a 'IJust 

Instances

Instances details
Show (SIJust as a i) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> SIJust as a i -> ShowS #

show :: SIJust as a i -> String #

showList :: [SIJust as a i] -> ShowS #

data SIRight (as :: Either j k) (a :: k) :: IRight as a -> Type where Source #

Kind-indexed singleton for IRight.

Constructors

SIRight :: SIRight ('Right a) a 'IRight 

Instances

Instances details
Show (SIRight as a i) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> SIRight as a i -> ShowS #

show :: SIRight as a i -> String #

showList :: [SIRight as a i] -> ShowS #

data SNEIndex (as :: NonEmpty k) (a :: k) :: NEIndex as a -> Type where Source #

Kind-indexed singleton for NEIndex.

Constructors

SNEHead :: SNEIndex (a ':| as) a 'NEHead 
SNETail :: SIndex as a i -> SNEIndex (b ':| as) a ('NETail i) 

Instances

Instances details
Show (SNEIndex as a i) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> SNEIndex as a i -> ShowS #

show :: SNEIndex as a i -> String #

showList :: [SNEIndex as a i] -> ShowS #

data SISnd (as :: (j, k)) (a :: k) :: ISnd as a -> Type where Source #

Kind-indexed singleton for ISnd.

Constructors

SISnd :: SISnd '(a, b) b 'ISnd 

Instances

Instances details
Show (SISnd as a i) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> SISnd as a i -> ShowS #

show :: SISnd as a i -> String #

showList :: [SISnd as a i] -> ShowS #

data SIIdentity (as :: Identity k) (a :: k) :: IIdentity as a -> Type where Source #

Kind-indexed singleton for IIdentity.

Since: 0.1.5.0

Constructors

SIId :: SIIdentity ('Identity a) a 'IId 

Instances

Instances details
Show (SIIdentity as a i) Source # 
Instance details

Defined in Data.Type.Functor.Product

Methods

showsPrec :: Int -> SIIdentity as a i -> ShowS #

show :: SIIdentity as a i -> String #

showList :: [SIIdentity as a i] -> ShowS #

Defunctionalization symbols

data ElemSym0 (f :: Type -> Type) :: f k ~> (k ~> Type) Source #

Instances

Instances details
type Apply (ElemSym0 f :: TyFun (f k) (k ~> Type) -> Type) (as :: f k) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Apply (ElemSym0 f :: TyFun (f k) (k ~> Type) -> Type) (as :: f k) = ElemSym1 f as

data ElemSym1 (f :: Type -> Type) :: f k -> k ~> Type Source #

Instances

Instances details
type Apply (ElemSym1 f as :: TyFun k Type -> Type) (a :: k) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Apply (ElemSym1 f as :: TyFun k Type -> Type) (a :: k) = Elem f as a

type ElemSym2 (f :: Type -> Type) (as :: f k) (a :: k) = Elem f as a Source #

data ProdSym0 (f :: Type -> Type) :: (k -> Type) ~> (f k ~> Type) Source #

Instances

Instances details
type Apply (ProdSym0 f :: TyFun (k -> Type) (f k ~> Type) -> Type) (g :: k -> Type) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Apply (ProdSym0 f :: TyFun (k -> Type) (f k ~> Type) -> Type) (g :: k -> Type) = ProdSym1 f g

data ProdSym1 (f :: Type -> Type) :: (k -> Type) -> f k ~> Type Source #

Instances

Instances details
type Apply (ProdSym1 f g :: TyFun (f k) Type -> Type) (as :: f k) Source # 
Instance details

Defined in Data.Type.Functor.Product

type Apply (ProdSym1 f g :: TyFun (f k) Type -> Type) (as :: f k) = Prod f g as

type ProdSym2 (f :: Type -> Type) (g :: k -> Type) (as :: f k) = Prod f g as Source #