Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
andfreeze
functions to convert between these.- Sometimes unsafe variants of
thaw
andfreeze
, 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.
Documentation
The Thaw
type class relates mutable and immutable versions of a type.
The instance is defined on the immutable variant;
is the
mutable version of an immutable type Mutable
s aa
, bound to the state token s
.
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
Thaw ConstMsg Source # | |
Defined in Data.Capnp.Message thaw :: (PrimMonad m, PrimState m ~ s) => ConstMsg -> m (Mutable s ConstMsg) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s ConstMsg -> m ConstMsg Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ConstMsg -> m (Mutable s ConstMsg) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s ConstMsg -> m ConstMsg Source # | |
Thaw (Segment ConstMsg) Source # | |
Defined in Data.Capnp.Message thaw :: (PrimMonad m, PrimState m ~ s) => Segment ConstMsg -> m (Mutable s (Segment ConstMsg)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Segment ConstMsg) -> m (Segment ConstMsg) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Segment ConstMsg -> m (Mutable s (Segment ConstMsg)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Segment ConstMsg) -> m (Segment ConstMsg) Source # | |
Thaw msg => Thaw (Struct msg) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => Struct msg -> m (Mutable s (Struct msg)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Struct msg) -> m (Struct msg) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Struct msg -> m (Mutable s (Struct msg)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Struct msg) -> m (Struct msg) Source # | |
Thaw msg => Thaw (List msg) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => List msg -> m (Mutable s (List msg)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List msg) -> m (List msg) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => List msg -> m (Mutable s (List msg)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List msg) -> m (List msg) Source # | |
Thaw msg => Thaw (Ptr msg) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => Ptr msg -> m (Mutable s (Ptr msg)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Ptr msg) -> m (Ptr msg) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Ptr msg -> m (Mutable s (Ptr msg)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Ptr msg) -> m (Ptr msg) Source # | |
Thaw msg => Thaw (ListOf msg (Maybe (Ptr msg))) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Maybe (Ptr msg)) -> m (Mutable s (ListOf msg (Maybe (Ptr msg)))) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Maybe (Ptr msg)) -> m (Mutable s (ListOf msg (Maybe (Ptr msg)))) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source # | |
Thaw msg => Thaw (ListOf msg (Struct msg)) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Struct msg) -> m (Mutable s (ListOf msg (Struct msg))) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Struct msg) -> m (Mutable s (ListOf msg (Struct msg))) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source # | |
Thaw msg => Thaw (ListOf msg Word64) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word64 -> m (Mutable s (ListOf msg Word64)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word64) -> m (ListOf msg Word64) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word64 -> m (Mutable s (ListOf msg Word64)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word64) -> m (ListOf msg Word64) Source # | |
Thaw msg => Thaw (ListOf msg Word32) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word32 -> m (Mutable s (ListOf msg Word32)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word32) -> m (ListOf msg Word32) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word32 -> m (Mutable s (ListOf msg Word32)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word32) -> m (ListOf msg Word32) Source # | |
Thaw msg => Thaw (ListOf msg Word16) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word16 -> m (Mutable s (ListOf msg Word16)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word16) -> m (ListOf msg Word16) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word16 -> m (Mutable s (ListOf msg Word16)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word16) -> m (ListOf msg Word16) Source # | |
Thaw msg => Thaw (ListOf msg Word8) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word8 -> m (Mutable s (ListOf msg Word8)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word8) -> m (ListOf msg Word8) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word8 -> m (Mutable s (ListOf msg Word8)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word8) -> m (ListOf msg Word8) Source # | |
Thaw msg => Thaw (ListOf msg Bool) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Bool -> m (Mutable s (ListOf msg Bool)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Bool) -> m (ListOf msg Bool) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Bool -> m (Mutable s (ListOf msg Bool)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Bool) -> m (ListOf msg Bool) Source # | |
Thaw msg => Thaw (ListOf msg ()) Source # | |
Defined in Data.Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg () -> m (Mutable s (ListOf msg ())) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg ()) -> m (ListOf msg ()) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg () -> m (Mutable s (ListOf msg ())) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg ()) -> m (ListOf msg ()) 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
.