capnp-0.12.0.0: Cap'n Proto for Haskell
Safe HaskellNone
LanguageHaskell2010

Data.Mutable

Description

There is a common pattern in Haskell libraries that work with mutable data:

  • Two types, a mutable and an immutable variant of the same structure.
  • thaw and freeze functions to convert between these.
  • Sometimes unsafe variants of thaw and freeze, which avoid a copy but can break referential transparency if misused.

This module abstracts out the above pattern into a generic type family Thaw, and provides some of the common higher-level tools built on top of these primitives.

Note that there's nothing terribly Cap'N Proto specific about this module; we may even factor it out into a separate package at some point.

Synopsis

Documentation

class Thaw a where Source #

The Thaw type class relates mutable and immutable versions of a type. The instance is defined on the immutable variant; Mutable s a is the mutable version of an immutable type a, bound to the state token s.

Minimal complete definition

thaw, freeze

Associated Types

type Mutable s a Source #

The mutable version of a, bound to the state token s.

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => a -> m (Mutable s a) Source #

Convert an immutable value to a mutable one.

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s a -> m a Source #

Convert a mutable value to an immutable one.

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => a -> m (Mutable s a) Source #

Like thaw, except that the caller is responsible for ensuring that the original value is not subsequently used; doing so may violate referential transparency.

The default implementation of this is just the same as thaw, but typically an instance will override this with a trivial (unsafe) cast, hence the obligation described above.

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s a -> m a Source #

Unsafe version of freeze analagous to unsafeThaw. The caller must ensure that the original value is not used after this call.

Instances

Instances details
Thaw a => Thaw (Maybe a) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (Maybe a) Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Maybe a -> m (Mutable s (Maybe a)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Maybe a) -> m (Maybe a) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Maybe a -> m (Mutable s (Maybe a)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Maybe a) -> m (Maybe a) Source #

Thaw (Segment 'Const) Source # 
Instance details

Defined in Capnp.Message

Associated Types

type Mutable s (Segment 'Const) Source #

Thaw (Message 'Const) Source # 
Instance details

Defined in Capnp.Message

Associated Types

type Mutable s (Message 'Const) Source #

Thaw (Struct 'Const) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (Struct 'Const) Source #

Thaw (List 'Const) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (List 'Const) Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => List 'Const -> m (Mutable s (List 'Const)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List 'Const) -> m (List 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => List 'Const -> m (Mutable s (List 'Const)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List 'Const) -> m (List 'Const) Source #

Thaw (Ptr 'Const) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (Ptr 'Const) Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Ptr 'Const -> m (Mutable s (Ptr 'Const)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Ptr 'Const) -> m (Ptr 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Ptr 'Const -> m (Mutable s (Ptr 'Const)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Ptr 'Const) -> m (Ptr 'Const) Source #

Thaw (Data 'Const) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

type Mutable s (Data 'Const) Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Data 'Const -> m (Mutable s (Data 'Const)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Data 'Const) -> m (Data 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Data 'Const -> m (Mutable s (Data 'Const)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Data 'Const) -> m (Data 'Const) Source #

Thaw (Text 'Const) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

type Mutable s (Text 'Const) Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Text 'Const -> m (Mutable s (Text 'Const)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Text 'Const) -> m (Text 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Text 'Const -> m (Mutable s (Text 'Const)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Text 'Const) -> m (Text 'Const) Source #

Thaw (ListOf 'Const Bool) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf 'Const Bool) Source #

Thaw (ListOf 'Const (Maybe (Ptr 'Const))) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf 'Const (Maybe (Ptr 'Const))) Source #

Thaw (ListOf 'Const Word8) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf 'Const Word8) Source #

Thaw (ListOf 'Const Word16) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf 'Const Word16) Source #

Thaw (ListOf 'Const Word32) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf 'Const Word32) Source #

Thaw (ListOf 'Const Word64) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf 'Const Word64) Source #

Thaw (ListOf 'Const ()) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf 'Const ()) Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf 'Const () -> m (Mutable s (ListOf 'Const ())) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf 'Const ()) -> m (ListOf 'Const ()) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf 'Const () -> m (Mutable s (ListOf 'Const ())) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf 'Const ()) -> m (ListOf 'Const ()) Source #

Thaw (ListOf 'Const (Struct 'Const)) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf 'Const (Struct 'Const)) Source #

create :: Thaw a => (forall s. ST s (Mutable s a)) -> a Source #

Create and freeze a mutable value, safely, without doing a full copy. internally, create calls unsafeFreeze, but it cannot be directly used to violate referential transparency, as the value is not available to the caller after freezing.

createT :: (Traversable f, Thaw a) => (forall s. ST s (f (Mutable s a))) -> f a Source #

Like create, but the result is wrapped in an instance of Traversable.