fixfile-0.1.0.0: File-backed recursive data structures.

Copyright(C) 2016 Rev. Johnny Healey
LicenseLGPL-3
MaintainerRev. Johnny Healey <rev.null@gmail.com>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Data.FixFile

Contents

Description

A FixFile is file for storing recursive data. The file supports MVCC through an append-only file.

In order to eliminate distinctions between data structures that are file-backed versus in-memory, this library makes heavy use of lazy IO. Transactions are used to ensure safety of the unsafe IO.

The data structures used by a FixFile should not be recursive directly, but should have instances of Foldable, Traversable, and Binary and should be structured such that the fixed point of the data type is recursive.

There is also the concept of the Root data of a FixFile. This can be used as a kind of header for a FixFile that can allow several recursive data structures to be modified in a single transaction.

Synopsis

Fixed point combinators

class Fixed g where Source

Fixed is a typeclass for representing the fixed point of a Functor. A well-behaved instance of Fixed should not change the shape of the underlying Functor.

In other words, the following should always be true: outf (inf x) == x

Methods

inf :: f (g f) -> g f Source

outf :: g f -> f (g f) Source

Instances

newtype Fix f Source

Fix is a type for creating an in-memory representation of the fixed point of a Functor.

Constructors

InF 

Fields

outF :: f (Fix f)
 

Instances

data Stored s f Source

Stored is a fixed-point combinator of f in Transaction s.

Instances

F-Algebras

type CataAlg f a = f a -> a Source

CataAlg is a catamorphism F-Algebra.

cata :: (Functor f, Fixed g) => CataAlg f a -> g f -> a Source

cata applies a CataAlg over a fixed point of a Functor.

type AnaAlg f a = a -> f a Source

AnaAlg is an anamorpism F-Algebra.

ana :: (Functor f, Fixed g) => AnaAlg f a -> a -> g f Source

ana applies an AnaAlg over an argument to produce a fixed-point of a Functor.

type ParaAlg g f a = f (g f, a) -> a Source

ParaAlg is a paramorphism F-Algebra.

para :: (Functor f, Fixed g) => ParaAlg g f a -> g f -> a Source

para applies a ParaAlg over a fixed point of a Functor.

iso :: (Functor f, Fixed g, Fixed h) => g f -> h f Source

iso maps from a fixed point of a Functor to a different fixed point of the same Functor. For any two well-behaved instances of Fixed, the shape of the Functor should remain unchanged.

Root Data

class Root r where Source

A Root datastructure acts as a kind of header that can contain one or more Refs to different recursive structures. It takes one argument, which has the kind of ((* -> *) -> *). This argument should be either an instance of Fixed or a Ptr. If it is an instance of Fixed, then the Root can contain recursive data structures. If it is passed Ptr as an argument, then the Root will contain a non-recursive structure, but can be serialized.

Methods

readRoot :: r Ptr -> Transaction r' s (r (Stored s)) Source

Deserialize r Ptr inside a Transaction.

writeRoot :: r (Stored s) -> Transaction r' s (r Ptr) Source

Serialize r Ptr inside a Transaction. This will result in | changes to any recursive structures to be written as well.

rootIso :: (Fixed g, Fixed h) => r g -> r h Source

iso, but applied to an instance of Root.

Instances

(Typeable (* -> *) f, Binary (f (Ptr f)), Traversable f) => Root (Ref f) Source 

data Ptr f Source

A Ptr points to a location in a FixFile and has a phantom type for a Functor f. A Root expects an argument that resembles a Fixed, but we can pass it a Ptr instead. This is not a well-formed Fixed because it can't be unpacked into f (Ptr f).

But, it can be serialized, which allows a Root object that takes this as an argument to be serialized.

Instances

data Ref f g Source

A Ref is a reference to a Functor f in the Fixed instance of g.

This is an instance of Root and acts to bridge between the Root and the recursively defined data structure that is (g f).

Constructors

Ref 

Fields

deRef :: g f
 

Instances

(Typeable (* -> *) f, Binary (f (Ptr f)), Traversable f) => Root (Ref f) Source 
Generic (Ref f g) Source 
Binary (Ref f Ptr) Source 
type Rep (Ref f g) Source 

ref :: Lens' (Ref f g) (g f) Source

Lens for accessing the value stored in a Ref

FixFiles

data FixFile r Source

A FixFile is a handle for accessing a file-backed recursive data structure. r is the Root object stored in the FixFile.

createFixFile :: (Root r, Binary (r Ptr), Typeable r) => r Fix -> FilePath -> IO (FixFile r) Source

Create a FixFile, using Fix f as the initial structure to store at the location described by FilePath.

createFixFileHandle :: (Root r, Binary (r Ptr), Typeable r) => r Fix -> FilePath -> Handle -> IO (FixFile r) Source

Create a FixFile, using Fix f as the initial structure to store at the location described by FilePath and using the Handle to the file to be created.

openFixFile :: Binary (r Ptr) => FilePath -> IO (FixFile r) Source

Open a FixFile from the file described by FilePath.

openFixFileHandle :: Binary (r Ptr) => FilePath -> Handle -> IO (FixFile r) Source

Open a FixFile from the file described by FilePath and using the Handle to the file.

closeFixFile :: FixFile r -> IO () Source

Close a FixFile. This can potentially cause errors on data that is lazily being read from a Transaction.

vacuum :: (Root r, Binary (r Ptr), Typeable r) => FixFile r -> IO () Source

Because a FixFile is backed by an append-only file, there is a periodic need to vacuum the file to garbage collect data that is no longer referenced from the root. This task operates on a temporary file that then replaces the file that backs FixFile.

The memory usage of this operation scales with the recursive depth of the structure stored in the file.

Transactions

data Transaction r s a Source

A Transaction is an isolated execution of a read or update operation on the root object stored in a FixFile. r is the Root data that is stored by the FixFile. s is a phantom type used to isolate Stored values to the transaction where they are run.

alterT :: (tr ~ Transaction (Ref f) s, Traversable f, Binary (f (Ptr f))) => (Stored s f -> Stored s f) -> tr () Source

The preferred way to modify the root object of a FixFile is by using alterT. It applies a function that takes the root object as a Stored s f and returns the new desired head of the same type.

lookupT :: (tr ~ Transaction (Ref f) s, Traversable f, Binary (f (Ptr f))) => (Stored s f -> a) -> tr a Source

The preferred way to read from a FixFile is to use lookupT. It applies a function that takes a Stored s f and returns a value.

readTransaction :: Root r => FixFile r -> (forall s. Transaction r s a) -> IO a Source

Perform a read transaction on a FixFile. This transaction cannot modify the root object stored in the file. The returned value is lazily evaluated, but will always correspond to the root object at the start of the transaction.

writeTransaction :: (Root r, Binary (r Ptr), Typeable r) => FixFile r -> (forall s. Transaction r s a) -> IO a Source

Perform a write transaction on a FixFile. This operation differs from the readTransaction in that the root object stored in the file can potentially be updated by this Transaction.

subTransaction :: Lens' (r (Stored s)) (r' (Stored s)) -> Transaction r' s a -> Transaction r s a Source

Perform a Transaction on a part of the root object.

getFull :: Functor f => Transaction (Ref f) s (Fix f) Source

Get the full datastructure from the transaction as a Fix f.