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.Struct

Contents

Description

Mutable structs

Synopsis

Mutable struct

data Struct s (h :: k -> *) (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. Associate k v xs => 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 (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)

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

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

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

Get an element in a product.

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.

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

Right-associative fold of a product.

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

Create a new Struct from a product.

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

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

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

Turn a product into a Struct temporarily.

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

Convert a product into an HList.