functor-products-0.1.0.0: General functor products for various Foldable instances

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Type.Functor.XProduct

Contents

Description

Generalize Data.Vinyl.XRec: provides a version of products in Data.Type.Functor.Product that "erases" newtype wrappers and other syntactical noise.

Data.Type.Functor.Product is the "main functionality", but this module provides an alternative interface that may be more convenient in some situations, in the same way that XRec can be more convenient than Rec in some situations.

Synopsis

Documentation

type XProd f g = (Prod f (XData g) :: f k -> Type) Source #

Generalize XRec to work over any foldable f that implements FProd. See Prod and FProd for more information.

fromXProd :: forall f g as. (FProd f, PureProdC f (IsoHKD g) as) => XProd f g as -> Prod f g as Source #

Convert an XProd back into a regular ol' Prod.

toXProd :: forall f g as. (FProd f, PureProdC f (IsoHKD g) as) => Prod f g as -> XProd f g as Source #

Convert a Prod into a fancy XProd.

Functions

mapProdX :: forall f g h as. FProd f => (forall a. HKD g a -> HKD h a) -> XProd f g as -> XProd f h as Source #

Convenient wrapper over mapProd that lets you deal with the "simplified" inner types. Generalizes rmapX.

mapProdXEndo :: forall f g as. FProd f => (forall a. HKD g a -> HKD g a) -> XProd f g as -> XProd f g as Source #

A version of mapProdX that doesn't change the context g; this can be easier for type inference in some situations. Generalizes rmapXEndo.

imapProdX :: forall f g h as. FProd f => (forall a. Elem f as a -> HKD g a -> HKD h a) -> XProd f g as -> XProd f h as Source #

A version of mapProdX that passes along the index Elem with each value. This can help with type inference in some situations.

zipWithProdX :: forall f g h j as. FProd f => (forall a. HKD g a -> HKD h a -> HKD j a) -> XProd f g as -> XProd f h as -> XProd f j as Source #

Zip two XProds together by supplying a function that works on their simplified HKD values.

ixProdX :: FProd f => Elem f as a -> Lens' (XProd f g as) (HKD g a) Source #

Given an index into an XProd, provides a lens into the simplified item that that index points to.

traverseProdX :: forall f g h m as. (FProd f, Applicative m) => (forall a. HKD g a -> m (HKD h a)) -> XProd f g as -> m (XProd f h as) Source #

Convenient wrapper over traverseProd that lets you deal with the "simplified" inner types.

traverseProdXEndo :: forall f g m as. (FProd f, Applicative m) => (forall a. HKD g a -> m (HKD g a)) -> XProd f g as -> m (XProd f g as) Source #

A version of traverseProdX that doesn't change the context g; this can be easier for type inference in some situations.

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

A version of traverseProdX that passes along the index Elem with each value. This can help with type inference in some situations.

foldMapProdX :: forall f g m as. (FProd f, Monoid m) => (forall a. HKD g a -> m) -> XProd f g as -> m Source #

Convenient wrapper over foldMapProd that lets you deal with the "simplified" inner types.

ifoldMapProdX :: forall f g m as. (FProd f, Monoid m) => (forall a. Elem f as a -> HKD g a -> m) -> XProd f g as -> m Source #

A version of foldMapProdX that passes along the index Elem with each value. This can help with type inference in some situations.

Instances

type XRec (f :: u -> Type) = Rec (XData f) #

pattern (::&) :: forall a (f :: a -> Type) (r :: a) (rs :: [a]). HKD f r -> XRec f rs -> XRec f (r ': rs) infixr 7 #

pattern XRNil :: forall u (f :: u -> Type). XRec f ([] :: [u]) #

type XMaybe f = PMaybe (XData f) Source #

PMaybe over HKD-d types.

pattern XJust :: HKD f a -> XMaybe f (Just a) Source #

PJust for XMaybe: allows you to provide the simplified type.

type XEither f = PEither (XData f) Source #

PEither over HKD-d types.

pattern XLeft :: Sing e -> XEither f (Left e) Source #

pattern XRight :: HKD f a -> XEither f (Right a) Source #

PRight for XEither: allows you to provide the simplified type.

type XNERec f = NERec (XData f) Source #

NERec over HKD-d types.

pattern (::&|) :: HKD f a -> XRec f as -> XNERec f (a :| as) Source #

A version of :&| that allows you to provide the simplified type, for XNERec.

type XTup f = PTup (XData f) Source #

PTup over HKD-d types.

pattern XTup :: Sing w -> HKD f a -> XTup f '(w, a) Source #

A version of PTup that allows you to provide the simplified type, for XTup.

type XIdentity f = PIdentity (XData f) Source #

PIdentity over HKD-d types.

pattern XIdentity :: HKD f a -> XIdentity f (Identity a) Source #

A version of PIdentity that allows you to provide the simplified type, for XIdentity.