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

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

Data.Extensible.Struct

Contents

Description

Mutable structs

Synopsis

Mutable struct

data Struct s h xs 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.

Atomic operations

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

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

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

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

Immutable product

data h :* s Source #

The type of extensible products.

(:*) :: (k -> *) -> [k] -> *

Instances

(Corepresentable p, Comonad (Corep p), Functor f) => Extensible k f p ((:*) k) Source # 

Methods

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

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.

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 #

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

Convert a product into an HList.