Skip to content

Commit

Permalink
version 0.0.0.17: more documentation for graph (#24)
Browse files Browse the repository at this point in the history
* version 0.0.0.17: more documentation for graph

* Fix haddock formatting

* Fix small mistakes

* Add examples to haddocks
  • Loading branch information
maksbotan authored and ozzzzz committed May 23, 2019
1 parent 64abb0d commit 3641cea
Show file tree
Hide file tree
Showing 10 changed files with 252 additions and 70 deletions.
4 changes: 4 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,10 @@ and this project adheres to [Semantic Versioning](http://semver.org/spec/v2.0.0.

## [Unreleased]

## [0.0.0.17] - 2019-05-09
### Changed
- Expanded documentation for `Database.Bolt.Extras.Graph`.

## [0.0.0.16] - 2019-02-01
### Changed
- Optimized query, easy way to extract entities from result graph.
Expand Down
2 changes: 1 addition & 1 deletion hasbolt-extras.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: hasbolt-extras
version: 0.0.0.16
version: 0.0.0.17
synopsis: Extras for hasbolt library
description: Extras for hasbolt library
homepage: https://github.com/biocad/hasbolt-extras#readme
Expand Down
136 changes: 131 additions & 5 deletions src/Database/Bolt/Extras/Graph.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,136 @@
{-|
This module defines everything needed to make template graph requests to Neo4j.
There are two types of queries that you can run: queries that return something from the
database (Get) and queries that save new data to it (Put). Both types are abstracted via type class
'GraphQuery'. Most of the time you will need only its 'makeRequest' method.
Get and Put queries are simply two instances of 'GraphQuery', differentiated by empty data
types 'GetRequest' and 'PutRequest'. This means that you will have to use @TypeApplications@
to call 'GraphQuery' methods, like this:
> makeRequest @GetRequest ...
All queries are built from simple templates that can be customized with endomorphisms
(things of type @a -> a@, like the Builder pattern in OOP).
Endomorphisms can be conveniently applied using 'Data.Function.&' operator.
A complete example of running Get and Put queries can be found in "@example/Main.hs@" file in this
repository.
-}

module Database.Bolt.Extras.Graph
(
module Database.Bolt.Extras.Graph.Internal.AbstractGraph
, module Database.Bolt.Extras.Graph.Internal.Class
, module Database.Bolt.Extras.Graph.Internal.Get
, module Database.Bolt.Extras.Graph.Internal.GraphQuery
, module Database.Bolt.Extras.Graph.Internal.Put
-- * Graph template construction
-- | Both query types require a 'Graph' type. Preffered way to create a variable of this type
-- is to start with 'emptyGraph' and add required nodes and relations with 'addNode' and
-- 'addRelation' function.
--
-- For example (using @Text@ as node data for simplicity):
--
-- > queryG :: Graph Text Text Text
-- > queryG = emptyGraph
-- > & addNode "a" "node a"
-- > & addNode "b" "node b
-- > & addRelation "a" "b" "relation a -> b"
--
Graph(..), vertices, relations,
emptyGraph, addNode, addRelation,

-- * Get queries
-- | Get queries are represented by 'GraphGetRequest' type - it is a 'Graph' filled with templates
-- for nodes and relations: 'NodeGetter' and 'RelGetter'.
--
-- To make a query, you need to build a template of graph that you want to find in the DB.
-- For that, start with empty nodes and relations like 'defaultNodeReturn' and 'defaultRelReturn'.
-- Customize them with endomorphisms in 'GetterLike' class and combine into template
-- graph 'Graph' using 'emptyGraph', 'addNode' and 'addRelation'.
--
-- Typically, a node template is constructed like this:
--
-- > defaultNodeReturn
-- > & withLabelQ ''NodeType
-- > & withBoltId nodeId
-- > & withReturn allProps
--
-- The result of running Get query will be represented as a 'Graph' as well, with 'GraphGetResponse'
-- alias. You can then use convenient functions like 'extractNode' and 'extractRelation' to get
-- your datatypes (that are instances of 'Database.Bolt.Extras.NodeLike'
-- or 'Database.Bolt.Extras.URelationshipLike') from the result.

-- ** Getter types
GetRequest,
GetterLike(..),
NodeGetter(..), RelGetter(..),
GraphGetRequest,

-- ** Default getters
defaultNode, defaultNodeReturn, defaultNodeNotReturn,
defaultRel, defaultRelReturn, defaultRelNotReturn,
allProps,

-- ** Result types
NodeResult(..), RelResult(..),
GraphGetResponse,

-- ** Extracting result
-- | These functions are for extracting nodes and relations in various formats.
-- If an entity does not exist in given 'GraphGetResponse' or is of invalid type,
-- an @error@ will be thrown.
--
-- For example, assume you have this query:
--
-- @
-- queryG :: GraphGetRequest
-- queryG = emptyGraph
-- & addNode "exNode"
-- (defaultNodeReturn
-- & withLabelQ ''ExampleNode
-- & withProp ("exampleFieldT", T "A")
-- & withReturn allProps
-- )
-- @
--
-- And run it:
--
-- > result <- makeRequest @GetRequest [] queryG
--
-- Then you can get @ExampleNode@ value from the result
--
-- > let nodes = map extractNode "exNode" result :: [ExampleNode]
--
-- You can also just ask for an id of node:
--
-- > let nodeIds = map extractNodeId "exNode" result
--
-- Or, if you did not use @withReturn allProps@, you can use 'extractNodeAeson' to get raw
-- 'NodeResult' value and inspect its properties.
extractNode, extractRelation,
extractNodeId, extractRelationId,
extractNodeAeson, extractRelationAeson,
mergeGraphs,

-- * Put queries
-- | Put queries are represented with 'GraphPutRequest' - a 'Graph' of 'PutNode' and 'PutRelationship'.
-- Build your graph the same way as with Get queryб representing new nodes and relations as
-- 'PutNode' and 'PutRelationship'. The query graph may also describe existing
-- nodes and relations, for example if you need to find a specific node in graph and attach a new one to
-- it, or update an existing node with new data.
--
-- Result of Put query will be graph with Neo4j ids of inserted data.
PutRequest,
PutNode(..), PutRelationship(..),
GraphPutRequest, GraphPutResponse,

-- * Internal machinery for forming Cypher queries
GraphQuery(..),
Requestable(..), Returnable(..), Extractable(..),
NodeName, relationName,
requestGetters, requestPut,

(#),
) where

import Database.Bolt.Extras.Graph.Internal.AbstractGraph
Expand Down
36 changes: 25 additions & 11 deletions src/Database/Bolt/Extras/Graph/Internal/AbstractGraph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,32 +21,46 @@ import Data.Text (Text)
import GHC.Generics (Generic)
import Text.Printf (printf)

-- | '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.
-- | Representation of Graph that is used for requests and responses. It is parameterized by three types:
--
-- * @n@: type of node names
-- * @a@: type of nodes
-- * @b@: type of relations
--
-- Relations are described by a pair of nodes - start and end.
--
-- There are lenses defined for 'Graph': 'vertices' and 'relations'.
--
data Graph n a b = Graph { _vertices :: Map n a
, _relations :: Map (n, n) b
} deriving (Show, Generic)

makeLenses ''Graph

-- | Creates empty graph.
-- | An empty graph.
--
emptyGraph :: Ord n => Graph n a b
emptyGraph = Graph mempty mempty

-- | Adds node to graph by it's @name@ and @node@ content.
-- If graph already contains vertex with given @name@, error will be thrown.
-- | Adds node to graph by its name and data.
-- If graph already contains node with given @name@, @error@ will be thrown.
--
addNode :: (Show n, Ord n) => n -> a -> Graph n a b -> Graph n a b
addNode :: (Show n, Ord n)
=> n -- ^ Name of the node
-> a -- ^ Node data
-> Graph n a b -> Graph n a b
addNode name node graph = if name `notMember` _vertices graph
then over vertices (insert name node) graph
else error . printf "vertex with name %s key already exists" . show $ name

-- | 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.
-- | Adds relation to graph by @startName@ of node, @endName@ of node, and @rel@ with relation data.
-- If graph already contains relation with given @(startName, endName)@, @error@ will be thrown.
--
addRelation :: (Show n, Ord n) => n -> n -> b -> Graph n a b -> Graph n a b
addRelation :: (Show n, Ord n)
=> n -- ^ Name of start node
-> n -- ^ Name of end node
-> b -- ^ Relation data
-> Graph n a b -> Graph n a b
addRelation startName endName rel graph = if (startName, endName) `notMember` _relations graph
then over relations (insert (startName, endName) rel) graph
else error $ printf "relation with names (%s, %s) already exists" (show startName) (show endName)
Expand All @@ -55,7 +69,7 @@ addRelation startName endName rel graph = if (startName, endName) `notMember` _r
--
type NodeName = Text

-- | Creates relationship name from the names of its start and end nodes
-- in the way `<startNodeName>0<endNodeName>`.
-- | Build relationship name from the names of its start and end nodes
-- like @[startNodeName]0[endNodeName]@.
relationName :: (NodeName, NodeName) -> Text
relationName (st, en) = st <> "0" <> en
6 changes: 3 additions & 3 deletions src/Database/Bolt/Extras/Graph/Internal/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,13 +9,13 @@ import Control.Monad.IO.Class (MonadIO)
import Data.Text (Text)
import Database.Bolt (BoltActionT, Record)

-- | Class describes entity, which can be requested.
-- | Entity which can be requested from Neo4j in @MATCH@ operator.
--
class Requestable a where
-- | How to convert entity to Cypher.
request :: a -> Text

-- | Class describes entity, which can be returned.
-- | Entity which can be returned from Neo4j in @RETURN@ operator.
--
class Returnable a where
-- | If the entity should be returned.
Expand All @@ -24,7 +24,7 @@ class Returnable a where
-- | How to return entity in the Cypher.
return' :: a -> Text

-- | Class describes entity, which can be extracted from records by name.
-- | Entity which can be extracted from 'Record' by its name.
--
class Extractable a where
extract :: MonadIO m => Text -> [Record] -> BoltActionT m [a]
45 changes: 31 additions & 14 deletions src/Database/Bolt/Extras/Graph/Internal/Get.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,54 +99,64 @@ import Text.Printf (printf)

-- | Helper to find 'Node's.
--
data NodeGetter = NodeGetter { ngboltId :: Maybe BoltId -- ^ known boltId
data NodeGetter = NodeGetter { ngboltId :: Maybe BoltId -- ^ known 'BoltId'
, ngLabels :: [Label] -- ^ known labels
, ngProps :: Map Text B.Value -- ^ known properties
, ngReturnProps :: [Text] -- ^ names of properties to return
, ngIsReturned :: Bool -- ^ whether return this node or not
, ngIsReturned :: Bool -- ^ whether to return this node or not
}
deriving (Show, Eq)

-- | Helper to find 'URelationship's.
--
data RelGetter = RelGetter { rgboltId :: Maybe BoltId -- ^ known boltId
data RelGetter = RelGetter { rgboltId :: Maybe BoltId -- ^ known 'BoltId'
, rgLabel :: Maybe Label -- ^ known labels
, rgProps :: Map Text B.Value -- ^ known properties
, rgReturnProps :: [Text] -- ^ names of properties to return
, rgIsReturned :: Bool -- ^ whether return this relation or not
, rgIsReturned :: Bool -- ^ whether to return this relation or not
}
deriving (Show, Eq)

-- | A synonym for '&'. Kept for historical reasons.
(#) :: a -> (a -> b) -> b
(#) = (&)

defaultNode :: Bool -> NodeGetter
-- | 'NodeGetter' that matches any node.
defaultNode :: Bool -- ^ Whether to return the node
-> NodeGetter
defaultNode = NodeGetter Nothing [] (fromList []) []

defaultRel :: Bool -> RelGetter
-- | 'RelGetter' that matches any relation.
defaultRel :: Bool -- ^ Whether to return the relation
-> RelGetter
defaultRel = RelGetter Nothing Nothing (fromList []) []

-- | 'NodeGetter' that matches any node and returns it.
defaultNodeReturn :: NodeGetter
defaultNodeReturn = defaultNode True

-- | 'NodeGetter' that matches any node and does not return it.
defaultNodeNotReturn :: NodeGetter
defaultNodeNotReturn = defaultNode False

-- | 'RelGetter' that matches any relation and returns it.
defaultRelReturn :: RelGetter
defaultRelReturn = defaultRel True


-- | 'RelGetter' that matches any relation and does not return it.
defaultRelNotReturn :: RelGetter
defaultRelNotReturn = defaultRel False

-- | Helper to work with Getters.
-- | Endomorphisms to set up 'NodeGetter' and 'RelGetter'.
--
class GetterLike a where
withBoltId :: BoltId -> a -> a -- ^ set known boltId
withBoltId :: BoltId -> a -> a -- ^ set known 'BoltId'
withLabel :: Label -> a -> a -- ^ set known label
withLabelQ :: Name -> a -> a -- ^ set known label as 'Name'
withLabelQ :: Name -> a -> a -- ^ set known label as TemplateHaskell 'Name'
withProp :: (Text, B.Value) -> a -> a -- ^ add known property
withReturn :: [Text] -> a -> a -- ^ add list of properties to return
isReturned :: a -> a -- ^ set that current node should be returned
isReturned :: a -> a -- ^ set that entity should be returned

instance GetterLike NodeGetter where
withBoltId boltId ng = ng { ngboltId = Just boltId }
Expand Down Expand Up @@ -198,6 +208,7 @@ instance Returnable ((NodeName, NodeName), RelGetter) where
} as $name
|]

-- | Return all properties of a node or relation. To be used with 'withReturn'.
allProps :: [Text]
allProps = ["*"]

Expand Down Expand Up @@ -227,15 +238,15 @@ requestGetters ngs rgs = ("MATCH " <> intercalate ", " (fmap request rgs ++ fmap
-- RESULT --
----------------------------------------------------------

-- | Result for node in the Aeson like format.
-- | Result for node where properties are represented as @aeson@ 'A.Value'.
--
data NodeResult = NodeResult { nresId :: BoltId
, nresLabels :: [Label]
, nresProps :: Map Text A.Value
}
deriving (Show, Eq, Generic)

-- | Result for relationship in the Aeson like format.
-- | Result for relation where properties are represented as @aeson@ 'A.Value'.
--
data RelResult = RelResult { rresId :: BoltId
, rresLabel :: Label
Expand Down Expand Up @@ -290,35 +301,41 @@ instance URelationLike RelResult where
-- GRAPH --
----------------------------------------------------------

-- | The combinations of 'Getter's to load graph from the database.
-- | The combinations of getters to load graph from the database.
--
type GraphGetRequest = Graph NodeName NodeGetter RelGetter

-- | The graph of 'Node's and 'URelationship's which we got from the database using 'GraphGetRequest'.
--
type GraphGetResponse = Graph NodeName NodeResult RelResult

-- | Some helpers to extract entities from the result graph.

-- | Extract a node by its name from 'GraphGetResponse' and convert it to user type
-- with 'fromNode'.
extractNode :: NodeLike a => NodeName -> GraphGetResponse -> a
extractNode var graph = graph ^. vertices . at var . non (errorForNode var) . to (fromNode . toNode)

-- | Extract a relation by name of it start and end nodes and convert to user type with 'fromURelation'.
extractRelation :: URelationLike a => NodeName -> NodeName -> GraphGetResponse -> a
extractRelation stVar enVar graph = graph ^. relations . at (stVar, enVar)
. non (errorForRelation stVar enVar)
. to (fromURelation . toURelation)

-- | Extract just node's 'BoltId'.
extractNodeId :: NodeName -> GraphGetResponse -> BoltId
extractNodeId var graph = graph ^. vertices . at var . non (errorForNode var) . to nresId

-- | Extract just relation's 'BoltId'.
extractRelationId :: NodeName -> NodeName -> GraphGetResponse -> BoltId
extractRelationId stVar enVar graph = graph ^. relations . at (stVar, enVar)
. non (errorForRelation stVar enVar)
. to rresId

-- | Extract 'NodeResult'.
extractNodeAeson :: NodeName -> GraphGetResponse -> NodeResult
extractNodeAeson var graph = graph ^. vertices . at var . non (errorForNode var)

-- | Extract 'RelResult'.
extractRelationAeson :: NodeName -> NodeName -> GraphGetResponse -> RelResult
extractRelationAeson stVar enVar graph = graph ^. relations . at (stVar, enVar)
. non (errorForRelation stVar enVar)
Expand Down
Loading

0 comments on commit 3641cea

Please sign in to comment.