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

Copyright(C) 2015-2017 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

>>> import Control.Monad.Primitive

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.

Minimal complete definition

Nothing

Methods

struct :: Dict (Coercible (t s) (Object s)) Source #

struct :: Coercible (t s) (Object s) => Dict (Coercible (t s) (Object s)) Source #

Instances
Struct Object Source # 
Instance details

Defined in Data.Struct.Internal

Methods

struct :: Dict (Coercible (Object s) (Object s)) Source #

Struct Label Source # 
Instance details

Defined in Data.Struct.Internal.Label

Methods

struct :: Dict (Coercible (Label s) (Object s)) Source #

Struct (LinkCut a) Source # 
Instance details

Defined in Data.Struct.Internal.LinkCut

Methods

struct :: Dict (Coercible (LinkCut a s) (Object s)) Source #

Struct (Order a) Source # 
Instance details

Defined in Data.Struct.Internal.Order

Methods

struct :: Dict (Coercible (Order a s) (Object s)) Source #

data Object s Source #

Constructors

Object 
Instances
Struct Object Source # 
Instance details

Defined in Data.Struct.Internal

Methods

struct :: Dict (Coercible (Object s) (Object s)) Source #

Eq (Object s) Source # 
Instance details

Defined in Data.Struct.Internal

Methods

(==) :: Object s -> Object s -> Bool #

(/=) :: Object s -> Object s -> Bool #

coerceF :: Dict (Coercible a b) -> a -> b Source #

coerceB :: Dict (Coercible a b) -> b -> a Source #

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 #

Box is designed to mirror object's single field but using the Null type instead of a mutable array. This hack relies on GHC reusing the same Null data constructor for all occurrences. Box's field must not be strict to prevent the compiler from making assumptions about its contents.

Constructors

Box Null 

data Null Source #

Constructors

Null 

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

Predicate to check if a struct is Nil.

>>> isNil (Nil :: Object (PrimState IO))
True
>>> o <- alloc 1 :: IO (Object (PrimState IO))
>>> isNil o
False

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.

Instances
Precomposable (Slot :: k1 -> k2 -> Type) Source # 
Instance details

Defined in Data.Struct.Internal

Methods

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

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
Precomposable (Slot :: k1 -> k2 -> Type) Source # 
Instance details

Defined in Data.Struct.Internal

Methods

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

Precomposable (Field :: k -> Type -> Type) Source # 
Instance details

Defined in Data.Struct.Internal

Methods

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

slot Source #

Arguments

:: Int

slot

-> Slot s t 

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

cas :: (PrimMonad m, Struct x, Struct y) => Slot x y -> x (PrimState m) -> y (PrimState m) -> y (PrimState m) -> m (Bool, y (PrimState m)) Source #

Compare-and-swap the value of the slot. Takes the expected old value, the new value and returns if it succeeded and the value found.

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
Precomposable (Field :: k -> Type -> Type) Source # 
Instance details

Defined in Data.Struct.Internal

Methods

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

field Source #

Arguments

:: Int

slot

-> Field s a 

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

unboxedField Source #

Arguments

:: Prim a 
=> Int

slot

-> Int

argument

-> Field s a 

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

initializeUnboxedField Source #

Arguments

:: (PrimMonad m, Struct x) 
=> Int

slot

-> Int

elements

-> Int

element size

-> x (PrimState m)

struct

-> m (MutableByteArray (PrimState m)) 

Initialized the mutable array used by unboxedField. Returns the array after storing it in the struct to help with initialization.

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

Modifiers

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

modifyField' :: (Struct x, PrimMonad m) => Field x a -> x (PrimState m) -> (a -> a) -> m () Source #