haskell-neo4j-client-0.3.2.4: A Haskell neo4j client

Copyright(c) 2014, Antoni Silvestre
LicenseMIT
MaintainerAntoni Silvestre <antoni.silvestre@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Database.Neo4j

Contents

Description

Library to interact with the Neo4j REST API.

Synopsis

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 Port = Int 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

newtype Neo4j a Source #

Neo4j monadic type to be able to sequence neo4j commands in a connection

Constructors

Neo4j 

Fields

Instances

Monad Neo4j Source # 

Methods

(>>=) :: Neo4j a -> (a -> Neo4j b) -> Neo4j b #

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

return :: a -> Neo4j a #

fail :: String -> Neo4j a #

Functor Neo4j Source # 

Methods

fmap :: (a -> b) -> Neo4j a -> Neo4j b #

(<$) :: a -> Neo4j b -> Neo4j a #

Applicative Neo4j Source # 

Methods

pure :: a -> Neo4j a #

(<*>) :: Neo4j (a -> b) -> Neo4j a -> Neo4j b #

(*>) :: Neo4j a -> Neo4j b -> Neo4j b #

(<*) :: Neo4j a -> Neo4j b -> Neo4j a #

MonadIO Neo4j Source # 

Methods

liftIO :: IO a -> Neo4j a #

MonadThrow Neo4j Source # 

Methods

throwM :: Exception e => e -> Neo4j a #

MonadBase Neo4j Neo4j Source # 

Methods

liftBase :: Neo4j α -> Neo4j α #

Constructing and managing node/relationship properties

data Val Source #

Type for a single value of a Neo4j property

Instances

Eq Val Source # 

Methods

(==) :: Val -> Val -> Bool #

(/=) :: Val -> Val -> Bool #

Show Val Source # 

Methods

showsPrec :: Int -> Val -> ShowS #

show :: Val -> String #

showList :: [Val] -> ShowS #

FromJSON Val Source #

JSON to single property values

ToJSON Val Source #

Specifying how to convert property single values to JSON

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

(|:) :: 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

data Node Source #

Representation of a Neo4j node, has a location URI and a set of properties

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

newtype NodePath Source #

Constructors

NodePath 

Fields

Instances

Eq NodePath Source # 
Ord NodePath Source # 
Show NodePath Source # 
Generic NodePath Source # 

Associated Types

type Rep NodePath :: * -> * #

Methods

from :: NodePath -> Rep NodePath x #

to :: Rep NodePath x -> NodePath #

Hashable NodePath Source # 

Methods

hashWithSalt :: Int -> NodePath -> Int #

hash :: NodePath -> Int #

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 # 
type Rep NodePath = D1 (MetaData "NodePath" "Database.Neo4j.Types" "haskell-neo4j-client-0.3.2.4-4isldq71xo3IrcS9ULR5fU" True) (C1 (MetaCons "NodePath" PrefixI True) (S1 (MetaSel (Just Symbol "runNodePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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 # 

data Direction Source #

Relationship direction

Constructors

Outgoing 
Incoming 
Any 

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

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

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

newtype RelPath Source #

Constructors

RelPath 

Fields

Instances

Eq RelPath Source # 

Methods

(==) :: RelPath -> RelPath -> Bool #

(/=) :: RelPath -> RelPath -> Bool #

Ord RelPath Source # 
Show RelPath Source # 
Generic RelPath Source # 

Associated Types

type Rep RelPath :: * -> * #

Methods

from :: RelPath -> Rep RelPath x #

to :: Rep RelPath x -> RelPath #

Hashable RelPath Source # 

Methods

hashWithSalt :: Int -> RelPath -> Int #

hash :: RelPath -> Int #

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 # 
type Rep RelPath = D1 (MetaData "RelPath" "Database.Neo4j.Types" "haskell-neo4j-client-0.3.2.4-4isldq71xo3IrcS9ULR5fU" True) (C1 (MetaCons "RelPath" PrefixI True) (S1 (MetaSel (Just Symbol "runRelPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Managing labels and getting nodes by label

type Label = Text Source #

Type for a label

allLabels :: Neo4j [Label] Source #

Get all labels in the DB

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

data Index Source #

Type for an index

Constructors

Index 

Instances

createIndex :: Label -> Text -> Neo4j Index Source #

Creates an index for a label and a property

getIndexes :: Label -> Neo4j [Index] Source #

Gets all indexes for a label

dropIndex :: Label -> Text -> Neo4j () Source #

Drop and index

Exceptions

Database version information