Safe Haskell | None |
---|---|
Language | Haskell2010 |
Working with Ptr
s 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
Synopsis
- type Ptr s a = ScopedResource s (Ptr a)
- mut :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadUnliftIO m) => a -> Scoped (s ': ss) m (Ptr s a)
- (.=) :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadIO m, s :< ss) => Ptr s a -> a -> Scoped ss m ()
- (?) :: forall a (m :: Type -> Type) s (ss :: [Type]). (Storable a, MonadIO m, s :< ss) => Ptr s a -> Scoped ss m a
Documentation
type Ptr s a = ScopedResource s (Ptr a) Source #
A Ptr
that is associated to a scope but it is mutable (can be read from and written to)
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.