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

Safe HaskellNone
LanguageHaskell98

Database.Neo4j.Transactional.Cypher

Contents

Description

Module to provide Cypher support using the transactional endpoint.

Example:

import qualified Database.Neo4j.Transactional.Cypher as T

withConnection host port $ do
   ...
   res <- TC.runTransaction $ do
           -- Queries return a result with columns, rows, a list of graphs and stats
           result <- TC.cypher "CREATE (pere: PERSON {age: {age}}) CREATE (pau: PERSON {props}) \
                             \CREATE p1 = (pere)-[:KNOWS]->(pau) RETURN pere, pau, p1, pere.age" $
                               M.fromList [("age", TC.newparam (78 :: Int64)),
                                           ("props", TC.ParamProperties $ M.fromList["age" |: (99 :: Int64)])]
           -- if any of the commands returns an error the transaction is rollbacked and leaves
           result 2 <- T.cypher "not a command" M.empty
           void $ TC.cypher "CREATE (pep: PERSON {age: 55})" M.empty
           -- Transactions are implicitly commited/rollbacked (in case of exception)
           -- but can be explicitly committed and rollbacked
           return (result, result2)

Synopsis

Types

data Result Source #

Type for a Cypher response with tuples containing column name and their values

Constructors

Result 

Fields

Instances

Eq Result Source # 

Methods

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

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

Show Result Source # 
FromJSON Result Source #

How to create a response object from a cypher JSON response

data Stats Source #

Holds the connection stats

Instances

Eq Stats Source # 

Methods

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

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

Show Stats Source # 

Methods

showsPrec :: Int -> Stats -> ShowS #

show :: Stats -> String #

showList :: [Stats] -> ShowS #

FromJSON Stats Source #

Instance to parse stats from a JSON

data ParamValue Source #

Value for a cypher parmeter value, might be a literal, a property map or a list of property maps

Instances

Eq ParamValue Source # 
Show ParamValue Source # 
ToJSON ParamValue Source #

Instance toJSON for param values so we can serialize them in queries

type Params = HashMap Text ParamValue Source #

We use hashmaps to represent Cypher parameters

emptyStats :: Stats Source #

Default stats

type TransError = (Text, Text) Source #

Error code and message for a transaction error

Sending queries

runTransaction :: Transaction a -> Neo4j (Either TransError a) Source #

Run a transaction and get its final result, has an implicit commit request (or rollback if an exception occurred). This implicit commit/rollback will only be executed if it hasn't before because of an explicit one

cypher :: Text -> Params -> Transaction Result Source #

Run a cypher query in a transaction, if an error occurs the transaction will stop and rollback

rollback :: Transaction () Source #

Rollback a transaction. After this, executing rollback, commit, keepalive, cypher in the transaction will result in an exception

commit :: Transaction () Source #

Commit a transaction. After this, executing rollback, commit, keepalive, cypher in the transaction will result in an exception

keepalive :: Transaction () Source #

Send a keep alive message to an open transaction

commitWith :: Text -> Params -> Transaction Result Source #

Send a cypher query and commit at the same time, if an error occurs the transaction will be rolled back. After this, executing rollback, commit, keepalive, cypher in the transaction will result in an exception

rollbackAndLeave :: Text -> Transaction () Source #

Rollback a transaction and stop processing it, set the message that runTransaction will return as error

Aux functions

isSuccess :: Either TransError Result -> Bool Source #

True if the operation succeeded

fromResult :: Result -> Either TransError Result -> Result Source #

Get the result of the response or a default value

fromSuccess :: Either TransError Result -> Result Source #

Get the result of the response or a default value