structs-0: Strict GC'd imperative object-oriented programming with cheap pointers.

Copyright(C) 2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellUnsafe
LanguageHaskell2010

Data.Struct.Internal

Contents

Description

 

Synopsis

Documentation

data Dict p where Source

A Dict reifies an instance of the constraint p into a value.

Constructors

Dict :: p => Dict p 

st :: PrimMonad m => ST (PrimState m) a -> m a Source

Run an ST calculation inside of a PrimMonad. This lets us avoid dispatching everything through the PrimMonad dictionary.

class Struct t where Source

An instance for Struct t is a witness to the machine-level equivalence of t and Object. The argument to struct is ignored and is only present to help type inference.

Methods

struct :: proxy t -> Dict (Coercible (t s) (Object s)) Source

data Object s Source

Constructors

Object 

unsafeCoerceStruct :: (Struct x, Struct y) => x s -> y s Source

eqStruct :: Struct t => t s -> t s -> Bool Source

pattern Struct :: () => Struct t => SmallMutableArray# s (Any *) -> t s Source

alloc :: (PrimMonad m, Struct t) => Int -> m (t (PrimState m)) Source

Allocate a structure made out of n slots. Initialize the structure before proceeding!

Tony Hoare's billion dollar mistake

data Box Source

Constructors

Box !Null 

data Null Source

Constructors

Null 

isNil :: Struct t => t s -> Bool Source

pattern Nil :: () => Struct t => t s Source

Truly imperative.

Faking SmallMutableArrayArray#s

Field Accessors

data Slot x y Source

A Slot is a reference to another unboxed mutable object.

Constructors

Slot (forall s. SmallMutableArray# s Any -> State# s -> (#State# s, SmallMutableArray# s Any#)) (forall s. SmallMutableArray# s Any -> SmallMutableArray# s Any -> State# s -> State# s) 

Instances

class Precomposable t where Source

We can compose slots to get a nested slot or field accessor

Methods

(#) :: Slot x y -> t y z -> t x z Source

Instances

slot :: Int -> Slot s t Source

The Slot at the given position in a Struct

get :: (PrimMonad m, Struct x, Struct y) => Slot x y -> x (PrimState m) -> m (y (PrimState m)) Source

Get the value from a Slot

set :: (PrimMonad m, Struct x, Struct y) => Slot x y -> x (PrimState m) -> y (PrimState m) -> m () Source

Set the value of a Slot

data Field x a Source

A Field is a reference from a struct to a normal Haskell data type.

Constructors

Field (forall s. SmallMutableArray# s Any -> State# s -> (#State# s, a#)) (forall s. SmallMutableArray# s Any -> a -> State# s -> State# s) 

Instances

field :: Int -> Field s a Source

Store the reference to the Haskell data type in a normal field

unboxedField :: Prim a => Int -> Int -> Field s a Source

Store the reference in the nth slot of the nth argument, treated as a MutableByteArray

getField :: (PrimMonad m, Struct x) => Field x a -> x (PrimState m) -> m a Source

Get the value of a field in a struct

setField :: (PrimMonad m, Struct x) => Field x a -> x (PrimState m) -> a -> m () Source

Set the value of a field in a struct