scoped-codensity-0.1.0.2: CPS resource allocation but as a Monad and completely safe
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Scoped.Ptr

Description

Working with Ptrs in a way that prevents use after free

>>> :set -XPostfixOperators
>>> import Control.Monad.Scoped.Internal
>>> scoped do x <- mut (69 :: Word); x .= 42; (x ?)
42

Since: 0.1.0.0

Synopsis

Documentation

type Ptr s a = ScopedResource s (Ptr a) Source #

A Ptr that is associated to a scope

Since: 0.1.0.0

foreignPtr :: forall (m :: Type -> Type) a s (ss :: [Type]). MonadUnliftIO m => ForeignPtr a -> Scoped (s ': ss) m (Ptr s a) Source #

this is a wrapper around withForeignPtr to allow for safe usage of this function in a scope

Since: 0.1.0.2

wrapScoped :: forall m s (ss :: [Type]) a r. (Monad m, s :< ss) => (Ptr a -> m r) -> Ptr s a -> Scoped ss m r Source #

takes a function that does something with a Ptr and makes it safe

Since: 0.1.0.2

mut :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadUnliftIO m) => a -> Scoped (s ': ss) m (Ptr s a) Source #

Acquire mutable memory for the duration of a scope. The value is automatically dropped at the end of the scope.

Since: 0.1.0.0

(.=) :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadIO m, s :< ss) => Ptr s a -> a -> Scoped ss m () Source #

write a value to a pointer

Since: 0.1.0.0

(?) :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadIO m, s :< ss) => Ptr s a -> Scoped ss m a Source #

read a value from a pointer

Since: 0.1.0.0