extensible-0.4.10: Extensible, efficient, optics-friendly data types and effects

Copyright(c) Fumiaki Kinoshita 2018
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Wrapper

Description

 
Synopsis

Documentation

class Wrapper (h :: k -> *) where Source #

The extensible data types should take k -> * as a parameter. This class allows us to take a shortcut for direct representation.

Minimal complete definition

_Wrapper

Associated Types

type Repr h (v :: k) :: * Source #

Repr h v is the actual representation of h v.

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (h v) (Repr h v) Source #

This is an isomorphism between h v and Repr h v.

_Wrapper :: Iso' (h v) (Repr h v)
Instances
Wrapper (Proxy :: k -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr Proxy v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (Proxy v) (Repr Proxy v) Source #

Wrapper (Const' a :: k -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr (Const' a) v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (Const' a v) (Repr (Const' a) v) Source #

Wrapper h => Wrapper (Nullable h :: k -> *) Source # 
Instance details

Defined in Data.Extensible.Nullable

Associated Types

type Repr (Nullable h) v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (Nullable h v) (Repr (Nullable h) v) Source #

Wrapper (OptionDescr h :: k -> *) Source # 
Instance details

Defined in Data.Extensible.GetOpt

Associated Types

type Repr (OptionDescr h) v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (OptionDescr h v) (Repr (OptionDescr h) v) Source #

(Wrapper f, Wrapper g) => Wrapper (Prod f g :: k -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr (Prod f g) v :: * Source #

Methods

_Wrapper :: (Functor f0, Profunctor p) => Optic' p f0 (Prod f g v) (Repr (Prod f g) v) Source #

Wrapper h => Wrapper (Match h r :: k -> *) Source # 
Instance details

Defined in Data.Extensible.Match

Associated Types

type Repr (Match h r) v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (Match h r v) (Repr (Match h r) v) Source #

(Functor f, Wrapper g) => Wrapper (Comp f g :: k -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr (Comp f g) v :: * Source #

Methods

_Wrapper :: (Functor f0, Profunctor p) => Optic' p f0 (Comp f g v) (Repr (Comp f g) v) Source #

Wrapper [] Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr [] v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f [v] (Repr [] v) Source #

Wrapper Maybe Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr Maybe v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (Maybe v) (Repr Maybe v) Source #

Wrapper Identity Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr Identity v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (Identity v) (Repr Identity v) Source #

Wrapper (Either e :: * -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr (Either e) v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (Either e v) (Repr (Either e) v) Source #

Wrapper h => Wrapper (Field h :: Assoc k v -> *) Source # 
Instance details

Defined in Data.Extensible.Field

Associated Types

type Repr (Field h) v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (Field h v0) (Repr (Field h) v0) Source #

_WrapperAs :: (Functor f, Profunctor p, Wrapper h) => proxy v -> Optic' p f (h v) (Repr h v) Source #

Restricted version of _Wrapper. It is useful for eliminating ambiguousness.

newtype Const' a x Source #

Poly-kinded Const

Constructors

Const' 

Fields

Instances
Wrapper (Const' a :: k -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr (Const' a) v :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (Const' a v) (Repr (Const' a) v) Source #

Unbox a => Vector Vector (Const' a b) # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Const' a b) -> m (Vector (Const' a b)) #

basicUnsafeThaw :: PrimMonad m => Vector (Const' a b) -> m (Mutable Vector (PrimState m) (Const' a b)) #

basicLength :: Vector (Const' a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Const' a b) -> Vector (Const' a b) #

basicUnsafeIndexM :: Monad m => Vector (Const' a b) -> Int -> m (Const' a b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Const' a b) -> Vector (Const' a b) -> m () #

elemseq :: Vector (Const' a b) -> Const' a b -> b0 -> b0 #

Unbox a => MVector MVector (Const' a b) # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

basicLength :: MVector s (Const' a b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Const' a b) -> MVector s (Const' a b) #

basicOverlaps :: MVector s (Const' a b) -> MVector s (Const' a b) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Const' a b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Const' a b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Const' a b -> m (MVector (PrimState m) (Const' a b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Const' a b) -> Int -> m (Const' a b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Const' a b) -> Int -> Const' a b -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Const' a b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Const' a b) -> Const' a b -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Const' a b) -> MVector (PrimState m) (Const' a b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Const' a b) -> MVector (PrimState m) (Const' a b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Const' a b) -> Int -> m (MVector (PrimState m) (Const' a b)) #

FromBits r a => FromBits r (Const' a b) Source # 
Instance details

Defined in Data.Extensible.Bits

Associated Types

type BitWidth (Const' a b) :: Nat Source #

Methods

fromBits :: r -> Const' a b Source #

toBits :: Const' a b -> r Source #

Functor (Const' a :: * -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

fmap :: (a0 -> b) -> Const' a a0 -> Const' a b #

(<$) :: a0 -> Const' a b -> Const' a a0 #

Foldable (Const' a :: * -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

fold :: Monoid m => Const' a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Const' a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Const' a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Const' a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Const' a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Const' a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Const' a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Const' a a0 -> a0 #

toList :: Const' a a0 -> [a0] #

null :: Const' a a0 -> Bool #

length :: Const' a a0 -> Int #

elem :: Eq a0 => a0 -> Const' a a0 -> Bool #

maximum :: Ord a0 => Const' a a0 -> a0 #

minimum :: Ord a0 => Const' a a0 -> a0 #

sum :: Num a0 => Const' a a0 -> a0 #

product :: Num a0 => Const' a a0 -> a0 #

Traversable (Const' a :: * -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

traverse :: Applicative f => (a0 -> f b) -> Const' a a0 -> f (Const' a b) #

sequenceA :: Applicative f => Const' a (f a0) -> f (Const' a a0) #

mapM :: Monad m => (a0 -> m b) -> Const' a a0 -> m (Const' a b) #

sequence :: Monad m => Const' a (m a0) -> m (Const' a a0) #

Eq a => Eq (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

(==) :: Const' a x -> Const' a x -> Bool #

(/=) :: Const' a x -> Const' a x -> Bool #

Ord a => Ord (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

compare :: Const' a x -> Const' a x -> Ordering #

(<) :: Const' a x -> Const' a x -> Bool #

(<=) :: Const' a x -> Const' a x -> Bool #

(>) :: Const' a x -> Const' a x -> Bool #

(>=) :: Const' a x -> Const' a x -> Bool #

max :: Const' a x -> Const' a x -> Const' a x #

min :: Const' a x -> Const' a x -> Const' a x #

Show a => Show (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

showsPrec :: Int -> Const' a x -> ShowS #

show :: Const' a x -> String #

showList :: [Const' a x] -> ShowS #

Generic (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Rep (Const' a x) :: * -> * #

Methods

from :: Const' a x -> Rep (Const' a x) x0 #

to :: Rep (Const' a x) x0 -> Const' a x #

Semigroup a => Semigroup (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

(<>) :: Const' a x -> Const' a x -> Const' a x #

sconcat :: NonEmpty (Const' a x) -> Const' a x #

stimes :: Integral b => b -> Const' a x -> Const' a x #

Monoid a => Monoid (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

mempty :: Const' a x #

mappend :: Const' a x -> Const' a x -> Const' a x #

mconcat :: [Const' a x] -> Const' a x #

Arbitrary a => Arbitrary (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

arbitrary :: Gen (Const' a x) #

shrink :: Const' a x -> [Const' a x] #

Hashable a => Hashable (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

hashWithSalt :: Int -> Const' a x -> Int #

hash :: Const' a x -> Int #

NFData a => NFData (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

rnf :: Const' a x -> () #

Unbox a => Unbox (Const' a b) # 
Instance details

Defined in Data.Extensible.Dictionary

type Repr (Const' a :: k -> *) (b :: k) Source # 
Instance details

Defined in Data.Extensible.Wrapper

type Repr (Const' a :: k -> *) (b :: k) = a
data MVector s (Const' a b) # 
Instance details

Defined in Data.Extensible.Dictionary

data MVector s (Const' a b) = MV_Const (MVector s a)
type Rep (Const' a x) Source # 
Instance details

Defined in Data.Extensible.Wrapper

type Rep (Const' a x) = D1 (MetaData "Const'" "Data.Extensible.Wrapper" "extensible-0.4.10-1w9j3i1U9Si7cH6Q7IPuj8" True) (C1 (MetaCons "Const'" PrefixI True) (S1 (MetaSel (Just "getConst'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
data Vector (Const' a b) # 
Instance details

Defined in Data.Extensible.Dictionary

data Vector (Const' a b) = V_Const (Vector a)
type BitWidth (Const' a b) Source # 
Instance details

Defined in Data.Extensible.Bits

type BitWidth (Const' a b) = BitWidth a

newtype Comp (f :: j -> *) (g :: i -> j) (a :: i) Source #

Poly-kinded composition

Constructors

Comp 

Fields

Instances
(Functor f, Wrapper g) => Wrapper (Comp f g :: k -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr (Comp f g) v :: * Source #

Methods

_Wrapper :: (Functor f0, Profunctor p) => Optic' p f0 (Comp f g v) (Repr (Comp f g) v) Source #

(Functor f, Functor g) => Functor (Comp f g) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

fmap :: (a -> b) -> Comp f g a -> Comp f g b #

(<$) :: a -> Comp f g b -> Comp f g a #

(Foldable f, Foldable g) => Foldable (Comp f g) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

fold :: Monoid m => Comp f g m -> m #

foldMap :: Monoid m => (a -> m) -> Comp f g a -> m #

foldr :: (a -> b -> b) -> b -> Comp f g a -> b #

foldr' :: (a -> b -> b) -> b -> Comp f g a -> b #

foldl :: (b -> a -> b) -> b -> Comp f g a -> b #

foldl' :: (b -> a -> b) -> b -> Comp f g a -> b #

foldr1 :: (a -> a -> a) -> Comp f g a -> a #

foldl1 :: (a -> a -> a) -> Comp f g a -> a #

toList :: Comp f g a -> [a] #

null :: Comp f g a -> Bool #

length :: Comp f g a -> Int #

elem :: Eq a => a -> Comp f g a -> Bool #

maximum :: Ord a => Comp f g a -> a #

minimum :: Ord a => Comp f g a -> a #

sum :: Num a => Comp f g a -> a #

product :: Num a => Comp f g a -> a #

(Traversable f, Traversable g) => Traversable (Comp f g) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Comp f g a -> f0 (Comp f g b) #

sequenceA :: Applicative f0 => Comp f g (f0 a) -> f0 (Comp f g a) #

mapM :: Monad m => (a -> m b) -> Comp f g a -> m (Comp f g b) #

sequence :: Monad m => Comp f g (m a) -> m (Comp f g a) #

Eq (f (g a)) => Eq (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

(==) :: Comp f g a -> Comp f g a -> Bool #

(/=) :: Comp f g a -> Comp f g a -> Bool #

Ord (f (g a)) => Ord (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

compare :: Comp f g a -> Comp f g a -> Ordering #

(<) :: Comp f g a -> Comp f g a -> Bool #

(<=) :: Comp f g a -> Comp f g a -> Bool #

(>) :: Comp f g a -> Comp f g a -> Bool #

(>=) :: Comp f g a -> Comp f g a -> Bool #

max :: Comp f g a -> Comp f g a -> Comp f g a #

min :: Comp f g a -> Comp f g a -> Comp f g a #

Show (f (g a)) => Show (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

showsPrec :: Int -> Comp f g a -> ShowS #

show :: Comp f g a -> String #

showList :: [Comp f g a] -> ShowS #

Generic (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Rep (Comp f g a) :: * -> * #

Methods

from :: Comp f g a -> Rep (Comp f g a) x #

to :: Rep (Comp f g a) x -> Comp f g a #

Semigroup (f (g a)) => Semigroup (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

(<>) :: Comp f g a -> Comp f g a -> Comp f g a #

sconcat :: NonEmpty (Comp f g a) -> Comp f g a #

stimes :: Integral b => b -> Comp f g a -> Comp f g a #

Monoid (f (g a)) => Monoid (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

mempty :: Comp f g a #

mappend :: Comp f g a -> Comp f g a -> Comp f g a #

mconcat :: [Comp f g a] -> Comp f g a #

Lift (f (g a)) => Lift (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

lift :: Comp f g a -> Q Exp #

Arbitrary (f (g a)) => Arbitrary (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

arbitrary :: Gen (Comp f g a) #

shrink :: Comp f g a -> [Comp f g a] #

Hashable (f (g a)) => Hashable (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

hashWithSalt :: Int -> Comp f g a -> Int #

hash :: Comp f g a -> Int #

NFData (f (g a)) => NFData (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

rnf :: Comp f g a -> () #

Pretty (f (g a)) => Pretty (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

pretty :: Comp f g a -> Doc ann #

prettyList :: [Comp f g a] -> Doc ann #

type Repr (Comp f g :: k -> *) (x :: k) Source # 
Instance details

Defined in Data.Extensible.Wrapper

type Repr (Comp f g :: k -> *) (x :: k) = f (Repr g x)
type Rep (Comp f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

type Rep (Comp f g a) = D1 (MetaData "Comp" "Data.Extensible.Wrapper" "extensible-0.4.10-1w9j3i1U9Si7cH6Q7IPuj8" True) (C1 (MetaCons "Comp" PrefixI True) (S1 (MetaSel (Just "getComp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (g a)))))

comp :: Functor f => (a -> g b) -> f a -> Comp f g b Source #

Wrap a result of fmap

data Prod f g a Source #

Poly-kinded product

Constructors

Prod (f a) (g a) 
Instances
(Wrapper f, Wrapper g) => Wrapper (Prod f g :: k -> *) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Repr (Prod f g) v :: * Source #

Methods

_Wrapper :: (Functor f0, Profunctor p) => Optic' p f0 (Prod f g v) (Repr (Prod f g) v) Source #

(Functor f, Functor g) => Functor (Prod f g) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

fmap :: (a -> b) -> Prod f g a -> Prod f g b #

(<$) :: a -> Prod f g b -> Prod f g a #

(Foldable f, Foldable g) => Foldable (Prod f g) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

fold :: Monoid m => Prod f g m -> m #

foldMap :: Monoid m => (a -> m) -> Prod f g a -> m #

foldr :: (a -> b -> b) -> b -> Prod f g a -> b #

foldr' :: (a -> b -> b) -> b -> Prod f g a -> b #

foldl :: (b -> a -> b) -> b -> Prod f g a -> b #

foldl' :: (b -> a -> b) -> b -> Prod f g a -> b #

foldr1 :: (a -> a -> a) -> Prod f g a -> a #

foldl1 :: (a -> a -> a) -> Prod f g a -> a #

toList :: Prod f g a -> [a] #

null :: Prod f g a -> Bool #

length :: Prod f g a -> Int #

elem :: Eq a => a -> Prod f g a -> Bool #

maximum :: Ord a => Prod f g a -> a #

minimum :: Ord a => Prod f g a -> a #

sum :: Num a => Prod f g a -> a #

product :: Num a => Prod f g a -> a #

(Traversable f, Traversable g) => Traversable (Prod f g) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Prod f g a -> f0 (Prod f g b) #

sequenceA :: Applicative f0 => Prod f g (f0 a) -> f0 (Prod f g a) #

mapM :: Monad m => (a -> m b) -> Prod f g a -> m (Prod f g b) #

sequence :: Monad m => Prod f g (m a) -> m (Prod f g a) #

(Eq (f a), Eq (g a)) => Eq (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

(==) :: Prod f g a -> Prod f g a -> Bool #

(/=) :: Prod f g a -> Prod f g a -> Bool #

(Ord (f a), Ord (g a)) => Ord (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

compare :: Prod f g a -> Prod f g a -> Ordering #

(<) :: Prod f g a -> Prod f g a -> Bool #

(<=) :: Prod f g a -> Prod f g a -> Bool #

(>) :: Prod f g a -> Prod f g a -> Bool #

(>=) :: Prod f g a -> Prod f g a -> Bool #

max :: Prod f g a -> Prod f g a -> Prod f g a #

min :: Prod f g a -> Prod f g a -> Prod f g a #

(Show (f a), Show (g a)) => Show (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

showsPrec :: Int -> Prod f g a -> ShowS #

show :: Prod f g a -> String #

showList :: [Prod f g a] -> ShowS #

Generic (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Associated Types

type Rep (Prod f g a) :: * -> * #

Methods

from :: Prod f g a -> Rep (Prod f g a) x #

to :: Rep (Prod f g a) x -> Prod f g a #

(Semigroup (f a), Semigroup (g a)) => Semigroup (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

(<>) :: Prod f g a -> Prod f g a -> Prod f g a #

sconcat :: NonEmpty (Prod f g a) -> Prod f g a #

stimes :: Integral b => b -> Prod f g a -> Prod f g a #

(Monoid (f a), Monoid (g a)) => Monoid (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

mempty :: Prod f g a #

mappend :: Prod f g a -> Prod f g a -> Prod f g a #

mconcat :: [Prod f g a] -> Prod f g a #

(Arbitrary (f a), Arbitrary (g a)) => Arbitrary (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

arbitrary :: Gen (Prod f g a) #

shrink :: Prod f g a -> [Prod f g a] #

(Hashable (f a), Hashable (g a)) => Hashable (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

hashWithSalt :: Int -> Prod f g a -> Int #

hash :: Prod f g a -> Int #

(NFData (f a), NFData (g a)) => NFData (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

Methods

rnf :: Prod f g a -> () #

type Repr (Prod f g :: k -> *) (a :: k) Source # 
Instance details

Defined in Data.Extensible.Wrapper

type Repr (Prod f g :: k -> *) (a :: k) = (Repr f a, Repr g a)
type Rep (Prod f g a) Source # 
Instance details

Defined in Data.Extensible.Wrapper

type Rep (Prod f g a) = D1 (MetaData "Prod" "Data.Extensible.Wrapper" "extensible-0.4.10-1w9j3i1U9Si7cH6Q7IPuj8" False) (C1 (MetaCons "Prod" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (g a))))