HGraphStorage-0.0.3: Graph database stored on disk

Safe HaskellNone
LanguageHaskell98

Database.Graph.HGraphStorage.API

Description

Higher level API for reading and writing

Synopsis

Documentation

data GsData Source

State for the monad

data IndexInfo Source

Index metadata

Constructors

IndexInfo 

Fields

iiName :: Text
 
iiTypes :: [Text]
 
iiProps :: [Text]
 

withGraphStorage :: forall m a. (MonadThrow m, MonadIO m, MonadLogger m, MonadBaseControl IO m) => FilePath -> GraphSettings -> GraphStorageT (ResourceT m) a -> m a Source

Run a computation with the graph storage engine, storing the data in the given directory

newtype GraphStorageT m a Source

Our monad transformer.

Constructors

Gs 

Fields

unIs :: StateT GsData m a
 

data GraphObject a Source

An object with a type and properties.

Constructors

GraphObject 

Instances

Eq a => Eq (GraphObject a) 
Ord a => Ord (GraphObject a) 
Read a => Read (GraphObject a) 
Show a => Show (GraphObject a) 
Typeable (* -> *) GraphObject 

data GraphRelation a b Source

A relation between two objects, with a type and properties.

Instances

(Eq a, Eq b) => Eq (GraphRelation a b) 
(Ord a, Ord b) => Ord (GraphRelation a b) 
(Read a, Read b) => Read (GraphRelation a b) 
(Show a, Show b) => Show (GraphRelation a b) 
Typeable (* -> * -> *) GraphRelation 

getHandles :: Monad m => GraphStorageT m Handles Source

Get the file handles.

getModel :: Monad m => GraphStorageT m Model Source

Get the currently known model.

getDirectory :: Monad m => GraphStorageT m FilePath Source

Get the currently known model.

getSettings :: Monad m => GraphStorageT m GraphSettings Source

Get the current settings.

getIndices :: Monad m => GraphStorageT m [(IndexInfo, Trie Int16 ObjectID)] Source

Get the current indices.

indexFile :: Monad m => GraphStorageT m FilePath Source

The file used to store the index information.

removeOldValuesFromIndex :: GraphUsableMonad m => GraphObject a -> Maybe ObjectID -> GraphStorageT m [(Text, [Trie Int16 ObjectID], [PropertyValue])] Source

Checks if there is a duplicate on any applicable index. Then remove obsolete values from the index, and generate the list of values to add We'll only add the values once the object has been properly written, so we can have the ID of new objects.

checkDuplicates :: GraphUsableMonad m => Maybe ObjectID -> [(Text, [Trie Int16 ObjectID], [PropertyValue])] -> GraphStorageT m () Source

Check if duplicates exist in index.

insertNewValuesInIndex :: GraphUsableMonad m => ObjectID -> [(Text, [Trie Int16 ObjectID], [PropertyValue])] -> GraphStorageT m () Source

Insert new values in applicable indices.

createProperties :: GraphUsableMonad m => Map Text [PropertyValue] -> GraphStorageT m PropertyID Source

Create properties from map, returns the first ID in the chain

populateObject :: GraphUsableMonad m => ObjectID -> Object -> GraphStorageT m (GraphObject ObjectID) Source

(Internal) Fill an object with its properties

getObject :: GraphUsableMonad m => ObjectID -> GraphStorageT m (GraphObject ObjectID) Source

Get one object from its ID.

getTypeName :: GraphUsableMonad m => Object -> GraphStorageT m Text Source

Get the type name for a given low level Object.

listProperties :: GraphUsableMonad m => PropertyID -> GraphStorageT m (Map Text [PropertyValue]) Source

(Internal) Build a property map by reading the property list.

deleteRelation :: GraphUsableMonad m => RelationID -> GraphStorageT m () Source

Delete a relation from the DB.

deleteRelation' Source

Arguments

:: GraphUsableMonad m 
=> RelationID 
-> Bool

Should we clean the origin object relation list?

-> Bool

Should we clean the target object relation list?

-> GraphStorageT m [RelationID]

The next ids in the chain we didn't clean

(Internal) Delete a relation from the DB.

deleteProperties :: GraphUsableMonad m => Handles -> PropertyID -> GraphStorageT m () Source

(Internal) Delete all properties in the list

objectType :: GraphUsableMonad m => Text -> GraphStorageT m ObjectTypeID Source

(Internal) retrieve an object type id from its name (creating it if need be)

propertyType :: GraphUsableMonad m => (Text, DataType) -> GraphStorageT m PropertyTypeID Source

(Internal) retrieve a property type id from its name and data type (creating it if need be)

relationType :: GraphUsableMonad m => Text -> GraphStorageT m RelationTypeID Source

(Internal) retrieve an relation type id from its name (creating it if need be)

fetchType :: (GraphUsableMonad m, Ord k, GraphIdSerializable i v) => (Model -> Lookup i k) -> (Model -> Lookup i k -> Model) -> k -> Text -> (PropertyID -> v) -> GraphStorageT m i Source

(Internal) Fetch type helper

addIndex :: GraphUsableMonad m => IndexInfo -> GraphStorageT m (Trie Int16 ObjectID) Source

Add an index to be automatically managed.

addIndex' :: GraphUsableMonad m => Bool -> IndexInfo -> GraphStorageT m (Trie Int16 ObjectID) Source

Add an index to be automatically managed.

createIndex :: forall k v m. (Binary k, Binary v, Default k, Default v, GraphUsableMonad m) => Text -> GraphStorageT m (Trie k v) Source

(Internal) Create an index.

indexMap :: GraphUsableMonad m => GraphObject a -> GraphStorageT m (Map Text [Trie Int16 ObjectID]) Source

Get the indices to update, per property.

isIndexApplicable :: IndexInfo -> Text -> Bool Source

Is the given index applicable to the given object type?