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

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

Data.Extensible.Struct

Contents

Description

Mutable structs

Synopsis

Mutable struct

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

Mutable type-indexed struct.

set :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> h x -> m () Source #

Write a value in a Struct.

get :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> m (h x) Source #

Read a value from a Struct.

new :: forall h m xs. (PrimMonad m, Generate xs) => (forall x. Membership xs x -> h x) -> m (Struct (PrimState m) h xs) Source #

Create a new Struct using the supplied initializer.

newRepeat :: forall h m xs. (PrimMonad m, Generate xs) => (forall x. h x) -> m (Struct (PrimState m) h xs) Source #

Create a Struct full of the specified value.

newFor :: forall proxy c h m xs. (PrimMonad m, Forall c xs) => proxy c -> (forall x. c x => Membership xs x -> h x) -> m (Struct (PrimState m) h xs) Source #

Create a new Struct using the supplied initializer with a context.

newFromHList :: forall h m xs. PrimMonad m => HList h xs -> m (Struct (PrimState m) h xs) Source #

Create a new Struct from an HList.

data WrappedPointer s h a where Source #

A pointer to an element in a Struct.

Constructors

WrappedPointer :: !(Struct s h xs) -> !(Membership xs x) -> WrappedPointer s h (Repr h x) 
Instances
(s ~ RealWorld, Wrapper h) => HasSetter (WrappedPointer s h a) a Source # 
Instance details

Defined in Data.Extensible.Struct

Methods

($=) :: MonadIO m => WrappedPointer s h a -> a -> m () #

(s ~ RealWorld, Wrapper h) => HasGetter (WrappedPointer s h a) a Source # 
Instance details

Defined in Data.Extensible.Struct

Methods

get :: MonadIO m => WrappedPointer s h a -> m a #

(s ~ RealWorld, Wrapper h) => HasUpdate (WrappedPointer s h a) a a Source # 
Instance details

Defined in Data.Extensible.Struct

Methods

($~) :: MonadIO m => WrappedPointer s h a -> (a -> a) -> m () #

($~!) :: MonadIO m => WrappedPointer s h a -> (a -> a) -> m () #

(-$>) :: forall k h xs v s. Lookup xs k v => Struct s h xs -> Proxy k -> WrappedPointer s h (Repr h (k :> v)) Source #

Get a WrappedPointer from a name.

Atomic operations

atomicModify :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> (h x -> (h x, a)) -> m a Source #

Atomically modify an element in a Struct.

atomicModify' :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> (h x -> (h x, a)) -> m a Source #

Strict version of atomicModify.

atomicModify_ :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> (h x -> h x) -> m (h x) Source #

Apply a function to an element atomically.

atomicModify'_ :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> (h x -> h x) -> m (h x) Source #

Strict version of atomicModify_.

Immutable product

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)

type (:*) h xs = xs :& h Source #

Deprecated: Use :& instead

unsafeFreeze :: PrimMonad m => Struct (PrimState m) h xs -> m (xs :& h) Source #

Turn Struct into an immutable product. The original Struct may not be used.

newFrom :: forall g h m xs. PrimMonad m => (xs :& g) -> (forall x. Membership xs x -> g x -> h x) -> m (Struct (PrimState m) h xs) Source #

Create a new Struct using the contents of a product.

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

Get an element in a product.

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.

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

Right-associative fold of a product.

thaw :: PrimMonad m => (xs :& h) -> m (Struct (PrimState m) h xs) Source #

Create a new Struct from a product.

hfrozen :: (forall s. ST s (Struct s h xs)) -> xs :& h Source #

Create a product from an ST action which returns a Struct.

hmodify :: (forall s. Struct s h xs -> ST s ()) -> (xs :& h) -> xs :& h Source #

Turn a product into a Struct temporarily.

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

Convert a product into an HList.