Copyright | (c) 2014, Antoni Silvestre |
---|---|
License | MIT |
Maintainer | Antoni Silvestre <[email protected]> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Database.Neo4j
Contents
Description
Library to interact with the Neo4j REST API.
- data Connection
- type Hostname = ByteString
- type Port = Int
- type Credentials = (Username, Password)
- newConnection :: Hostname -> Port -> IO Connection
- withConnection :: Hostname -> Port -> Neo4j a -> IO a
- newAuthConnection :: Hostname -> Port -> Credentials -> IO Connection
- withAuthConnection :: Hostname -> Port -> Credentials -> Neo4j a -> IO a
- newSecureConnection :: Hostname -> Port -> IO Connection
- withSecureConnection :: Hostname -> Port -> Neo4j a -> IO a
- newSecureAuthConnection :: Hostname -> Port -> Credentials -> IO Connection
- withSecureAuthConnection :: Hostname -> Port -> Credentials -> Neo4j a -> IO a
- newtype Neo4j a = Neo4j {
- runNeo4j :: Connection -> IO a
- data Val
- data PropertyValue
- = ValueProperty Val
- | ArrayProperty [Val]
- newval :: PropertyValueConstructor a => a -> PropertyValue
- (|:) :: PropertyValueConstructor a => Text -> a -> (Text, PropertyValue)
- type Properties = HashMap Text PropertyValue
- emptyProperties :: HashMap Text PropertyValue
- getProperties :: Entity a => a -> Neo4j Properties
- getProperty :: Entity a => a -> Text -> Neo4j (Maybe PropertyValue)
- setProperties :: Entity a => a -> Properties -> Neo4j a
- setProperty :: Entity a => a -> Text -> PropertyValue -> Neo4j a
- deleteProperties :: Entity a => a -> Neo4j a
- deleteProperty :: Entity a => a -> Text -> Neo4j a
- data Node
- getNodeProperties :: Node -> Properties
- createNode :: Properties -> Neo4j Node
- getNode :: NodeIdentifier a => a -> Neo4j (Maybe Node)
- deleteNode :: NodeIdentifier a => a -> Neo4j ()
- nodeId :: Node -> ByteString
- nodePath :: Node -> NodePath
- runNodeIdentifier :: NodeIdentifier a => a -> ByteString
- class NodeIdentifier a where
- newtype NodePath = NodePath {
- runNodePath :: Text
- data Relationship
- data Direction
- type RelationshipType = Text
- createRelationship :: RelationshipType -> Properties -> Node -> Node -> Neo4j Relationship
- getRelationship :: RelIdentifier a => a -> Neo4j (Maybe Relationship)
- deleteRelationship :: RelIdentifier a => a -> Neo4j ()
- getRelationships :: Node -> Direction -> [RelationshipType] -> Neo4j [Relationship]
- relId :: Relationship -> ByteString
- relPath :: Relationship -> RelPath
- allRelationshipTypes :: Neo4j [RelationshipType]
- getRelProperties :: Relationship -> Properties
- getRelType :: Relationship -> RelationshipType
- runRelIdentifier :: RelIdentifier a => a -> ByteString
- getRelationshipFrom :: Relationship -> Neo4j Node
- getRelationshipTo :: Relationship -> Neo4j Node
- class RelIdentifier a where
- newtype RelPath = RelPath {
- runRelPath :: Text
- class EntityIdentifier a where
- type Label = Text
- allLabels :: Neo4j [Label]
- getLabels :: Node -> Neo4j [Label]
- getNodesByLabelAndProperty :: Label -> Maybe (Text, PropertyValue) -> Neo4j [Node]
- addLabels :: [Label] -> Node -> Neo4j ()
- changeLabels :: [Label] -> Node -> Neo4j ()
- removeLabel :: Label -> Node -> Neo4j ()
- data Index = Index {
- indexLabel :: Label
- indexProperties :: [Text]
- createIndex :: Label -> Text -> Neo4j Index
- getIndexes :: Label -> Neo4j [Index]
- dropIndex :: Label -> Text -> Neo4j ()
- data Neo4jException
- getDatabaseVersion :: Neo4j Neo4jVersion
How to use this library
In order to start issuing commands to neo4j you must establish a connection, in order to do that you can use
the function withConnection
:
withConnection "127.0.0.1" 7474 $ do neo <- createNode M.empty cypher <- createNode M.empty r <- createRelationship "KNOWS" M.empty neo cypher ...
Also most calls have a batch analogue version, with batch mode you can issue several commands to Neo4j at once. In order to issue batches you must use the Database.Neo4j.Batch monad, parameters in batch mode can be actual entities already obtained by issuing regular commands or previous batch commands, or even batch futures, that is you can refer to entities created in the same batch, for instance:
withConnection "127.0.0.1" 7474 $ do g <- B.runBatch $ do neo <- B.createNode M.empty cypher <- B.createNode M.empty B.createRelationship "KNOWS" M.empty neo cypher ...
As you can see this example does the same thing the previous one does but it will be more efficient as it will be translated into only one request to the database.
Batch commands return a Database.Neo4j.Graph object that holds all the information about relationships, nodes and their labels that can be inferred from running a batch command.
Another example with batches would be for instance remove all the nodes in a Database.Neo4j.Graph object
withConnection "127.0.0.1" 7474 $ do ... B.runBatch $ mapM_ B.deleteNode (G.getNodes gp)
For more information about batch commands and graph objects you can refer to their Database.Neo4j.Batch and Database.Neo4j.Graph modules.
Properties are hashmaps with key Text
and values a custom type called PropertyValue
.
This custom type tries to use Haskell's type system to match property values to what Neo4j expects, we only allow
Int64
, Double
, Bool
and Text
like values and one-level arrays of these.
The only restriction we cannot guarantee with these types is that arrays of values must be of the same type.
In order to create a PropertyValue
from a literal or a value of one of the allowed types you can use the newval
function or the operator |:
to create pairs of key values:
import qualified Data.HashMap.Lazy as M myval = newval False someProperties = M.fromList ["mytext" |: ("mytext" :: T.Text), "textarrayprop" |: ["a" :: T.Text, "", "adeu"], "int" |: (-12 :: Int64), "intarray" |: [1 :: Int64, 2], "double" |: (-12.23 :: Double), "doublearray" |: [0.1, -12.23 :: Double], "bool" |: False, "aboolproparray" |: [False, True] ]
When unexpected errors occur a Neo4jException
will be raised, sometimes with a specific exception value like for
instance Neo4jNoEntityException
, or more generic ones like Neo4jHttpException
or Neo4jParseException
if the server returns something totally unexpected. (I'm sure there's still work to do here preparing the code
to return more specific exceptions for known scenarios)
About Cypher support for now we allow sending queries with parameters, the result is a collection of column headers and JSON data values, the Graph object has the function addCypher that tries to find nodes and relationships in a cypher query result and insert them in a Database.Neo4j.Graph object
import qualified Database.Neo4j.Cypher as C withConnection host port $ do ... -- Run a cypher query with parameters res <- C.cypher "CREATE (n:Person { name : {name} }) RETURN n" M.fromList [("name", C.newparam ("Pep" :: T.Text))] -- Get all nodes and relationships that this query returned and insert them in a Graph object let graph = G.addCypher (C.fromSuccess res) G.empty -- Get the column headers let columnHeaders = C.cols $ C.fromSuccess res -- Get the rows of JSON values received let values = C.vals $ C.fromSuccess res
Connection handling objects
data Connection Source #
Type for a connection
type Hostname = ByteString Source #
type Credentials = (Username, Password) Source #
newConnection :: Hostname -> Port -> IO Connection Source #
Create a new connection that can be manually closed with runResourceT
withConnection :: Hostname -> Port -> Neo4j a -> IO a Source #
Run a set of Neo4j commands in a single connection
newAuthConnection :: Hostname -> Port -> Credentials -> IO Connection Source #
Create a new connection that can be manually closed with runResourceT using provided credentials for basic auth
withAuthConnection :: Hostname -> Port -> Credentials -> Neo4j a -> IO a Source #
Run a set of Neo4j commands in a single connection using provided credentials for basic auth
newSecureConnection :: Hostname -> Port -> IO Connection Source #
Create a new https connection that can be manually closed with runResourceT
withSecureConnection :: Hostname -> Port -> Neo4j a -> IO a Source #
Run a set of Neo4j commands in a single https connection
newSecureAuthConnection :: Hostname -> Port -> Credentials -> IO Connection Source #
Create a new https connection that can be manually closed with runResourceT using provided credentials for basic auth
withSecureAuthConnection :: Hostname -> Port -> Credentials -> Neo4j a -> IO a Source #
Run a set of Neo4j commands in a single https connection using provided credentials for basic auth
Main monadic type to handle sequences of commands to Neo4j
Neo4j monadic type to be able to sequence neo4j commands in a connection
Constructors
Neo4j | |
Fields
|
Constructing and managing node/relationship properties
Type for a single value of a Neo4j property
data PropertyValue Source #
Wrapping type for a Neo4j single property or array of properties Using these types allows type checking for only correct properties that is int, double, string, boolean and single typed arrays of these, also nulls are not allowed
Constructors
ValueProperty Val | |
ArrayProperty [Val] |
Instances
Eq PropertyValue Source # | |
Show PropertyValue Source # | |
FromJSON PropertyValue Source # | JSON to property values |
ToJSON PropertyValue Source # | Specifying how to convert property values to JSON |
newval :: PropertyValueConstructor a => a -> PropertyValue Source #
(|:) :: PropertyValueConstructor a => Text -> a -> (Text, PropertyValue) Source #
This operator allows easy construction of property value types from literals
type Properties = HashMap Text PropertyValue Source #
We use hashmaps to represent Neo4j properties
emptyProperties :: HashMap Text PropertyValue Source #
Shortcut for emtpy properties
getProperties :: Entity a => a -> Neo4j Properties Source #
Retrieve relationship/node properties from the DB, if the entity is not present it will raise an exception If the entity doesn't exist it will raise a Neo4jNoEntity exception
getProperty :: Entity a => a -> Text -> Neo4j (Maybe PropertyValue) Source #
Get a relationship/node property If the 404 is because the parent entity doesn't exist we'll raise the corresponding Neo4jNoEntity If the 404 is because there is no property just return Nothing
setProperties :: Entity a => a -> Properties -> Neo4j a Source #
Set all relationship/node properties If the entity doesn't exist it will raise a Neo4jNoEntity exception
setProperty :: Entity a => a -> Text -> PropertyValue -> Neo4j a Source #
Set a relationship/node property If the entity doesn't exist it will raise a Neo4jNoEntity exception
deleteProperties :: Entity a => a -> Neo4j a Source #
Delete all relationship/node properties If the entity doesn't exist it will raise a Neo4jNoEntity exception
deleteProperty :: Entity a => a -> Text -> Neo4j a Source #
Delete a relationship/node property If the entity doesn't exist it will raise a Neo4jNoEntity exception
Managing nodes
Representation of a Neo4j node, has a location URI and a set of properties
Instances
Eq Node Source # | |
Ord Node Source # | |
Show Node Source # | |
FromJSON Node Source # | JSON to Node |
FromJSON FullPath # | How to decodify an IdPath from JSON |
EntityIdentifier Node Source # | |
NodeIdentifier Node Source # | |
Entity Node Source # | |
NodeBatchIdentifier Node Source # | |
BatchEntity Node Source # | |
NodeBatchIdentifier (BatchFuture Node) Source # | |
BatchEntity (BatchFuture Node) Source # | |
getNodeProperties :: Node -> Properties Source #
Get the properties of a node
createNode :: Properties -> Neo4j Node Source #
Create a new node with a set of properties
getNode :: NodeIdentifier a => a -> Neo4j (Maybe Node) Source #
Refresh a node entity with the contents in the DB
deleteNode :: NodeIdentifier a => a -> Neo4j () Source #
Delete a node, if the node has relationships it will raise a Neo4jNonOrphanNodeDeletion
nodeId :: Node -> ByteString Source #
Get the ID of a node
runNodeIdentifier :: NodeIdentifier a => a -> ByteString Source #
class NodeIdentifier a where Source #
Minimal complete definition
Methods
getNodePath :: a -> NodePath Source #
Constructors
NodePath | |
Fields
|
Instances
Eq NodePath Source # | |
Ord NodePath Source # | |
Show NodePath Source # | |
Generic NodePath Source # | |
Hashable NodePath Source # | |
FromJSON IdPath # | How to decodify an IdPath from JSON |
EntityIdentifier NodePath Source # | |
NodeIdentifier NodePath Source # | |
NodeBatchIdentifier NodePath Source # | |
BatchEntity NodePath Source # | |
type Rep NodePath Source # | |
Managing relationships
data Relationship Source #
Type for a Neo4j relationship, has a location URI, a relationship type, a starting node and a destination node
Instances
Eq Relationship Source # | |
Ord Relationship Source # | |
Show Relationship Source # | |
FromJSON Relationship Source # | JSON to Relationship |
FromJSON FullPath # | How to decodify an IdPath from JSON |
EntityIdentifier Relationship Source # | |
RelIdentifier Relationship Source # | |
Entity Relationship Source # | |
RelBatchIdentifier Relationship Source # | |
BatchEntity Relationship Source # | |
RelBatchIdentifier (BatchFuture Relationship) Source # | |
BatchEntity (BatchFuture Relationship) Source # | |
Relationship direction
type RelationshipType = Text Source #
Type for a relationship type description
createRelationship :: RelationshipType -> Properties -> Node -> Node -> Neo4j Relationship Source #
Create a new relationship with a type and a set of properties
getRelationship :: RelIdentifier a => a -> Neo4j (Maybe Relationship) Source #
Refresh a relationship entity with the contents in the DB
deleteRelationship :: RelIdentifier a => a -> Neo4j () Source #
Delete a relationship
getRelationships :: Node -> Direction -> [RelationshipType] -> Neo4j [Relationship] Source #
Get all relationships for a node, if the node has disappeared it will raise an exception
relId :: Relationship -> ByteString Source #
Get the ID of a relationship
relPath :: Relationship -> RelPath Source #
allRelationshipTypes :: Neo4j [RelationshipType] Source #
Gets all relationship types in the DB
getRelProperties :: Relationship -> Properties Source #
Get the properties of a relationship
getRelType :: Relationship -> RelationshipType Source #
Get the type of a relationship
runRelIdentifier :: RelIdentifier a => a -> ByteString Source #
getRelationshipFrom :: Relationship -> Neo4j Node Source #
Get the "node from" from a relationship from the DB | Raises Neo4jNoEntityException if the node (and thus the relationship) does not exist any more
getRelationshipTo :: Relationship -> Neo4j Node Source #
Get the "node to" from a relationship from the DB | Raises Neo4jNoEntityException if the node (and thus the relationship) does not exist any more
class RelIdentifier a where Source #
Minimal complete definition
Methods
getRelPath :: a -> RelPath Source #
Constructors
RelPath | |
Fields
|
Instances
Eq RelPath Source # | |
Ord RelPath Source # | |
Show RelPath Source # | |
Generic RelPath Source # | |
Hashable RelPath Source # | |
FromJSON IdPath # | How to decodify an IdPath from JSON |
EntityIdentifier RelPath Source # | |
RelIdentifier RelPath Source # | |
RelBatchIdentifier RelPath Source # | |
BatchEntity RelPath Source # | |
type Rep RelPath Source # | |
Managing labels and getting nodes by label
class EntityIdentifier a where Source #
Minimal complete definition
Methods
getEntityPath :: a -> EntityPath Source #
getLabels :: Node -> Neo4j [Label] Source #
Retrieve all labels for a node, if the node doesn't exist already it will raise an exception | Raises Neo4jNoEntityException if the node doesn't exist
getNodesByLabelAndProperty :: Label -> Maybe (Text, PropertyValue) -> Neo4j [Node] Source #
Get all nodes using a label and a property
addLabels :: [Label] -> Node -> Neo4j () Source #
Add labels to a node | Raises Neo4jNoEntityException if the node doesn't exist
changeLabels :: [Label] -> Node -> Neo4j () Source #
Change node labels | Raises Neo4jNoEntityException if the node doesn't exist
removeLabel :: Label -> Node -> Neo4j () Source #
Remove a label for a node | Raises Neo4jNoEntityException if the node doesn't exist
Indexes
Type for an index
Constructors
Index | |
Fields
|
Exceptions
data Neo4jException Source #
Exceptions this library can raise
Constructors
Instances