Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module introduces primitives to safely allocate and discard system heap memory (not GC heap memory) for storing values explicitly. (Basically, a haskell program has a GC that at runtime, manages its own heap by freeing and allocating space from the system heap.) Values discarded explicitly don't need to be managed by the garbage collector (GC), which therefore has less work to do. Less work for the GC can sometimes mean more predictable request latencies in multi-threaded and distributed applications.
This module is meant to be imported qualified.
The Interface
Run a computation that uses heap memory by passing a continuation to
withPool
of type Pool %1-> Ur b
. Allocate and free with
alloc
and deconstruct
. Make as many or as few pools you need, by
using the Dupable
and Consumable
instances of Pool
.
A toy example:
>>>
:set -XLinearTypes
>>>
import Data.Unrestricted.Linear
>>>
import qualified Foreign.Marshal.Pure as Manual
>>>
:{
nothingWith3 :: Pool %1-> Ur Int nothingWith3 pool = move (Manual.deconstruct (Manual.alloc 3 pool)) :}
>>>
unur (Manual.withPool nothingWith3)
3
What are Pool
s?
Pool
s are memory pools from which a user can safely allocate and use
heap memory manually by passing withPool
a continuation.
An alternative design would have allowed passing continuations to
allocation functions but this could break tail-recursion in certain cases.
Pools play another role: resilience to exceptions. If an exception is raised, all the data in the pool is deallocated.
Note that data from one pool can refer to data in another pool and vice versa.
Large Examples
You can find example data structure implementations in Foreign.List
and
Foreign.Heap
here.
Synopsis
- data Pool
- withPool :: (Pool %1 -> Ur b) %1 -> Ur b
- data Box a
- alloc :: forall a. Representable a => a %1 -> Pool %1 -> Box a
- deconstruct :: Representable a => Box a %1 -> a
- class KnownRepresentable a
- class KnownRepresentable (AsKnown a) => Representable a where
- class Representable b => MkRepresentable a b | a -> b where
Allocating and using values on the heap
withPool :: (Pool %1 -> Ur b) %1 -> Ur b Source #
Given a linear computation that manages memory, run that computation.
'Box a' is the abstract type of manually managed data. It can be used as
part of data type definitions in order to store linked data structure off
heap. See Foreign.List
and Foreign.Pair
in the examples
directory of
the source repository.
Instances
Storable (Box a) Source # | |
Representable (Box a) Source # | |
KnownRepresentable (Box a) Source # | |
Defined in Foreign.Marshal.Pure | |
type AsKnown (Box a) Source # | |
Defined in Foreign.Marshal.Pure |
alloc :: forall a. Representable a => a %1 -> Pool %1 -> Box a Source #
Store a value a
on the system heap that is not managed by the GC.
deconstruct :: Representable a => Box a %1 -> a Source #
Retrieve the value stored on system heap memory.
Typeclasses for values that can be allocated
class KnownRepresentable a Source #
This abstract type class represents values natively known to have a GC-less implementation. Basically, these are sequences (represented as tuples) of base types.
Instances
KnownRepresentable Int Source # | |
Defined in Foreign.Marshal.Pure | |
KnownRepresentable Word Source # | |
Defined in Foreign.Marshal.Pure | |
KnownRepresentable () Source # | |
Defined in Foreign.Marshal.Pure | |
KnownRepresentable a => KnownRepresentable (Maybe a) Source # | |
Defined in Foreign.Marshal.Pure | |
KnownRepresentable (Ptr a) Source # | |
Defined in Foreign.Marshal.Pure | |
KnownRepresentable a => KnownRepresentable (Ur a) Source # | |
Defined in Foreign.Marshal.Pure | |
KnownRepresentable (Box a) Source # | |
Defined in Foreign.Marshal.Pure | |
(KnownRepresentable a, KnownRepresentable b) => KnownRepresentable (a, b) Source # | |
Defined in Foreign.Marshal.Pure | |
(KnownRepresentable a, KnownRepresentable b, KnownRepresentable c) => KnownRepresentable (a, b, c) Source # | |
Defined in Foreign.Marshal.Pure |
class KnownRepresentable (AsKnown a) => Representable a where Source #
Laws of Representable
:
Nothing
Instances
Representable Int Source # | |
Representable Word Source # | |
Representable () Source # | |
Representable a => Representable (Maybe a) Source # | |
Representable (Ptr a) Source # | |
Representable (Box a) Source # | |
(Representable a, Representable b) => Representable (a, b) Source # | |
(Representable a, Representable b, Representable c) => Representable (a, b, c) Source # | |
class Representable b => MkRepresentable a b | a -> b where Source #
This is an easier way to create an instance of Representable
. It is a bit
abusive to use a type class for this (after all, it almost never makes sense
to use this as a constraint). But it works in practice.
To use, define an instance of MkRepresentable myType intermediateType
then declare the following instance:
instance Representable myType where {type AsKnown = AsKnown intermediateType}
And the default instance mechanism will create the appropriate
Representable
instance.
Laws of MkRepresentable
:
Orphan instances
Storable a => Storable (Maybe a) Source # | |
Storable a => Storable (Ur a) Source # | |