| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Database.Neo4j.Transactional.Cypher
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)- data Result = Result {}
- data Stats = Stats {}
- data ParamValue
- type Params = HashMap Text ParamValue
- newparam :: PropertyValueConstructor a => a -> ParamValue
- emptyStats :: Stats
- type TransError = (Text, Text)
- type Transaction a = ExceptT TransError (ReaderT Connection (StateT TransState (ResourceT IO))) a
- loneQuery :: Text -> Params -> Neo4j (Either TransError Result)
- runTransaction :: Transaction a -> Neo4j (Either TransError a)
- cypher :: Text -> Params -> Transaction Result
- rollback :: Transaction ()
- commit :: Transaction ()
- keepalive :: Transaction ()
- commitWith :: Text -> Params -> Transaction Result
- rollbackAndLeave :: Text -> Transaction ()
- isSuccess :: Either TransError Result -> Bool
- fromResult :: Result -> Either TransError Result -> Result
- fromSuccess :: Either TransError Result -> Result
Types
Type for a Cypher response with tuples containing column name and their values
Holds the connection stats
Constructors
| Stats | |
| Fields 
 | |
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 | |
| Show ParamValue | |
| ToJSON ParamValue | 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
newparam :: PropertyValueConstructor a => a -> ParamValue Source
Default stats
type TransError = (Text, Text) Source
Error code and message for a transaction error
type Transaction a = ExceptT TransError (ReaderT Connection (StateT TransState (ResourceT IO))) a Source
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
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