Copyright | (c) Fumiaki Kinoshita 2018 |
---|---|
License | BSD3 |
Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Mutable structs
Synopsis
- data Struct s (h :: k -> Type) (xs :: [k])
- set :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> h x -> m ()
- get :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> m (h x)
- new :: forall h m xs. (PrimMonad m, Generate xs) => (forall x. Membership xs x -> h x) -> m (Struct (PrimState m) h xs)
- newRepeat :: forall h m xs. (PrimMonad m, Generate xs) => (forall x. h x) -> m (Struct (PrimState m) h xs)
- 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)
- newFromHList :: forall h m xs. PrimMonad m => HList h xs -> m (Struct (PrimState m) h xs)
- data WrappedPointer s h a where
- WrappedPointer :: !(Struct s h xs) -> !(Membership xs x) -> WrappedPointer s h (Repr h x)
- (-$>) :: forall k h xs v s. Lookup xs k v => Struct s h xs -> Proxy k -> WrappedPointer s h (Repr h (k :> v))
- atomicModify :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> (h x -> (h x, a)) -> m a
- atomicModify' :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> (h x -> (h x, a)) -> m a
- atomicModify_ :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> (h x -> h x) -> m (h x)
- atomicModify'_ :: PrimMonad m => Struct (PrimState m) h xs -> Membership xs x -> (h x -> h x) -> m (h x)
- data (s :: [k]) :& (h :: k -> *)
- type (:*) h xs = xs :& h
- unsafeFreeze :: PrimMonad m => Struct (PrimState m) h xs -> m (xs :& h)
- 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)
- hlookup :: Membership xs x -> (xs :& h) -> h x
- hlength :: (xs :& h) -> Int
- type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ...
- happend :: (xs :& h) -> (ys :& h) -> (xs ++ ys) :& h
- hfoldrWithIndex :: (forall x. Membership xs x -> h x -> r -> r) -> r -> (xs :& h) -> r
- thaw :: PrimMonad m => (xs :& h) -> m (Struct (PrimState m) h xs)
- hfrozen :: (forall s. ST s (Struct s h xs)) -> xs :& h
- hmodify :: (forall s. Struct s h xs -> ST s ()) -> (xs :& h) -> xs :& h
- toHList :: forall h xs. (xs :& h) -> HList h xs
Mutable 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
.
WrappedPointer :: !(Struct s h xs) -> !(Membership xs x) -> WrappedPointer s h (Repr h x) |
Instances
(s ~ RealWorld, Wrapper h) => HasGetter (WrappedPointer s h a) a Source # | |
Defined in Data.Extensible.Struct get :: MonadIO m => WrappedPointer s h a -> m a | |
(s ~ RealWorld, Wrapper h) => HasSetter (WrappedPointer s h a) a Source # | |
Defined in Data.Extensible.Struct ($=) :: MonadIO m => WrappedPointer s h a -> a -> m () | |
(s ~ RealWorld, Wrapper h) => HasUpdate (WrappedPointer s h a) a a Source # | |
Defined in Data.Extensible.Struct ($~) :: 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 -> *) Source #
The type of extensible products.
(:&) :: [k] -> (k -> *) -> *
Instances
(Corepresentable p, Comonad (Corep p), Functor f) => Extensible f p ((:&) :: [k] -> (k -> Type) -> Type) Source # | |
Defined in Data.Extensible.Struct type ExtensibleConstr (:&) xs h x :: Constraint Source # 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 # | |
Defined in Data.Extensible.Label | |
WrapForall Unbox h (x ': xs) => Vector Vector ((x ': xs) :& h) | |
Defined in Data.Extensible.Dictionary 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) | |
Defined in Data.Extensible.Dictionary 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 # | |
WrapForall Eq h xs => Eq (xs :& h) Source # | |
(Eq (xs :& h), WrapForall Ord h xs) => Ord (xs :& h) Source # | |
Defined in Data.Extensible.Dictionary | |
WrapForall Show h xs => Show (xs :& h) Source # | |
WrapForall Semigroup h xs => Semigroup (xs :& h) Source # | |
(WrapForall Semigroup h xs, WrapForall Monoid h xs) => Monoid (xs :& h) Source # | |
WrapForall Lift h xs => Lift (xs :& h) Source # | |
WrapForall NFData h xs => NFData (xs :& h) Source # | |
Defined in Data.Extensible.Dictionary | |
WrapForall Hashable h xs => Hashable (xs :& h) | |
Defined in Data.Extensible.Dictionary | |
WrapForall Pretty h xs => Pretty (xs :& h) | |
Defined in Data.Extensible.Dictionary pretty :: (xs :& h) -> Doc ann prettyList :: [xs :& h] -> Doc ann | |
WrapForall Arbitrary h xs => Arbitrary (xs :& h) | |
Forall (KeyTargetAre KnownSymbol (Instance1 FromJSON h)) xs => FromJSON (xs :& Nullable (Field h :: Assoc Symbol v -> Type)) | |
Defined in Data.Extensible.Dictionary | |
Forall (KeyTargetAre KnownSymbol (Instance1 FromJSON h)) xs => FromJSON (xs :& (Field h :: Assoc Symbol v -> Type)) |
|
Defined in Data.Extensible.Dictionary | |
Forall (KeyTargetAre KnownSymbol (Instance1 ToJSON h)) xs => ToJSON (xs :& Nullable (Field h :: Assoc Symbol v -> Type)) | |
Defined in Data.Extensible.Dictionary | |
Forall (KeyTargetAre KnownSymbol (Instance1 ToJSON h)) xs => ToJSON (xs :& (Field h :: Assoc Symbol v -> Type)) | |
Defined in Data.Extensible.Dictionary toJSON :: (xs :& Field h) -> Value toEncoding :: (xs :& Field h) -> Encoding toJSONList :: [xs :& Field h] -> Value toEncodingList :: [xs :& Field h] -> Encoding | |
Forall (KeyTargetAre KnownSymbol (Instance1 FromField h)) xs => FromNamedRecord (xs :& (Field h :: Assoc Symbol v -> Type)) | |
Defined in Data.Extensible.Dictionary parseNamedRecord :: NamedRecord -> Parser (xs :& Field h) | |
WrapForall FromField h xs => FromRecord (xs :& h) | |
Defined in Data.Extensible.Dictionary parseRecord :: Record -> Parser (xs :& h) | |
Forall (KeyTargetAre KnownSymbol (Instance1 ToField h)) xs => ToNamedRecord (xs :& (Field h :: Assoc Symbol v -> Type)) | |
Defined in Data.Extensible.Dictionary toNamedRecord :: (xs :& Field h) -> NamedRecord | |
WrapForall ToField h xs => ToRecord (xs :& h) | |
Defined in Data.Extensible.Dictionary | |
WrapForall Unbox h (x ': xs) => Unbox ((x ': xs) :& h) | |
Defined in Data.Extensible.Dictionary | |
type ExtensibleConstr ((:&) :: [k] -> (k -> Type) -> Type) (xs :: [k]) (h :: k -> Type) (x :: k) Source # | |
Defined in Data.Extensible.Struct type ExtensibleConstr ((:&) :: [k] -> (k -> Type) -> Type) (xs :: [k]) (h :: k -> Type) (x :: k) = () | |
newtype MVector s (xs :& h) | |
Defined in Data.Extensible.Dictionary | |
newtype Vector (xs :& h) | |
Defined in Data.Extensible.Dictionary |
unsafeFreeze :: PrimMonad m => Struct (PrimState m) h xs -> m (xs :& h) Source #
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.
type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ... infixr 5 Source #
Concatenate type level lists
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.