hasbolt-extras-0.0.0.15: Extras for hasbolt library

Safe HaskellNone
LanguageHaskell2010

Database.Bolt.Extras.Graph

Contents

Synopsis

Documentation

data Graph n a b Source #

Graph contains vertices, that are parameterized by some type n, and relations, that parameterized by pair of type n. This pair represents vertices, that are connected with this relation.

Constructors

Graph 

Fields

Instances
(Show n, Show a, Show b) => Show (Graph n a b) Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.AbstractGraph

Methods

showsPrec :: Int -> Graph n a b -> ShowS #

show :: Graph n a b -> String #

showList :: [Graph n a b] -> ShowS #

Generic (Graph n a b) Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.AbstractGraph

Associated Types

type Rep (Graph n a b) :: Type -> Type #

Methods

from :: Graph n a b -> Rep (Graph n a b) x #

to :: Rep (Graph n a b) x -> Graph n a b #

type Rep (Graph n a b) Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.AbstractGraph

type Rep (Graph n a b) = D1 (MetaData "Graph" "Database.Bolt.Extras.Graph.Internal.AbstractGraph" "hasbolt-extras-0.0.0.15-HDWUrnwpJjRBwu6nqvxe91" False) (C1 (MetaCons "Graph" PrefixI True) (S1 (MetaSel (Just "_vertices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map n a)) :*: S1 (MetaSel (Just "_relations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map (n, n) b))))

vertices :: forall n a b a. Lens (Graph n a b) (Graph n a b) (Map n a) (Map n a) Source #

relations :: forall n a b b. Lens (Graph n a b) (Graph n a b) (Map (n, n) b) (Map (n, n) b) Source #

emptyGraph :: Ord n => Graph n a b Source #

Creates empty graph.

addNode :: (Show n, Ord n) => n -> a -> Graph n a b -> Graph n a b Source #

Adds node to graph by it's name and node content. If graph already contains vertex with given name, error will be thrown.

addRelation :: (Show n, Ord n) => n -> n -> b -> Graph n a b -> Graph n a b Source #

Adds relation to graph by startName of vertex, endName of vertex, and rel with relation content. If graph already contains relation with given (startName, endName), error will be thrown.

type NodeName = Text Source #

Alias for text node name.

relationName :: (NodeName, NodeName) -> Text Source #

Creates relationship name from the names of its start and end nodes in the way `<startNodeName>0<endNodeName>`.

class Requestable a where Source #

Class describes entity, which can be requested.

Methods

request :: a -> Text Source #

How to convert entity to Cypher.

class Returnable a where Source #

Class describes entity, which can be returned.

Methods

isReturned' :: a -> Bool Source #

If the entity should be returned.

return' :: a -> Text Source #

How to return entity in the Cypher.

class Extractable a where Source #

Class describes entity, which can be extracted from records by name.

Methods

extract :: MonadIO m => Text -> [Record] -> BoltActionT m [a] Source #

Types for requesting nodes and relationships

data NodeGetter Source #

Helper to find Nodes.

Constructors

NodeGetter 

Fields

data RelGetter Source #

Helper to find URelationships.

Constructors

RelGetter 

Fields

class GetterLike a where Source #

Helper to work with Getters.

Methods

withBoltId Source #

Arguments

:: BoltId 
-> a 
-> a

set known boltId

withLabel Source #

Arguments

:: Label 
-> a 
-> a

set known label

withLabelQ Source #

Arguments

:: Name 
-> a 
-> a

set known label as Name

withProp Source #

Arguments

:: (Text, Value) 
-> a 
-> a

add known property

withReturn Source #

Arguments

:: [Text] 
-> a 
-> a

add list of properties to return

isReturned Source #

Arguments

:: a 
-> a

set that current node should be returned

(#) :: a -> (a -> b) -> b Source #

requestGetters :: [(NodeName, NodeGetter)] -> [((NodeName, NodeName), RelGetter)] -> (Text, [Text]) Source #

Takes all node getters and relationship getters and write them to single query to request. Also return conditions on known boltId-s.

Types for extracting nodes and relationships

data NodeResult Source #

AESON FORMAT

Result for node in the Aeson like format.

Constructors

NodeResult 
Instances
Eq NodeResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

Show NodeResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

Generic NodeResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

Associated Types

type Rep NodeResult :: Type -> Type #

ToJSON NodeResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

FromJSON NodeResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

Extractable NodeResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

GetBoltId NodeResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

NodeLike NodeResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

type Rep NodeResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

type Rep NodeResult = D1 (MetaData "NodeResult" "Database.Bolt.Extras.Graph.Internal.Get" "hasbolt-extras-0.0.0.15-HDWUrnwpJjRBwu6nqvxe91" False) (C1 (MetaCons "NodeResult" PrefixI True) (S1 (MetaSel (Just "nresId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BoltId) :*: (S1 (MetaSel (Just "nresLabels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Label]) :*: S1 (MetaSel (Just "nresProps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Value)))))

data RelResult Source #

Result for relationship in the Aeson like format.

Constructors

RelResult 
Instances
Eq RelResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

Show RelResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

Generic RelResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

Associated Types

type Rep RelResult :: Type -> Type #

ToJSON RelResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

FromJSON RelResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

Extractable RelResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

Methods

extract :: MonadIO m => Text -> [Record] -> BoltActionT m [RelResult] Source #

GetBoltId RelResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

URelationLike RelResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

type Rep RelResult Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.Get

type Rep RelResult = D1 (MetaData "RelResult" "Database.Bolt.Extras.Graph.Internal.Get" "hasbolt-extras-0.0.0.15-HDWUrnwpJjRBwu6nqvxe91" False) (C1 (MetaCons "RelResult" PrefixI True) (S1 (MetaSel (Just "rresId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BoltId) :*: (S1 (MetaSel (Just "rresLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Label) :*: S1 (MetaSel (Just "rresProps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Value)))))

relationName :: (NodeName, NodeName) -> Text Source #

Creates relationship name from the names of its start and end nodes in the way `<startNodeName>0<endNodeName>`.

Graph types

type GraphGetRequest = Graph NodeName NodeGetter RelGetter Source #

The combinations of Getters to load graph from the database.

type GraphGetResponseA = Graph NodeName NodeResult RelResult Source #

The graph of Nodes and URelationships which we got from the database using GraphGetRequest, converted to the Aeson Value like.

type GraphGetResponseB = Graph NodeName Node URelationship Source #

The graph of Nodes and URelationships which we got from the database using GraphGetRequest, converted to the Bolt Value like.

class GraphQuery a where Source #

Type family used to perform requests to the Neo4j based on graphs.

Minimal complete definition

requestEntities

Associated Types

type NodeReq a :: * Source #

Type of entity, describing node for request.

type RelReq a :: * Source #

Type of entity, describing relationship for request.

type NodeRes a :: * Source #

Type of node entity, which will be extracted from result.

type RelRes a :: * Source #

Type of relationship entity, which will be extracted from result.

Methods

requestEntities :: (Requestable (NodeName, NodeReq a), Requestable ((NodeName, NodeName), RelReq a)) => [(NodeName, NodeReq a)] -> [((NodeName, NodeName), RelReq a)] -> (Text, [Text]) Source #

How to convert requestable entities to text in the query.

formQuery :: (Requestable (NodeName, NodeReq a), Requestable ((NodeName, NodeName), RelReq a), Returnable (NodeName, NodeReq a), Returnable ((NodeName, NodeName), RelReq a)) => [Text] -> Graph NodeName (NodeReq a) (RelReq a) -> Text Source #

Abstract function to form query for request.

extractGraphs :: (Extractable (NodeRes a), Extractable (RelRes a), MonadIO m) => [NodeName] -> [(NodeName, NodeName)] -> [Record] -> BoltActionT m [Graph NodeName (NodeRes a) (RelRes a)] Source #

Abstract function, which exctracts graph from records if nodes and relations can be extracted.

makeRequest :: (Requestable (NodeName, NodeReq a), Requestable ((NodeName, NodeName), RelReq a), Returnable (NodeName, NodeReq a), Returnable ((NodeName, NodeName), RelReq a), Extractable (NodeRes a), Extractable (RelRes a), MonadIO m) => [Text] -> Graph NodeName (NodeReq a) (RelReq a) -> BoltActionT m [Graph NodeName (NodeRes a) (RelRes a)] Source #

For given query graph, perform query and extract results graph.

Instances
GraphQuery PutRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

GraphQuery GetRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

GraphQuery GetRequestA Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

data GetRequestA Source #

Get request with result in Aeson format. Easy way to show result graphs.

Constructors

GetRequestA 
Instances
GraphQuery GetRequestA Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type NodeReq GetRequestA Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type RelReq GetRequestA Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type NodeRes GetRequestA Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type RelRes GetRequestA Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

data GetRequestB Source #

Get request with result in Bolt format. Easy way to extract results and convert them to another entities (using fromNode).

Constructors

GetRequestB 
Instances
GraphQuery GetRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type NodeReq GetRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type RelReq GetRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type NodeRes GetRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type RelRes GetRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

data PutRequestB Source #

Put request in Bolt format with BoltIds of uploaded entities as result.

Constructors

PutRequestB 
Instances
GraphQuery PutRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type NodeReq PutRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type RelReq PutRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type NodeRes PutRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

type RelRes PutRequestB Source # 
Instance details

Defined in Database.Bolt.Extras.Graph.Internal.GraphQuery

mergeGraphs :: GetBoltId a => [Graph NodeName a b] -> Graph NodeName a b Source #

Helper function to merge graphs of results, i.e. if you requested graph A->B->C and in the database there were two B entities connected to the same entity A and four C entities, connected to the same two entities B, cypher query will return four graphs, which satisfy this path, despite the fact that A was presented only once in the database and B was presented only two times in the database. This function will merge these four graphs in one and return nodes by node names with suffixes equal to their BoltId-s.

For example, if there were four graphs: nodes: [A (boltId = 0), B (boltId = 1), C (boltId = 3)], relations: [A -> B, B -> C], nodes: [A (boltId = 0), B (boltId = 1), C (boltId = 4)], relations: [A -> B, B -> C], nodes: [A (boltId = 0), B (boltId = 2), C (boltId = 5)], relations: [A -> B, B -> C], nodes: [A (boltId = 0), B (boltId = 2), C (boltId = 6)], relations: [A -> B, B -> C], this function will merge them into new graph: nodes: [A0 (boltId = 0), B1 (boltId = 1), B2 (boltId = 2), C3 (boltId = 3), C4 (boltId = 4), C5 (boltId = 5), C6 (boltId = 6)], relations: [A0 -> B1, A0 -> B2, B1 -> C3, B1 -> C4, B2 -> C5, B2 -> C6].

data PutNode Source #

BOLT FORMAT

PutNode is the wrapper for Node where we can specify if we want to merge or create it.

type GraphPutRequest = Graph NodeName PutNode PutRelationship Source #

The graph of Nodes with specified uploading type and URelationships.

type GraphPutResponse = Graph NodeName BoltId BoltId Source #

The graph of PutNodes corresponding to the nodes and relationships which we get after putting GraphPutRequest.

requestPut :: [(NodeName, PutNode)] -> [((NodeName, NodeName), PutRelationship)] -> (Text, [Text]) Source #

Takes all PutNodes and PutRelationships and write them to single query to request. Here WITH is used, because you cannot perform "match", "merge" or "create" at the same query.