extensible-0.4.10: 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 (h :: k -> *) :* (s :: [k]) Source #

The type of extensible products.

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

Defined in Data.Extensible.Struct

Associated Types

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

Methods

pieceAt :: ExtensibleConstr (:*) h xs x => Membership xs x -> Optic' p f (h :* xs) (h x) Source #

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

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

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

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

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Extensible.Dictionary

Methods

minBound :: h :* xs #

maxBound :: h :* xs #

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

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

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

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

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

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

Defined in Data.Extensible.Dictionary

Methods

mempty :: h :* xs #

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

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

WrapForall Lift h xs => Lift (h :* xs) # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

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

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

Defined in Data.Extensible.Dictionary

Methods

arbitrary :: Gen (h :* xs) #

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

WrapForall Hashable h xs => Hashable (h :* xs) # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

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

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

Forall (KeyValue KnownSymbol (Instance1 ToJSON h)) xs => ToJSON (Nullable (Field h :: Assoc Symbol v -> *) :* xs) # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

toJSON :: (Nullable (Field h) :* xs) -> Value #

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

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

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

Forall (KeyValue KnownSymbol (Instance1 ToJSON h)) xs => ToJSON ((Field h :: Assoc Symbol v -> *) :* xs) # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

toJSON :: (Field h :* xs) -> Value #

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

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

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

Forall (KeyValue KnownSymbol (Instance1 FromJSON h)) xs => FromJSON (Nullable (Field h :: Assoc Symbol v -> *) :* xs) # 
Instance details

Defined in Data.Extensible.Dictionary

Forall (KeyValue KnownSymbol (Instance1 FromJSON h)) xs => FromJSON ((Field h :: Assoc Symbol v -> *) :* xs) #

parseJSON Null is called for missing fields.

Instance details

Defined in Data.Extensible.Dictionary

Methods

parseJSON :: Value -> Parser (Field h :* xs) #

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

Defined in Data.Extensible.Dictionary

Methods

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

Forall (KeyValue KnownSymbol (Instance1 FromField h)) xs => FromNamedRecord ((Field h :: Assoc Symbol v -> *) :* xs) # 
Instance details

Defined in Data.Extensible.Dictionary

Forall (KeyValue KnownSymbol (Instance1 ToField h)) xs => ToNamedRecord ((Field h :: Assoc Symbol v -> *) :* xs) # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

toNamedRecord :: (Field h :* xs) -> NamedRecord #

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

Defined in Data.Extensible.Dictionary

Methods

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

Defined in Data.Extensible.Dictionary

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

Defined in Data.Extensible.Struct

type ExtensibleConstr ((:*) :: (k -> *) -> [k] -> *) (h :: k -> *) (xs :: [k]) (x :: k) = ()
data MVector s (h :* xs) # 
Instance details

Defined in Data.Extensible.Dictionary

data MVector s (h :* xs) = MV_Product (Comp (MVector s) h :* xs)
data Vector (h :* xs) # 
Instance details

Defined in Data.Extensible.Dictionary

data Vector (h :* xs) = V_Product (Comp Vector h :* xs)

nil :: h :* '[] Source #

An empty product.

(<:) :: h x -> (h :* xs) -> h :* (x ': xs) 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 -> (h :* xs) -> h :* (x ': xs) infixr 0 Source #

Strict version of (<:).

hlength :: (h :* xs) -> 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 :: (h :* xs) -> (h :* ys) -> h :* (xs ++ ys) Source #

Combine products.

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

Map a function to every element of a product.

hmapWithIndexFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> g x -> h x) -> (g :* xs) -> h :* xs Source #

Map a function to every element of a product.

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

zipWith for heterogeneous product

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

zipWith3 for heterogeneous product

hfoldMap :: Monoid a => (forall x. h x -> a) -> (h :* xs) -> 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) -> (g :* xs) -> a Source #

hfoldMap with the membership of elements.

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

Right-associative fold of a product.

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

Perform a strict left fold over the elements.

htraverse :: Applicative f => (forall x. g x -> f (h x)) -> (g :* xs) -> f (h :* xs) 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)) -> (g :* xs) -> f (h :* xs) Source #

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

sequence analog for extensible products

Constrained fold

hfoldMapFor :: (Forall c xs, Monoid a) => proxy c -> (forall x. c x => h x -> a) -> (h :* xs) -> a Source #

Constrained hfoldMap

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

hfoldMapWithIndex with a constraint for each element.

hfoldrWithIndexFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x -> r -> r) -> r -> (h :* xs) -> 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 -> (h :* xs) -> r Source #

Constrained hfoldlWithIndex

Evaluating

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

Evaluate every element in a product.

Update

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

Accumulate sums on a product.

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

haccum = haccumMap id

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

Group sums by type.

Lookup

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

Get an element in a product.

hindex :: (h :* xs) -> Membership xs x -> h x Source #

Flipped hlookup

Generation

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

Every type-level list is an instance of Generate.

Minimal complete definition

henumerate, hcount, hgenerateList

Methods

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

Enumerate all possible Memberships of xs.

hcount :: proxy xs -> Int Source #

Count the number of memberships.

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

Enumerate Memberships and construct an HList.

Instances
Generate ([] :: [k]) Source # 
Instance details

Defined in Data.Extensible.Class

Methods

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

hcount :: proxy [] -> Int Source #

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

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

Defined in Data.Extensible.Class

Methods

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

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

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

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

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

A product filled with the specified value.

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

The dual of htraverse

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

The dual of hsequence

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

Convert HList into a product.

toHList :: forall h xs. (h :* xs) -> HList h xs Source #

Convert a product into an HList.

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

Every element in xs satisfies c

Minimal complete definition

henumerateFor, hgenerateListFor

Methods

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

Enumerate all possible Memberships of xs with an additional context.

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

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

Defined in Data.Extensible.Class

Methods

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

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

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

Defined in Data.Extensible.Class

Methods

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

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

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

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

Pure version of hgenerateFor.

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

A product filled with the specified value.