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

Capnp.Untyped

Description

The types and functions in this module know about things like structs and lists, but are not schema aware.

Each of the data types exported by this module is parametrized over the mutability of the message it contains (see Capnp.Message).

Synopsis

Documentation

data Ptr mut Source #

A an absolute pointer to a value (of arbitrary type) in a message. Note that there is no variant for far pointers, which don't make sense with absolute addressing.

Constructors

PtrCap (Cap mut) 
PtrList (List mut) 
PtrStruct (Struct mut) 

Instances

Instances details
TraverseMsg Ptr Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Ptr mutA -> m (Ptr mutB) 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 #

HasMessage (Ptr mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: Ptr mut -> Message mut 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 #

MessageDefault (ListOf mut (Maybe (Ptr mut))) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut (Maybe (Ptr mut))) Source #

type Mutable s (Ptr 'Const) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (Ptr 'Const) = Ptr ('Mut s)
type Mutable s (ListOf 'Const (Maybe (Ptr 'Const))) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (ListOf 'Const (Maybe (Ptr 'Const))) = ListOf ('Mut s) (Maybe (Ptr ('Mut s)))
type ReprFor (Ptr mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (Ptr mut) = 'Ptr ('Nothing :: Maybe PtrRepr)

data List mut Source #

A list of values (of arbitrary type) in a message.

Constructors

List0 (ListOf mut ()) 
List1 (ListOf mut Bool) 
List8 (ListOf mut Word8) 
List16 (ListOf mut Word16) 
List32 (ListOf mut Word32) 
List64 (ListOf mut Word64) 
ListPtr (ListOf mut (Maybe (Ptr mut))) 
ListStruct (ListOf mut (Struct mut)) 

Instances

Instances details
TraverseMsg List Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> List mutA -> m (List mutB) 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 #

HasMessage (List mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: List mut -> Message mut Source #

type Mutable s (List 'Const) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (List 'Const) = List ('Mut s)
type ReprFor (List mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (List mut) = 'Ptr ('Just ('List ('Nothing :: Maybe ListRepr)))

data Struct mut Source #

A struct value in a message.

Instances

Instances details
TraverseMsg Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Struct mutA -> m (Struct mutB) Source #

Thaw (Struct 'Const) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type Mutable s (Struct 'Const) Source #

MessageDefault (Struct mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Struct mut) Source #

HasMessage (Struct mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: Struct mut -> Message mut Source #

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

Defined in Capnp.Untyped

Associated Types

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

MessageDefault (ListOf mut (Struct mut)) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut (Struct mut)) Source #

type Mutable s (Struct 'Const) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (Struct 'Const) = Struct ('Mut s)
type Mutable s (ListOf 'Const (Struct 'Const)) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (ListOf 'Const (Struct 'Const)) = ListOf ('Mut s) (Struct ('Mut s))
type ReprFor (Struct mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (Struct mut) = 'Ptr ('Just 'Struct)

data ListOf mut a Source #

A list of values of type a in a message.

Instances

Instances details
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 #

MessageDefault (ListOf mut (Maybe (Ptr mut))) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut (Maybe (Ptr mut))) Source #

MessageDefault (ListOf mut Word64) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Word64) Source #

MessageDefault (ListOf mut Word32) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Word32) Source #

MessageDefault (ListOf mut Word16) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Word16) Source #

MessageDefault (ListOf mut Word8) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Word8) Source #

MessageDefault (ListOf mut Bool) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Bool) Source #

MessageDefault (ListOf mut (Struct mut)) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut (Struct mut)) Source #

MessageDefault (ListOf mut ()) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut ()) Source #

HasMessage (ListOf mut a) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: ListOf mut a -> Message mut Source #

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

Defined in Capnp.Untyped

type Mutable s (ListOf 'Const (Maybe (Ptr 'Const))) = ListOf ('Mut s) (Maybe (Ptr ('Mut s)))
type Mutable s (ListOf 'Const (Struct 'Const)) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (ListOf 'Const (Struct 'Const)) = ListOf ('Mut s) (Struct ('Mut s))
type Mutable s (ListOf 'Const Word64) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (ListOf 'Const Word32) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (ListOf 'Const Word16) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (ListOf 'Const Word8) Source # 
Instance details

Defined in Capnp.Untyped

type Mutable s (ListOf 'Const Bool) Source # 
Instance details

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

type Mutable s (ListOf 'Const ()) = ListOf ('Mut s) ()
type ReprFor (ListOf mut a) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (ListOf mut a) = ReprFor (List a)

data Cap mut Source #

A Capability in a message.

Instances

Instances details
TraverseMsg Cap Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Cap mutA -> m (Cap mutB) Source #

HasMessage (Cap mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: Cap mut -> Message mut Source #

type ReprFor (Cap mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (Cap mut) = 'Ptr ('Just 'Cap)

structByteCount :: Struct msg -> ByteCount Source #

Get the size (in bytes) of a struct's data section.

structWordCount :: Struct msg -> WordCount Source #

Get the size (in words) of a struct's data section.

structPtrCount :: Struct msg -> Word16 Source #

Get the size of a struct's pointer section.

structListByteCount :: ListOf msg (Struct msg) -> ByteCount Source #

Get the size (in words) of the data sections in a struct list.

structListWordCount :: ListOf msg (Struct msg) -> WordCount Source #

Get the size (in words) of the data sections in a struct list.

structListPtrCount :: ListOf msg (Struct msg) -> Word16 Source #

Get the size of the pointer sections in a struct list.

getData :: ReadCtx m msg => Int -> Struct msg -> m Word64 Source #

getData i struct gets the ith word from the struct's data section, returning 0 if it is absent.

getPtr :: ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Source #

getPtr i struct gets the ith word from the struct's pointer section, returning Nothing if it is absent.

setData :: (ReadCtx m ('Mut s), WriteCtx m s) => Word64 -> Int -> Struct ('Mut s) -> m () Source #

setData value i struct sets the ith word in the struct's data section to value.

setPtr :: (ReadCtx m ('Mut s), WriteCtx m s) => Maybe (Ptr ('Mut s)) -> Int -> Struct ('Mut s) -> m () Source #

setData value i struct sets the ith pointer in the struct's pointer section to value.

copyStruct :: RWCtx m s => Struct ('Mut s) -> Struct ('Mut s) -> m () Source #

copyStruct dest src copies the source struct to the destination struct.

copyPtr :: RWCtx m s => Message ('Mut s) -> Maybe (Ptr ('Mut s)) -> m (Maybe (Ptr ('Mut s))) Source #

Make a copy of the value at the pointer, in the target message.

copyList :: RWCtx m s => Message ('Mut s) -> List ('Mut s) -> m (List ('Mut s)) Source #

Make a copy of the list, in the target message.

copyCap :: RWCtx m s => Message ('Mut s) -> Cap ('Mut s) -> m (Cap ('Mut s)) Source #

Make a copy of a capability inside the target message.

copyListOf :: RWCtx m s => ListOf ('Mut s) a -> ListOf ('Mut s) a -> m () Source #

Make a copy of the list, in the target message.

getClient :: ReadCtx m mut => Cap mut -> m Client Source #

Extract a client (indepedent of the messsage) from the capability.

get :: ReadCtx m mut => WordPtr mut -> m (Maybe (Ptr mut)) Source #

get ptr returns the Ptr stored at ptr. Deducts 1 from the quota for each word read (which may be multiple in the case of far pointers).

index :: ReadCtx m mut => Int -> ListOf mut a -> m a Source #

index i list returns the ith element in list. Deducts 1 from the quota

length :: ListOf msg a -> Int Source #

Returns the length of a list

setIndex :: RWCtx m s => a -> Int -> ListOf ('Mut s) a -> m () Source #

'setIndex value i list Set the ith element of list to value.

take :: MonadThrow m => Int -> ListOf msg a -> m (ListOf msg a) Source #

Return a prefix of the list, of the given length.

rootPtr :: ReadCtx m mut => Message mut -> m (Struct mut) Source #

Returns the root pointer of a message.

setRoot :: WriteCtx m s => Struct ('Mut s) -> m () Source #

Make the given struct the root object of its message.

rawBytes :: ReadCtx m 'Const => ListOf 'Const Word8 -> m ByteString Source #

rawBytes returns the raw bytes corresponding to the list.

type ReadCtx m mut = (MonadReadMessage mut m, MonadThrow m, MonadLimit m) Source #

Type (constraint) synonym for the constraints needed for most read operations.

type RWCtx m s = (ReadCtx m ('Mut s), WriteCtx m s) Source #

Synonym for ReadCtx + WriteCtx

class HasMessage a mut | a -> mut where Source #

Types a whose storage is owned by a message..

Methods

message :: a -> Message mut Source #

Get the message in which the a is stored.

Instances

Instances details
HasMessage (WordPtr mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: WordPtr mut -> Message mut Source #

HasMessage (Struct mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: Struct mut -> Message mut Source #

HasMessage (Cap mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: Cap mut -> Message mut Source #

HasMessage (List mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: List mut -> Message mut Source #

HasMessage (Ptr mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: Ptr mut -> Message mut Source #

HasMessage (ListOf mut a) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: ListOf mut a -> Message mut Source #

HasMessage (Untyped mut (ReprFor a)) mut => HasMessage (Raw mut a) mut Source # 
Instance details

Defined in Capnp.Repr

Methods

message :: Raw mut a -> Message mut Source #

class HasMessage a mut => MessageDefault a mut where Source #

Types which have a "default" value, but require a message to construct it.

The default is usually conceptually zero-size. This is mostly useful for generated code, so that it can use standard decoding techniques on default values.

Methods

messageDefault :: ReadCtx m mut => Message mut -> m a Source #

Instances

Instances details
MessageDefault (Struct mut) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Struct mut) Source #

MessageDefault (ListOf mut (Maybe (Ptr mut))) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut (Maybe (Ptr mut))) Source #

MessageDefault (ListOf mut Word64) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Word64) Source #

MessageDefault (ListOf mut Word32) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Word32) Source #

MessageDefault (ListOf mut Word16) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Word16) Source #

MessageDefault (ListOf mut Word8) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Word8) Source #

MessageDefault (ListOf mut Bool) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut Bool) Source #

MessageDefault (ListOf mut (Struct mut)) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut (Struct mut)) Source #

MessageDefault (ListOf mut ()) mut Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (ListOf mut ()) Source #

MessageDefault (Untyped mut (ReprFor a)) mut => MessageDefault (Raw mut a) mut Source # 
Instance details

Defined in Capnp.Repr

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Raw mut a) Source #

allocStruct :: WriteCtx m s => Message ('Mut s) -> Word16 -> Word16 -> m (Struct ('Mut s)) Source #

Allocate a struct in the message.

allocCompositeList Source #

Arguments

:: WriteCtx m s 
=> Message ('Mut s)

The message to allocate in.

-> Word16

The size of the data section

-> Word16

The size of the pointer section

-> Int

The length of the list in elements.

-> m (ListOf ('Mut s) (Struct ('Mut s))) 

Allocate a composite list.

allocList0 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) ()) Source #

Allocate a list of capnproto Void values.

allocList1 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Bool) Source #

Allocate a list of booleans

allocList8 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word8) Source #

Allocate a list of 8-bit values.

allocList16 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word16) Source #

Allocate a list of 16-bit values.

allocList32 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word32) Source #

Allocate a list of 32-bit values.

allocList64 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word64) Source #

Allocate a list of 64-bit words.

allocListPtr :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) (Maybe (Ptr ('Mut s)))) Source #

Allocate a list of pointers.

appendCap :: WriteCtx m s => Message ('Mut s) -> Client -> m (Cap ('Mut s)) Source #

class TraverseMsg f where Source #

N.B. this should mostly be considered an implementation detail, but it is exposed because it is used by generated code.

TraverseMsg is similar to Traversable from the prelude, but the intent is that rather than conceptually being a "container", the instance is a value backed by a message, and the point of the type class is to be able to apply transformations to the underlying message.

We don't just use Traversable for this for two reasons:

  1. While algebraically it makes sense, it would be very unintuitive to e.g. have the Traversable instance for List not traverse over the *elements* of the list.
  2. For the instance for WordPtr, we actually need a stronger constraint than Applicative in order for the implementation to type check. A previous version of the library *did* have tMsg :: Applicative m => ..., but performance considerations eventually forced us to open up the hood a bit.

Methods

tMsg :: TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> f mutA -> m (f mutB) Source #

Instances

Instances details
TraverseMsg WordPtr Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> WordPtr mutA -> m (WordPtr mutB) Source #

TraverseMsg Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Struct mutA -> m (Struct mutB) Source #

TraverseMsg Cap Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Cap mutA -> m (Cap mutB) Source #

TraverseMsg List Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> List mutA -> m (List mutB) Source #

TraverseMsg Ptr Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Ptr mutA -> m (Ptr mutB) Source #

Orphan instances

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

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 #