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

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

Data.Extensible.Product

Contents

Description

 
Synopsis

Basic operations

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

The type of extensible products.

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

Defined in Data.Extensible.Struct

Associated Types

type ExtensibleConstr (:&) xs h x :: Constraint Source #

Methods

pieceAt :: ExtensibleConstr (:&) 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.Label

Methods

getField :: RecordOf h xs -> a #

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

Defined in Data.Extensible.Dictionary

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) ((x ': xs) :& h) -> m (Vector ((x ': xs) :& h)) #

basicUnsafeThaw :: PrimMonad m => Vector ((x ': xs) :& h) -> m (Mutable Vector (PrimState m) ((x ': xs) :& h)) #

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

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

basicUnsafeIndexM :: Monad m => Vector ((x ': xs) :& h) -> Int -> m ((x ': xs) :& h) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) ((x ': xs) :& h) -> Vector ((x ': xs) :& h) -> m () #

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

WrapForall Unbox h (x ': xs) => MVector MVector ((x ': xs) :& h) Source # 
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 :: PrimMonad m => Int -> m (MVector (PrimState m) ((x ': xs) :& h)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) ((x ': xs) :& h) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> ((x ': xs) :& h) -> m (MVector (PrimState m) ((x ': xs) :& h)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) ((x ': xs) :& h) -> Int -> m ((x ': xs) :& h) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) ((x ': xs) :& h) -> Int -> ((x ': xs) :& h) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) ((x ': xs) :& h) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) ((x ': xs) :& h) -> ((x ': xs) :& h) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) ((x ': xs) :& h) -> MVector (PrimState m) ((x ': xs) :& h) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) ((x ': xs) :& h) -> MVector (PrimState m) ((x ': xs) :& h) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) ((x ': xs) :& h) -> Int -> m (MVector (PrimState m) ((x ': 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 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 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 #

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 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 Lift h xs => Lift (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

lift :: (xs :& h) -> Q Exp #

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] #

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 #

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)) -> Value #

toEncoding :: (xs :& Nullable (Field h)) -> Encoding #

toJSONList :: [xs :& Nullable (Field h)] -> Value #

toEncodingList :: [xs :& Nullable (Field h)] -> Encoding #

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) -> Value #

toEncoding :: (xs :& Field h) -> Encoding #

toJSONList :: [xs :& Field h] -> Value #

toEncodingList :: [xs :& Field h] -> Encoding #

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 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) #

parseJSONList :: Value -> Parser [xs :& Field h] #

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

Defined in Data.Extensible.Dictionary

Methods

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

Defined in Data.Extensible.Dictionary

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) -> NamedRecord #

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

Defined in Data.Extensible.Dictionary

Methods

rnf :: (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) Source # 
Instance details

Defined in Data.Extensible.Dictionary

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) Source # 
Instance details

Defined in Data.Extensible.Dictionary

newtype MVector s (xs :& h) = MV_Product (xs :& Comp (MVector s) h)
newtype Vector (xs :& h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

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

nil :: '[] :& h Source #

An empty product.

(<:) :: 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.

(<!) :: h x -> (xs :& h) -> (x ': xs) :& h infixr 0 Source #

Strict version of (<:).

(=<:) :: Wrapper h => Repr h x -> (xs :& h) -> (x ': xs) :& h infixr 0 Source #

hlength :: (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

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

happend :: (xs :& h) -> (ys :& h) -> (xs ++ ys) :& h infixr 5 Source #

Combine products.

hmap :: (forall x. 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 x. Membership xs x -> g x -> h x) -> (xs :& g) -> xs :& h Source #

Map a function to every element of a product.

hzipWith :: (forall x. f x -> g x -> h x) -> (xs :& f) -> (xs :& g) -> xs :& h Source #

zipWith for heterogeneous product

hzipWith3 :: (forall x. f x -> g x -> h x -> i x) -> (xs :& f) -> (xs :& g) -> (xs :& h) -> xs :& i Source #

zipWith3 for heterogeneous product

hfoldMap :: Monoid a => (forall x. h x -> a) -> (xs :& h) -> a Source #

Map elements to a monoid and combine the results.

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

hfoldMapWithIndex :: Monoid a => (forall x. Membership xs x -> g x -> a) -> (xs :& g) -> a Source #

hfoldMap with the membership of elements.

hfoldrWithIndex :: (forall x. Membership xs x -> h x -> r -> r) -> r -> (xs :& h) -> r Source #

Right-associative fold of a product.

hfoldlWithIndex :: (forall x. Membership xs x -> r -> h x -> r) -> r -> (xs :& h) -> r Source #

Perform a strict left fold over the elements.

htraverse :: Applicative f => (forall x. 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 (Comp . fmap g . f) ≡ Comp . fmap (htraverse g) . htraverse f

htraverseWithIndex :: Applicative f => (forall x. Membership xs x -> g x -> f (h x)) -> (xs :& g) -> f (xs :& h) Source #

hsequence :: Applicative f => (xs :& Comp f h) -> f (xs :& h) Source #

sequence analog for extensible products

Constrained fold

hmapWithIndexFor :: Forall c xs => proxy c -> (forall x. 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 c xs, Monoid a) => proxy c -> (forall x. c x => h x -> a) -> (xs :& h) -> a Source #

Constrained hfoldMap

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

hfoldMapWithIndex with a constraint for each element.

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

hfoldrWithIndex with a constraint for each element.

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

Constrained hfoldlWithIndex

Constraind fold without proxies

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

Constrained hfoldMap

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

hfoldMapWithIndex with a constraint for each element.

hfoldrWithIndexWith :: forall c xs h r. Forall c xs => (forall x. c x => Membership xs x -> h x -> r -> r) -> r -> (xs :& h) -> r Source #

hfoldlWithIndexWith :: forall c xs h r. Forall c xs => (forall x. c x => Membership xs x -> r -> h x -> r) -> r -> (xs :& h) -> r Source #

Constrained hfoldlWithIndex

hmapWithIndexWith :: forall c xs g h. Forall c xs => (forall x. c x => Membership xs x -> g x -> h x) -> (xs :& g) -> xs :& h Source #

Evaluating

hforce :: (xs :& h) -> xs :& h Source #

Evaluate every element in a product.

Update

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

Accumulate sums on a product.

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

haccum = haccumMap id

hpartition :: (Foldable f, Generate xs) => (a -> xs :/ h) -> f a -> xs :& Comp [] h Source #

Group sums by type.

Lookup

hlookup :: Membership xs x -> (xs :& h) -> h x Source #

Get an element in a product.

hindex :: (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
Generate ([] :: [k]) 
Instance details

Defined in Type.Membership

Methods

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

hcount :: proxy [] -> Int #

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

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

Defined in Type.Membership

Methods

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

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

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

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

htabulate :: Generate xs => (forall x. 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 :: Generate xs => (forall x. h x) -> xs :& h Source #

A product filled with the specified value.

hcollect :: (Functor f, Generate xs) => (a -> xs :& h) -> f a -> xs :& Comp f h Source #

The dual of htraverse

hdistribute :: (Functor f, Generate xs) => f (xs :& h) -> xs :& Comp f h Source #

The dual of hsequence

fromHList :: HList h xs -> xs :& h Source #

Convert HList into a product.

toHList :: forall h xs. (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
Forall (c :: k -> Constraint) ([] :: [k]) 
Instance details

Defined in Type.Membership

Methods

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

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

(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 :: k). c x0 => Membership (x ': xs) x0 -> r -> r) -> r -> r #

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

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

htabulateFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x) -> xs :& h Source #

Pure version of hgenerateFor.

hrepeatFor :: Forall c xs => proxy c -> (forall x. c x => h x) -> xs :& h Source #

A product filled with the specified value.

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

htabulateWith :: forall c xs h. Forall c xs => (forall x. c x => Membership xs x -> h x) -> xs :& h Source #

Pure version of hgenerateFor.

hrepeatWith :: forall c xs h. Forall c xs => (forall x. c x => h x) -> xs :& h Source #

A product filled with the specified value.