linear-base-0.1.0: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Foreign.Marshal.Pure

Description

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 Pools?

Pools 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

Allocating and using values on the heap

data Pool Source #

Pools represent collections of values. A Pool can be consume-ed. This is a no-op: it does not deallocate the data in that pool. It cannot do so, because accessible values might still exist. Consuming a pool simply makes it impossible to add new data to the pool.

Instances

Instances details
Consumable Pool Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

consume :: Pool %1 -> () Source #

Dupable Pool Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

dupV :: forall (n :: Nat). KnownNat n => Pool %1 -> V n Pool Source #

dup2 :: Pool %1 -> (Pool, Pool) Source #

withPool :: (Pool %1 -> Ur b) %1 -> Ur b Source #

Given a linear computation that manages memory, run that computation.

data Box a Source #

'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

Instances details
Storable (Box a) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

sizeOf :: Box a -> Int #

alignment :: Box a -> Int #

peekElemOff :: Ptr (Box a) -> Int -> IO (Box a) #

pokeElemOff :: Ptr (Box a) -> Int -> Box a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Box a) #

pokeByteOff :: Ptr b -> Int -> Box a -> IO () #

peek :: Ptr (Box a) -> IO (Box a) #

poke :: Ptr (Box a) -> Box a -> IO () #

Representable (Box a) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Associated Types

type AsKnown (Box a) Source #

Methods

toKnown :: Box a %1 -> AsKnown (Box a) Source #

ofKnown :: AsKnown (Box a) %1 -> Box a Source #

KnownRepresentable (Box a) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable (Box a))

type AsKnown (Box a) Source # 
Instance details

Defined in Foreign.Marshal.Pure

type AsKnown (Box a) = Box a

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

Instances details
KnownRepresentable Int Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable Int)

KnownRepresentable Word Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable Word)

KnownRepresentable () Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable ())

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

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable (Maybe a))

KnownRepresentable (Ptr a) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable (Ptr a))

KnownRepresentable a => KnownRepresentable (Ur a) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable (Ur a))

KnownRepresentable (Box a) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable (Box a))

(KnownRepresentable a, KnownRepresentable b) => KnownRepresentable (a, b) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable (a, b))

(KnownRepresentable a, KnownRepresentable b, KnownRepresentable c) => KnownRepresentable (a, b, c) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Methods

storable :: Dict (Storable (a, b, c))

class KnownRepresentable (AsKnown a) => Representable a where Source #

Laws of Representable:

  • toKnown must be total
  • ofKnown may be partial, but must be total on the image of toKnown
  • ofKnown . toKnown == id

Minimal complete definition

Nothing

Associated Types

type AsKnown a :: Type Source #

Methods

toKnown :: a %1 -> AsKnown a Source #

default toKnown :: (MkRepresentable a b, AsKnown a ~ AsKnown b) => a %1 -> AsKnown a Source #

ofKnown :: AsKnown a %1 -> a Source #

default ofKnown :: (MkRepresentable a b, AsKnown a ~ AsKnown b) => AsKnown a %1 -> a Source #

Instances

Instances details
Representable Int Source # 
Instance details

Defined in Foreign.Marshal.Pure

Associated Types

type AsKnown Int Source #

Representable Word Source # 
Instance details

Defined in Foreign.Marshal.Pure

Associated Types

type AsKnown Word Source #

Representable () Source # 
Instance details

Defined in Foreign.Marshal.Pure

Associated Types

type AsKnown () Source #

Methods

toKnown :: () %1 -> AsKnown () Source #

ofKnown :: AsKnown () %1 -> () Source #

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

Defined in Foreign.Marshal.Pure

Associated Types

type AsKnown (Maybe a) Source #

Methods

toKnown :: Maybe a %1 -> AsKnown (Maybe a) Source #

ofKnown :: AsKnown (Maybe a) %1 -> Maybe a Source #

Representable (Ptr a) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Associated Types

type AsKnown (Ptr a) Source #

Methods

toKnown :: Ptr a %1 -> AsKnown (Ptr a) Source #

ofKnown :: AsKnown (Ptr a) %1 -> Ptr a Source #

Representable (Box a) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Associated Types

type AsKnown (Box a) Source #

Methods

toKnown :: Box a %1 -> AsKnown (Box a) Source #

ofKnown :: AsKnown (Box a) %1 -> Box a Source #

(Representable a, Representable b) => Representable (a, b) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Associated Types

type AsKnown (a, b) Source #

Methods

toKnown :: (a, b) %1 -> AsKnown (a, b) Source #

ofKnown :: AsKnown (a, b) %1 -> (a, b) Source #

(Representable a, Representable b, Representable c) => Representable (a, b, c) Source # 
Instance details

Defined in Foreign.Marshal.Pure

Associated Types

type AsKnown (a, b, c) Source #

Methods

toKnown :: (a, b, c) %1 -> AsKnown (a, b, c) Source #

ofKnown :: AsKnown (a, b, c) %1 -> (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:

  • toRepr must be total
  • ofRepr may be partial, but must be total on the image of toRepr
  • ofRepr . toRepr = id

Methods

toRepr :: a %1 -> b Source #

ofRepr :: b %1 -> a Source #

Orphan instances

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

Methods

sizeOf :: Maybe a -> Int #

alignment :: Maybe a -> Int #

peekElemOff :: Ptr (Maybe a) -> Int -> IO (Maybe a) #

pokeElemOff :: Ptr (Maybe a) -> Int -> Maybe a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Maybe a) #

pokeByteOff :: Ptr b -> Int -> Maybe a -> IO () #

peek :: Ptr (Maybe a) -> IO (Maybe a) #

poke :: Ptr (Maybe a) -> Maybe a -> IO () #

Storable a => Storable (Ur a) Source # 
Instance details

Methods

sizeOf :: Ur a -> Int #

alignment :: Ur a -> Int #

peekElemOff :: Ptr (Ur a) -> Int -> IO (Ur a) #

pokeElemOff :: Ptr (Ur a) -> Int -> Ur a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ur a) #

pokeByteOff :: Ptr b -> Int -> Ur a -> IO () #

peek :: Ptr (Ur a) -> IO (Ur a) #

poke :: Ptr (Ur a) -> Ur a -> IO () #