fixfile-0.4.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 Typeable, 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

Minimal complete definition

inf, outf

Methods

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

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

Instances

Fixed Fix Source # 

Methods

inf :: f (Fix f) -> Fix f Source #

outf :: Fix f -> f (Fix f) Source #

Fixed (Stored s) Source # 

Methods

inf :: f (Stored s f) -> Stored s f Source #

outf :: Stored s f -> f (Stored s f) Source #

newtype Fix f Source #

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

Constructors

InF 

Fields

Instances

Fixed Fix Source # 

Methods

inf :: f (Fix f) -> Fix f Source #

outf :: Fix f -> f (Fix f) Source #

data Stored s f Source #

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

Instances

Fixed (Stored s) Source # 

Methods

inf :: f (Stored s f) -> Stored s f Source #

outf :: Stored s f -> f (Stored s f) Source #

MonadState (r (Stored s)) (Transaction r s) Source # 

Methods

get :: Transaction r s (r (Stored s)) #

put :: r (Stored s) -> Transaction r s () #

state :: (r (Stored s) -> (a, r (Stored s))) -> Transaction r s a #

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.

Fixed Typeclasses

class FixedAlg f Source #

FixedAlg is a typeclass for describing the relationship between a Functor that is used with a Fixed combinator and an algebraic datatype in that Functor other than the one used for fixed-point recursion.

Associated Types

type Alg f :: * Source #

Instances

FixedAlg (Set i) Source # 

Associated Types

type Alg (Set i :: * -> *) :: * Source #

FixedAlg (Tree23 (Map k v)) Source # 

Associated Types

type Alg (Tree23 (Map k v) :: * -> *) :: * Source #

FixedAlg (Tree23 (Set k)) Source # 

Associated Types

type Alg (Tree23 (Set k) :: * -> *) :: * Source #

FixedAlg (Trie v) Source # 

Associated Types

type Alg (Trie v :: * -> *) :: * Source #

FixedAlg (BTree n k v) Source # 

Associated Types

type Alg (BTree n k v :: * -> *) :: * Source #

class FixedAlg f => FixedSub f Source #

FixedSub is a typeclass for describing the relationship between a FixedAlg Functor f and that same Functor with Alg f switched from v to v'.

Associated Types

type Sub f v v' :: * -> * Source #

Instances

FixedSub (Tree23 (Map k v)) Source # 

Associated Types

type Sub (Tree23 (Map k v) :: * -> *) v v' :: * -> * Source #

FixedSub (Trie v) Source # 

Associated Types

type Sub (Trie v :: * -> *) v v' :: * -> * Source #

FixedSub (BTree n k v) Source # 

Associated Types

type Sub (BTree n k v :: * -> *) v v' :: * -> * Source #

class FixedSub f => FixedFunctor f where Source #

FixedFunctor is a typeclass for describing mapping behavior for datatypes used with Fixed combinators.

Minimal complete definition

fmapF

Methods

fmapF :: (Fixed g, Fixed g', a ~ Alg f) => (a -> b) -> g f -> g' (Sub f a b) Source #

Map over a Fixed recursive FixedSub f.

Instances

FixedFunctor (Tree23 (Map k v)) Source # 

Methods

fmapF :: (Fixed g, Fixed g', (* ~ a) (Alg (Tree23 (Map k v)))) => (a -> b) -> g (Tree23 (Map k v)) -> g' (Sub (Tree23 (Map k v)) a b) Source #

FixedFunctor (Trie v) Source # 

Methods

fmapF :: (Fixed g, Fixed g', (* ~ a) (Alg (Trie v))) => (a -> b) -> g (Trie v) -> g' (Sub (Trie v) a b) Source #

FixedFunctor (BTree n k v) Source # 

Methods

fmapF :: (Fixed g, Fixed g', (* ~ a) (Alg (BTree n k v))) => (a -> b) -> g (BTree n k v) -> g' (Sub (BTree n k v) a b) Source #

fmapF' :: (FixedFunctor f, Fixed g, a ~ Alg f) => (a -> b) -> g f -> g (Sub f a b) Source #

fmapF, but using a single instance of Fixed.

class FixedAlg f => FixedFoldable f where Source #

FixedFoldable is a typeclass for describing folds over datatypes with Fixed combinators.

Minimal complete definition

foldMapF

Methods

foldMapF :: (Fixed g, Monoid m, a ~ Alg f) => (a -> m) -> g f -> m Source #

Fold over a Fixed recursive FixedAlg f.

Instances

FixedFoldable (Set i) Source # 

Methods

foldMapF :: (Fixed g, Monoid m, (* ~ a) (Alg (Set i))) => (a -> m) -> g (Set i) -> m Source #

FixedFoldable (Tree23 (Map k v)) Source # 

Methods

foldMapF :: (Fixed g, Monoid m, (* ~ a) (Alg (Tree23 (Map k v)))) => (a -> m) -> g (Tree23 (Map k v)) -> m Source #

FixedFoldable (Tree23 (Set k)) Source # 

Methods

foldMapF :: (Fixed g, Monoid m, (* ~ a) (Alg (Tree23 (Set k)))) => (a -> m) -> g (Tree23 (Set k)) -> m Source #

FixedFoldable (Trie v) Source # 

Methods

foldMapF :: (Fixed g, Monoid m, (* ~ a) (Alg (Trie v))) => (a -> m) -> g (Trie v) -> m Source #

FixedFoldable (BTree n k v) Source # 

Methods

foldMapF :: (Fixed g, Monoid m, (* ~ a) (Alg (BTree n k v))) => (a -> m) -> g (BTree n k v) -> m Source #

class FixedSub f => FixedTraversable f where Source #

FixedTraversable is a typeclass for describing traversals over datatypes with Fixed combinators.

Minimal complete definition

traverseF

Methods

traverseF :: (Fixed g, Fixed g', Applicative h, a ~ Alg f) => (a -> h b) -> g f -> h (g' (Sub f a b)) Source #

Traverse over a Fixed recursive FixedSub f in the Applicative h.

Instances

FixedTraversable (Tree23 (Map k v)) Source # 

Methods

traverseF :: (Fixed g, Fixed g', Applicative h, (* ~ a) (Alg (Tree23 (Map k v)))) => (a -> h b) -> g (Tree23 (Map k v)) -> h (g' (Sub (Tree23 (Map k v)) a b)) Source #

FixedTraversable (Trie v) Source # 

Methods

traverseF :: (Fixed g, Fixed g', Applicative h, (* ~ a) (Alg (Trie v))) => (a -> h b) -> g (Trie v) -> h (g' (Sub (Trie v) a b)) Source #

FixedTraversable (BTree n k v) Source # 

Methods

traverseF :: (Fixed g, Fixed g', Applicative h, (* ~ a) (Alg (BTree n k v))) => (a -> h b) -> g (BTree n k v) -> h (g' (Sub (BTree n k v) a b)) Source #

traverseF' :: (FixedTraversable f, Fixed g, Applicative h, a ~ Alg f) => (a -> h b) -> g f -> h (g (Sub f a b)) Source #

traverseF, but using a single instance of Fixed.

Root Data

type Fixable f = (Traversable f, Binary (f (Ptr f)), Typeable f) Source #

A Constraint for data that can be used with a Ref

class FixTraverse t where Source #

FixTraverse is a class based on Traverse but taking an argument of kind ((* -> *) -> *) instead of *.

Minimal complete definition

sequenceAFix

Methods

sequenceAFix :: Applicative f => (forall g. Fixable g => a g -> f (b g)) -> t a -> f (t b) Source #

Given a function that maps from a to b over Fixable g in the Applicative f, traverse over t changing the fixed-point combinator from a to b.

Instances

Fixable f => FixTraverse (Ref f) Source # 

Methods

sequenceAFix :: Applicative f => (forall g. Fixable g => a g -> f (b g)) -> Ref f a -> f (Ref f b) Source #

type Root r = (FixTraverse r, Binary (r Ptr)) Source #

A Root is a datastructure that is an instance of FixTraverse and Binary. This acts as a sort of "header" for the file where the Root may have several Refs under it to different Functors.

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

Eq (Ptr f) Source # 

Methods

(==) :: Ptr f -> Ptr f -> Bool #

(/=) :: Ptr f -> Ptr f -> Bool #

Ord (Ptr f) Source # 

Methods

compare :: Ptr f -> Ptr f -> Ordering #

(<) :: Ptr f -> Ptr f -> Bool #

(<=) :: Ptr f -> Ptr f -> Bool #

(>) :: Ptr f -> Ptr f -> Bool #

(>=) :: Ptr f -> Ptr f -> Bool #

max :: Ptr f -> Ptr f -> Ptr f #

min :: Ptr f -> Ptr f -> Ptr f #

Read (Ptr f) Source # 
Show (Ptr f) Source # 

Methods

showsPrec :: Int -> Ptr f -> ShowS #

show :: Ptr f -> String #

showList :: [Ptr f] -> ShowS #

Generic (Ptr f) Source # 

Associated Types

type Rep (Ptr f) :: * -> * #

Methods

from :: Ptr f -> Rep (Ptr f) x #

to :: Rep (Ptr f) x -> Ptr f #

Binary (Ptr f) Source # 

Methods

put :: Ptr f -> Put #

get :: Get (Ptr f) #

putList :: [Ptr f] -> Put #

Hashable (Ptr f) Source # 

Methods

hashWithSalt :: Int -> Ptr f -> Int #

hash :: Ptr f -> Int #

Binary (Ref f Ptr) Source # 

Methods

put :: Ref f Ptr -> Put #

get :: Get (Ref f Ptr) #

putList :: [Ref f Ptr] -> Put #

type Rep (Ptr f) Source # 
type Rep (Ptr f)

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

Instances

Fixable f => FixTraverse (Ref f) Source # 

Methods

sequenceAFix :: Applicative f => (forall g. Fixable g => a g -> f (b g)) -> Ref f a -> f (Ref f b) Source #

Generic (Ref f g) Source # 

Associated Types

type Rep (Ref f g) :: * -> * #

Methods

from :: Ref f g -> Rep (Ref f g) x #

to :: Rep (Ref f g) x -> Ref f g #

Binary (Ref f Ptr) Source # 

Methods

put :: Ref f Ptr -> Put #

get :: Get (Ref f Ptr) #

putList :: [Ref f Ptr] -> Put #

type Rep (Ref f g) Source # 
type Rep (Ref f g) = D1 (MetaData "Ref" "Data.FixFile" "fixfile-0.4.0.0-6Rx1TzJaeAW4euV9dndAsy" False) (C1 (MetaCons "Ref" PrefixI True) (S1 (MetaSel (Just Symbol "deRef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (g f))))

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 => 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 => 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.

clone :: Root r => FilePath -> FixFile r -> IO () Source #

It's potentially useful to copy the contents of a FixFile to a new location as a backup. The clone function essentially runs vacuum on a FixFile, but writes the output to the specified path.

vacuum :: Root 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.

Instances

MonadState (r (Stored s)) (Transaction r s) Source # 

Methods

get :: Transaction r s (r (Stored s)) #

put :: r (Stored s) -> Transaction r s () #

state :: (r (Stored s) -> (a, r (Stored s))) -> Transaction r s a #

Monad (Transaction f s) Source # 

Methods

(>>=) :: Transaction f s a -> (a -> Transaction f s b) -> Transaction f s b #

(>>) :: Transaction f s a -> Transaction f s b -> Transaction f s b #

return :: a -> Transaction f s a #

fail :: String -> Transaction f s a #

Functor (Transaction f s) Source # 

Methods

fmap :: (a -> b) -> Transaction f s a -> Transaction f s b #

(<$) :: a -> Transaction f s b -> Transaction f s a #

Applicative (Transaction f s) Source # 

Methods

pure :: a -> Transaction f s a #

(<*>) :: Transaction f s (a -> b) -> Transaction f s a -> Transaction f s b #

(*>) :: Transaction f s a -> Transaction f s b -> Transaction f s b #

(<*) :: Transaction f s a -> Transaction f s b -> Transaction f s a #

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 => 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.

writeExceptTransaction :: Root r => FixFile r -> (forall s. ExceptT e (Transaction r s) a) -> IO (Either e a) Source #

The writeExceptTransaction function behaves like writeTransaction, but applies to a Transaction wrapped in ExceptT. In the event that an exception propagates through the Transaction, the updates are not committed to disk.

This is meant to provide a mechanism for aborting Transactions.

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.

getRoot :: Root r => Transaction r s (r Fix) Source #

Get the root datastructure from the transaction as r Fix.

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

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