| Copyright | (C) 2016 Rev. Johnny Healey |
|---|---|
| License | LGPL-3 |
| Maintainer | Rev. Johnny Healey <rev.null@gmail.com> |
| Stability | experimental |
| Portability | unknown |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.FixFile
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.
- class Fixed g where
- newtype Fix f = InF {}
- data Stored s f
- type CataAlg f a = f a -> a
- cata :: (Functor f, Fixed g) => CataAlg f a -> g f -> a
- type AnaAlg f a = a -> f a
- ana :: (Functor f, Fixed g) => AnaAlg f a -> a -> g f
- type ParaAlg g f a = f (g f, a) -> a
- para :: (Functor f, Fixed g) => ParaAlg g f a -> g f -> a
- iso :: (Functor f, Fixed g, Fixed h) => g f -> h f
- class Root r where
- data Ptr f
- data Ref f g = Ref {
- deRef :: g f
- ref :: Lens' (Ref f g) (g f)
- data FixFile r
- createFixFile :: (Root r, Binary (r Ptr), Typeable r) => r Fix -> FilePath -> IO (FixFile r)
- createFixFileHandle :: (Root r, Binary (r Ptr), Typeable r) => r Fix -> FilePath -> Handle -> IO (FixFile r)
- openFixFile :: Binary (r Ptr) => FilePath -> IO (FixFile r)
- openFixFileHandle :: Binary (r Ptr) => FilePath -> Handle -> IO (FixFile r)
- closeFixFile :: FixFile r -> IO ()
- vacuum :: (Root r, Binary (r Ptr), Typeable r) => FixFile r -> IO ()
- data Transaction r s a
- alterT :: (tr ~ Transaction (Ref f) s, Traversable f, Binary (f (Ptr f))) => (Stored s f -> Stored s f) -> tr ()
- lookupT :: (tr ~ Transaction (Ref f) s, Traversable f, Binary (f (Ptr f))) => (Stored s f -> a) -> tr a
- readTransaction :: Root r => FixFile r -> (forall s. Transaction r s a) -> IO a
- writeTransaction :: (Root r, Binary (r Ptr), Typeable r) => FixFile r -> (forall s. Transaction r s a) -> IO a
- subTransaction :: Lens' (r (Stored s)) (r' (Stored s)) -> Transaction r' s a -> Transaction r s a
- getFull :: Functor f => Transaction (Ref f) s (Fix f)
Fixed point combinators
Stored is a fixed-point combinator of f in Transaction s.
Instances
| Fixed (Stored s) Source | |
| MonadState (r (Stored s)) (Transaction r s) Source |
F-Algebras
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.
Root Data
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 inside a r PtrTransaction.
writeRoot :: r (Stored s) -> Transaction r' s (r Ptr) Source
Serialize inside a r PtrTransaction. This will result in
| changes to any recursive structures to be written as well.
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.
FixFiles
createFixFileHandle :: (Root r, Binary (r Ptr), Typeable r) => r Fix -> FilePath -> Handle -> IO (FixFile r) Source
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.
Instances
| MonadState (r (Stored s)) (Transaction r s) Source | |
| Monad (Transaction f s) Source | |
| Functor (Transaction f s) Source | |
| Applicative (Transaction f s) Source |
alterT :: (tr ~ Transaction (Ref f) s, Traversable f, Binary (f (Ptr f))) => (Stored s f -> Stored s f) -> tr () Source
lookupT :: (tr ~ Transaction (Ref f) s, Traversable f, Binary (f (Ptr f))) => (Stored s f -> a) -> tr a Source
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.