extensible-0.9.2: Extensible, efficient, optics-friendly data types and effects
Copyright(c) Fumiaki Kinoshita 2018
LicenseBSD3
MaintainerFumiaki Kinoshita <[email protected]>
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Extensible.Product

Description

 
Synopsis

Basic operations

data (s :: [k]) :& (h :: k -> Type) Source #

The type of extensible products.

(:&) :: [k] -> (k -> Type) -> Type

Instances

Instances details
(Corepresentable p, Comonad (Corep p), Functor f) => Extensible f p ((:&) :: [k] -> (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Extensible.Struct

Methods

pieceAt :: forall (xs :: [k]) h (x :: k). ExtensibleConstr ((:&) :: [k] -> (k -> Type) -> Type) xs h x => Membership xs x -> Optic' p f (xs :& h) (h x) Source #

(Lookup xs k2 v2, Wrapper h, Repr h v2 ~ a) => HasField (k2 :: k1) (RecordOf h xs) a Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

getField :: RecordOf h xs -> a #

WrapForall (Lift :: Type -> Constraint) h xs => Lift (xs :& h :: Type) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

lift :: Quote m => (xs :& h) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (xs :& h) -> Code m (xs :& h) #

WrapForall Unbox h (x ': xs) => Vector Vector ((x ': xs) :& h) 
Instance details

Defined in Data.Extensible.Dictionary

Methods

basicUnsafeFreeze :: Mutable Vector s ((x ': xs) :& h) -> ST s (Vector ((x ': xs) :& h))

basicUnsafeThaw :: Vector ((x ': xs) :& h) -> ST s (Mutable Vector s ((x ': xs) :& h))

basicLength :: Vector ((x ': xs) :& h) -> Int

basicUnsafeSlice :: Int -> Int -> Vector ((x ': xs) :& h) -> Vector ((x ': xs) :& h)

basicUnsafeIndexM :: Vector ((x ': xs) :& h) -> Int -> Box ((x ': xs) :& h)

basicUnsafeCopy :: Mutable Vector s ((x ': xs) :& h) -> Vector ((x ': xs) :& h) -> ST s ()

elemseq :: Vector ((x ': xs) :& h) -> ((x ': xs) :& h) -> b -> b

WrapForall Unbox h (x ': xs) => MVector MVector ((x ': xs) :& h) 
Instance details

Defined in Data.Extensible.Dictionary

Methods

basicLength :: MVector s ((x ': xs) :& h) -> Int

basicUnsafeSlice :: Int -> Int -> MVector s ((x ': xs) :& h) -> MVector s ((x ': xs) :& h)

basicOverlaps :: MVector s ((x ': xs) :& h) -> MVector s ((x ': xs) :& h) -> Bool

basicUnsafeNew :: Int -> ST s (MVector s ((x ': xs) :& h))

basicInitialize :: MVector s ((x ': xs) :& h) -> ST s ()

basicUnsafeReplicate :: Int -> ((x ': xs) :& h) -> ST s (MVector s ((x ': xs) :& h))

basicUnsafeRead :: MVector s ((x ': xs) :& h) -> Int -> ST s ((x ': xs) :& h)

basicUnsafeWrite :: MVector s ((x ': xs) :& h) -> Int -> ((x ': xs) :& h) -> ST s ()

basicClear :: MVector s ((x ': xs) :& h) -> ST s ()

basicSet :: MVector s ((x ': xs) :& h) -> ((x ': xs) :& h) -> ST s ()

basicUnsafeCopy :: MVector s ((x ': xs) :& h) -> MVector s ((x ': xs) :& h) -> ST s ()

basicUnsafeMove :: MVector s ((x ': xs) :& h) -> MVector s ((x ': xs) :& h) -> ST s ()

basicUnsafeGrow :: MVector s ((x ': xs) :& h) -> Int -> ST s (MVector s ((x ': xs) :& h))

WrapForall Arbitrary h xs => Arbitrary (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

arbitrary :: Gen (xs :& h) #

shrink :: (xs :& h) -> [xs :& h] #

Forall (KeyTargetAre KnownSymbol (Instance1 FromJSON h)) xs => FromJSON (xs :& (Field h :: Assoc Symbol v -> Type)) Source #

parseJSON Null is called for missing fields.

Instance details

Defined in Data.Extensible.Dictionary

Methods

parseJSON :: Value -> Parser (xs :& (Field h :: Assoc Symbol v -> Type)) #

parseJSONList :: Value -> Parser [xs :& (Field h :: Assoc Symbol v -> Type)] #

omittedField :: Maybe (xs :& (Field h :: Assoc Symbol v -> Type)) #

Forall (KeyTargetAre KnownSymbol (Instance1 FromJSON h)) xs => FromJSON (xs :& Nullable (Field h :: Assoc Symbol v -> Type)) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Forall (KeyTargetAre KnownSymbol (Instance1 ToJSON h)) xs => ToJSON (xs :& (Field h :: Assoc Symbol v -> Type)) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

toJSON :: (xs :& (Field h :: Assoc Symbol v -> Type)) -> Value #

toEncoding :: (xs :& (Field h :: Assoc Symbol v -> Type)) -> Encoding #

toJSONList :: [xs :& (Field h :: Assoc Symbol v -> Type)] -> Value #

toEncodingList :: [xs :& (Field h :: Assoc Symbol v -> Type)] -> Encoding #

omitField :: (xs :& (Field h :: Assoc Symbol v -> Type)) -> Bool #

Forall (KeyTargetAre KnownSymbol (Instance1 ToJSON h)) xs => ToJSON (xs :& Nullable (Field h :: Assoc Symbol v -> Type)) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

toJSON :: (xs :& Nullable (Field h :: Assoc Symbol v -> Type)) -> Value #

toEncoding :: (xs :& Nullable (Field h :: Assoc Symbol v -> Type)) -> Encoding #

toJSONList :: [xs :& Nullable (Field h :: Assoc Symbol v -> Type)] -> Value #

toEncodingList :: [xs :& Nullable (Field h :: Assoc Symbol v -> Type)] -> Encoding #

omitField :: (xs :& Nullable (Field h :: Assoc Symbol v -> Type)) -> Bool #

(WrapForall Semigroup h xs, WrapForall Monoid h xs) => Monoid (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

mempty :: xs :& h #

mappend :: (xs :& h) -> (xs :& h) -> xs :& h #

mconcat :: [xs :& h] -> xs :& h #

WrapForall Semigroup h xs => Semigroup (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

(<>) :: (xs :& h) -> (xs :& h) -> xs :& h #

sconcat :: NonEmpty (xs :& h) -> xs :& h #

stimes :: Integral b => b -> (xs :& h) -> xs :& h #

WrapForall Bounded h xs => Bounded (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

minBound :: xs :& h #

maxBound :: xs :& h #

WrapForall Show h xs => Show (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

showsPrec :: Int -> (xs :& h) -> ShowS #

show :: (xs :& h) -> String #

showList :: [xs :& h] -> ShowS #

Forall (KeyTargetAre KnownSymbol (Instance1 FromField h)) xs => FromNamedRecord (xs :& (Field h :: Assoc Symbol v -> Type)) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

parseNamedRecord :: NamedRecord -> Parser (xs :& (Field h :: Assoc Symbol v -> Type)) #

WrapForall FromField h xs => FromRecord (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

parseRecord :: Record -> Parser (xs :& h) #

Forall (KeyTargetAre KnownSymbol (Instance1 ToField h)) xs => ToNamedRecord (xs :& (Field h :: Assoc Symbol v -> Type)) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

toNamedRecord :: (xs :& (Field h :: Assoc Symbol v -> Type)) -> NamedRecord #

WrapForall ToField h xs => ToRecord (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

toRecord :: (xs :& h) -> Record #

WrapForall NFData h xs => NFData (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

rnf :: (xs :& h) -> () #

WrapForall Eq h xs => Eq (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

(==) :: (xs :& h) -> (xs :& h) -> Bool #

(/=) :: (xs :& h) -> (xs :& h) -> Bool #

(Eq (xs :& h), WrapForall Ord h xs) => Ord (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

compare :: (xs :& h) -> (xs :& h) -> Ordering #

(<) :: (xs :& h) -> (xs :& h) -> Bool #

(<=) :: (xs :& h) -> (xs :& h) -> Bool #

(>) :: (xs :& h) -> (xs :& h) -> Bool #

(>=) :: (xs :& h) -> (xs :& h) -> Bool #

max :: (xs :& h) -> (xs :& h) -> xs :& h #

min :: (xs :& h) -> (xs :& h) -> xs :& h #

(WrapForall Eq h xs, WrapForall Hashable h xs) => Hashable (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

hashWithSalt :: Int -> (xs :& h) -> Int #

hash :: (xs :& h) -> Int #

WrapForall Incremental h xs => Incremental (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Associated Types

type Delta (xs :& h) 
Instance details

Defined in Data.Extensible.Dictionary

type Delta (xs :& h) = xs :& WrapDelta h

Methods

patch :: (xs :& h) -> Delta (xs :& h) -> xs :& h #

diff :: (xs :& h) -> (xs :& h) -> Maybe (Delta (xs :& h)) #

WrapForall Pretty h xs => Pretty (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

pretty :: (xs :& h) -> Doc ann #

prettyList :: [xs :& h] -> Doc ann #

WrapForall Unbox h (x ': xs) => Unbox ((x ': xs) :& h) 
Instance details

Defined in Data.Extensible.Dictionary

Forall (KeyIs KnownSymbol :: Assoc Symbol v -> Constraint) xs => DefaultOrdered (RecordOf h xs) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

headerOrder :: RecordOf h xs -> Header #

type ExtensibleConstr ((:&) :: [k] -> (k -> Type) -> Type) (xs :: [k]) (h :: k -> Type) (x :: k) Source # 
Instance details

Defined in Data.Extensible.Struct

type ExtensibleConstr ((:&) :: [k] -> (k -> Type) -> Type) (xs :: [k]) (h :: k -> Type) (x :: k) = ()
newtype MVector s (xs :& h) 
Instance details

Defined in Data.Extensible.Dictionary

newtype MVector s (xs :& h) = MV_Product (xs :& Compose (MVector s) h)
type Delta (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

type Delta (xs :& h) = xs :& WrapDelta h
newtype Vector (xs :& h) 
Instance details

Defined in Data.Extensible.Dictionary

newtype Vector (xs :& h) = V_Product (xs :& Compose Vector h)

nil :: forall {k} (h :: k -> Type). ('[] :: [k]) :& h Source #

An empty product.

(<:) :: forall {k} h (x :: k) (xs :: [k]). h x -> (xs :& h) -> (x ': xs) :& h infixr 0 Source #

O(n) Prepend an element onto a product. Expressions like a <: b <: c <: nil are transformed to a single fromHList.

(<!) :: forall {k} h (x :: k) (xs :: [k]). h x -> (xs :& h) -> (x ': xs) :& h infixr 0 Source #

Strict version of (<:).

(=<:) :: forall {k} (h :: k -> Type) (x :: k) (xs :: [k]). Wrapper h => Repr h x -> (xs :& h) -> (x ': xs) :& h infixr 0 Source #

hlength :: forall {k} (xs :: [k]) (h :: k -> Type). (xs :& h) -> Int Source #

The size of a product.

type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ... infixr 5 Source #

Concatenate type level lists

Equations

('[] :: [k]) ++ (ys :: [k]) = ys 
(x ': xs :: [k]) ++ (ys :: [k]) = x ': (xs ++ ys) 

happend :: forall {k} (xs :: [k]) (h :: k -> Type) (ys :: [k]). (xs :& h) -> (ys :& h) -> (xs ++ ys) :& h infixr 5 Source #

Combine products.

hmap :: forall {k} g h (xs :: [k]). (forall (x :: k). g x -> h x) -> (xs :& g) -> xs :& h Source #

Transform every element in a product, preserving the order.

hmap idid
hmap (f . g) ≡ hmap f . hmap g

hmapWithIndex :: forall {k} (xs :: [k]) g h. (forall (x :: k). Membership xs x -> g x -> h x) -> (xs :& g) -> xs :& h Source #

Map a function to every element of a product.

hzipWith :: forall {k} f g h (xs :: [k]). (forall (x :: k). f x -> g x -> h x) -> (xs :& f) -> (xs :& g) -> xs :& h Source #

zipWith for heterogeneous product

hzipWith3 :: forall {k} f g h i (xs :: [k]). (forall (x :: k). f x -> g x -> h x -> i x) -> (xs :& f) -> (xs :& g) -> (xs :& h) -> xs :& i Source #

zipWith3 for heterogeneous product

hfoldMap :: forall {k} a h (xs :: [k]). Monoid a => (forall (x :: k). h x -> a) -> (xs :& h) -> a Source #

Map elements to a monoid and combine the results.

hfoldMap f . hmap g ≡ hfoldMap (f . g)

hfoldMapWithIndex :: forall {k} a (xs :: [k]) g. Monoid a => (forall (x :: k). Membership xs x -> g x -> a) -> (xs :& g) -> a Source #

hfoldMap with the membership of elements.

hfoldrWithIndex :: forall {k} (xs :: [k]) h r. (forall (x :: k). Membership xs x -> h x -> r -> r) -> r -> (xs :& h) -> r Source #

Right-associative fold of a product.

hfoldlWithIndex :: forall {k} (xs :: [k]) r h. (forall (x :: k). Membership xs x -> r -> h x -> r) -> r -> (xs :& h) -> r Source #

Perform a strict left fold over the elements.

htraverse :: forall {k} f g h (xs :: [k]). Applicative f => (forall (x :: k). g x -> f (h x)) -> (xs :& g) -> f (xs :& h) Source #

Traverse all elements and combine the result sequentially. htraverse (fmap f . g) ≡ fmap (hmap f) . htraverse g htraverse pure ≡ pure htraverse (Compose . fmap g . f) ≡ Compose . fmap (htraverse g) . htraverse f

htraverseWithIndex :: forall {k} f (xs :: [k]) g h. Applicative f => (forall (x :: k). Membership xs x -> g x -> f (h x)) -> (xs :& g) -> f (xs :& h) Source #

hsequence :: forall {k} f (xs :: [k]) (h :: k -> Type). Applicative f => (xs :& Compose f h) -> f (xs :& h) Source #

sequence analog for extensible products

Constrained fold

hmapWithIndexFor :: forall {k} c (xs :: [k]) proxy g h. Forall c xs => proxy c -> (forall (x :: k). c x => Membership xs x -> g x -> h x) -> (xs :& g) -> xs :& h Source #

Map a function to every element of a product.

hfoldMapFor :: forall {k} c (xs :: [k]) a proxy h. (Forall c xs, Monoid a) => proxy c -> (forall (x :: k). c x => h x -> a) -> (xs :& h) -> a Source #

Constrained hfoldMap

hfoldMapWithIndexFor :: forall {k} c (xs :: [k]) a proxy h. (Forall c xs, Monoid a) => proxy c -> (forall (x :: k). c x => Membership xs x -> h x -> a) -> (xs :& h) -> a Source #

hfoldMapWithIndex with a constraint for each element.

hfoldrWithIndexFor :: forall {k} c (xs :: [k]) h r proxy. Forall c xs => proxy c -> (forall (x :: k). c x => Membership xs x -> h x -> r -> r) -> r -> (xs :& h) -> r Source #

hfoldrWithIndex with a constraint for each element.

hfoldlWithIndexFor :: forall {k} c (xs :: [k]) proxy r h. Forall c xs => proxy c -> (forall (x :: k). c x => Membership xs x -> r -> h x -> r) -> r -> (xs :& h) -> r Source #

Constrained hfoldlWithIndex

Constraind fold without proxies

hfoldMapWith :: forall {k} c (xs :: [k]) h a. (Forall c xs, Monoid a) => (forall (x :: k). c x => h x -> a) -> (xs :& h) -> a Source #

Constrained hfoldMap

hfoldMapWithIndexWith :: forall {k} c (xs :: [k]) h a. (Forall c xs, Monoid a) => (forall (x :: k). c x => Membership xs x -> h x -> a) -> (xs :& h) -> a Source #

hfoldMapWithIndex with a constraint for each element.

hfoldrWithIndexWith :: forall {k} c (xs :: [k]) h r. Forall c xs => (forall (x :: k). c x => Membership xs x -> h x -> r -> r) -> r -> (xs :& h) -> r Source #

hfoldlWithIndexWith :: forall {k} c (xs :: [k]) h r. Forall c xs => (forall (x :: k). c x => Membership xs x -> r -> h x -> r) -> r -> (xs :& h) -> r Source #

Constrained hfoldlWithIndex

hmapWithIndexWith :: forall {k} c (xs :: [k]) g h. Forall c xs => (forall (x :: k). c x => Membership xs x -> g x -> h x) -> (xs :& g) -> xs :& h Source #

Evaluating

hforce :: forall {k} (xs :: [k]) (h :: k -> Type). (xs :& h) -> xs :& h Source #

Evaluate every element in a product.

Update

haccumMap :: forall {k} f a (xs :: [k]) g h. Foldable f => (a -> xs :/ g) -> (forall (x :: k). Membership xs x -> g x -> h x -> h x) -> (xs :& h) -> f a -> xs :& h Source #

Accumulate sums on a product.

haccum :: forall {k} f (xs :: [k]) g h. Foldable f => (forall (x :: k). Membership xs x -> g x -> h x -> h x) -> (xs :& h) -> f (xs :/ g) -> xs :& h Source #

haccum = haccumMap id

hpartition :: forall {k1} f (xs :: [k1]) a (h :: k1 -> Type). (Foldable f, Generate xs) => (a -> xs :/ h) -> f a -> xs :& Compose [] h Source #

Group sums by type.

Lookup

hlookup :: forall {k} (xs :: [k]) (x :: k) h. Membership xs x -> (xs :& h) -> h x Source #

Get an element in a product.

hindex :: forall {k} (xs :: [k]) h (x :: k). (xs :& h) -> Membership xs x -> h x Source #

Flipped hlookup

Generation

class Generate (xs :: [k]) where #

Every type-level list is an instance of Generate.

Methods

henumerate :: (forall (x :: k). Membership xs x -> r -> r) -> r -> r #

Enumerate all possible Memberships of xs.

hcount :: proxy xs -> Int #

Count the number of memberships.

hgenerateList :: Applicative f => (forall (x :: k). Membership xs x -> f (h x)) -> f (HList h xs) #

Enumerate Memberships and construct an HList.

Instances

Instances details
Generate ('[] :: [k]) 
Instance details

Defined in Type.Membership

Methods

henumerate :: (forall (x :: k). Membership ('[] :: [k]) x -> r -> r) -> r -> r #

hcount :: proxy ('[] :: [k]) -> Int #

hgenerateList :: Applicative f => (forall (x :: k). Membership ('[] :: [k]) x -> f (h x)) -> f (HList h ('[] :: [k])) #

Generate xs => Generate (x ': xs :: [k]) 
Instance details

Defined in Type.Membership

Methods

henumerate :: (forall (x0 :: k). Membership (x ': xs) x0 -> r -> r) -> r -> r #

hcount :: proxy (x ': xs) -> Int #

hgenerateList :: Applicative f => (forall (x0 :: k). Membership (x ': xs) x0 -> f (h x0)) -> f (HList h (x ': xs)) #

hgenerate :: forall {k} (xs :: [k]) f h. (Generate xs, Applicative f) => (forall (x :: k). Membership xs x -> f (h x)) -> f (xs :& h) Source #

htabulate :: forall {k} (xs :: [k]) h. Generate xs => (forall (x :: k). Membership xs x -> h x) -> xs :& h Source #

Construct a product using a function which takes a Membership.

hmap f (htabulate g) ≡ htabulate (f . g)
htabulate (hindex m) ≡ m
hindex (htabulate k) ≡ k

hrepeat :: forall {k} (xs :: [k]) h. Generate xs => (forall (x :: k). h x) -> xs :& h Source #

A product filled with the specified value.

hcollect :: forall {k1} f (xs :: [k1]) a (h :: k1 -> Type). (Functor f, Generate xs) => (a -> xs :& h) -> f a -> xs :& Compose f h Source #

The dual of htraverse

hdistribute :: forall {k1} f (xs :: [k1]) (h :: k1 -> Type). (Functor f, Generate xs) => f (xs :& h) -> xs :& Compose f h Source #

The dual of hsequence

fromHList :: forall {k} (h :: k -> Type) (xs :: [k]). HList h xs -> xs :& h Source #

Convert HList into a product.

toHList :: forall {k} (h :: k -> Type) (xs :: [k]). (xs :& h) -> HList h xs Source #

Convert a product into an HList.

class (ForallF c xs, Generate xs) => Forall (c :: k -> Constraint) (xs :: [k]) where #

Every element in xs satisfies c

Methods

henumerateFor :: proxy c -> proxy' xs -> (forall (x :: k). c x => Membership xs x -> r -> r) -> r -> r #

Enumerate all possible Memberships of xs with an additional context.

hgenerateListFor :: Applicative f => proxy c -> (forall (x :: k). c x => Membership xs x -> f (h x)) -> f (HList h xs) #

Instances

Instances details
Forall (c :: k -> Constraint) ('[] :: [k]) 
Instance details

Defined in Type.Membership

Methods

henumerateFor :: proxy c -> proxy' ('[] :: [k]) -> (forall (x :: k). c x => Membership ('[] :: [k]) x -> r -> r) -> r -> r #

hgenerateListFor :: Applicative f => proxy c -> (forall (x :: k). c x => Membership ('[] :: [k]) x -> f (h x)) -> f (HList h ('[] :: [k])) #

(c x, Forall c xs) => Forall (c :: a -> Constraint) (x ': xs :: [a]) 
Instance details

Defined in Type.Membership

Methods

henumerateFor :: proxy c -> proxy' (x ': xs) -> (forall (x0 :: a). c x0 => Membership (x ': xs) x0 -> r -> r) -> r -> r #

hgenerateListFor :: Applicative f => proxy c -> (forall (x0 :: a). c x0 => Membership (x ': xs) x0 -> f (h x0)) -> f (HList h (x ': xs)) #

hgenerateFor :: forall {k} c (xs :: [k]) f proxy h. (Forall c xs, Applicative f) => proxy c -> (forall (x :: k). c x => Membership xs x -> f (h x)) -> f (xs :& h) Source #

htabulateFor :: forall {k} c (xs :: [k]) proxy h. Forall c xs => proxy c -> (forall (x :: k). c x => Membership xs x -> h x) -> xs :& h Source #

Pure version of hgenerateFor.

hrepeatFor :: forall {k} c (xs :: [k]) proxy h. Forall c xs => proxy c -> (forall (x :: k). c x => h x) -> xs :& h Source #

A product filled with the specified value.

hgenerateWith :: forall {k} c (xs :: [k]) f h. (Forall c xs, Applicative f) => (forall (x :: k). c x => Membership xs x -> f (h x)) -> f (xs :& h) Source #

htabulateWith :: forall {k} c (xs :: [k]) h. Forall c xs => (forall (x :: k). c x => Membership xs x -> h x) -> xs :& h Source #

Pure version of hgenerateFor.

hrepeatWith :: forall {k} c (xs :: [k]) h. Forall c xs => (forall (x :: k). c x => h x) -> xs :& h Source #

A product filled with the specified value.