large-generics-0.2.1: Generic programming API for large-records and large-anon
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Record.Generic.Rep

Description

Operations on the generic representation

We also re-export some non-derive functions to clarify where they belong in this list.

This module is intended for qualified import.

import qualified Data.Record.Generic.Rep as Rep

TODO: Could we provide instances for the generics-sop type classes? Might lessen the pain of switching between the two or using both?

Synopsis

Documentation

newtype Rep f a Source #

Representation of some record a

The f parameter describes which functor has been applied to all fields of the record; in other words Rep I is isomorphic to the record itself.

Constructors

Rep (SmallArray (f Any)) 

Instances

Instances details
Show x => Show (Rep (K x :: Type -> Type) a) Source # 
Instance details

Defined in Data.Record.Generic.Rep.Internal

Methods

showsPrec :: Int -> Rep (K x) a -> ShowS #

show :: Rep (K x) a -> String #

showList :: [Rep (K x) a] -> ShowS #

Eq x => Eq (Rep (K x :: Type -> Type) a) Source # 
Instance details

Defined in Data.Record.Generic.Rep.Internal

Methods

(==) :: Rep (K x) a -> Rep (K x) a -> Bool #

(/=) :: Rep (K x) a -> Rep (K x) a -> Bool #

Functor

map :: Generic a => (forall x. f x -> g x) -> Rep f a -> Rep g a Source #

mapM :: (Applicative m, Generic a) => (forall x. f x -> m (g x)) -> Rep f a -> m (Rep g a) Source #

cmap :: (Generic a, Constraints a c) => Proxy c -> (forall x. c x => f x -> g x) -> Rep f a -> Rep g a Source #

cmapM :: forall m f g c a. (Generic a, Applicative m, Constraints a c) => Proxy c -> (forall x. c x => f x -> m (g x)) -> Rep f a -> m (Rep g a) Source #

Zipping

zip :: Generic a => Rep f a -> Rep g a -> Rep (Product f g) a Source #

zipWith :: Generic a => (forall x. f x -> g x -> h x) -> Rep f a -> Rep g a -> Rep h a Source #

zipWithM :: forall m f g h a. (Generic a, Applicative m) => (forall x. f x -> g x -> m (h x)) -> Rep f a -> Rep g a -> m (Rep h a) Source #

czipWith :: (Generic a, Constraints a c) => Proxy c -> (forall x. c x => f x -> g x -> h x) -> Rep f a -> Rep g a -> Rep h a Source #

czipWithM :: forall m f g h c a. (Generic a, Applicative m, Constraints a c) => Proxy c -> (forall x. c x => f x -> g x -> m (h x)) -> Rep f a -> Rep g a -> m (Rep h a) Source #

Foldable

collapse :: Rep (K a) b -> [a] Source #

Traversable

sequenceA :: Applicative m => Rep (m :.: f) a -> m (Rep f a) Source #

Applicable

pure :: forall f a. Generic a => (forall x. f x) -> Rep f a Source #

cpure :: (Generic a, Constraints a c) => Proxy c -> (forall x. c x => f x) -> Rep f a Source #

ap :: forall f g a. Generic a => Rep (f -.-> g) a -> Rep f a -> Rep g a Source #

Higher-order version of *

Lazy in the second argument.

Array-like interface

data Index a x Source #

getAtIndex :: Index a x -> Rep f a -> f x Source #

putAtIndex :: Index a x -> f x -> Rep f a -> Rep f a Source #

updateAtIndex :: Functor m => Index a x -> (f x -> m (f x)) -> Rep f a -> m (Rep f a) Source #

allIndices :: forall a. Generic a => Rep (Index a) a Source #

mapWithIndex :: forall f g a. Generic a => (forall x. Index a x -> f x -> g x) -> Rep f a -> Rep g a Source #

Map with index

This is an important building block in this module. Crucially, mapWithIndex f a is lazy in a, reading elements from a only if and when f demands them.