hasbolt-0.1.3.4: Haskell driver for Neo4j 3+ (BOLT protocol)

Safe HaskellNone
LanguageHaskell2010

Database.Bolt

Synopsis

Documentation

type BoltActionT = ReaderT Pipe Source #

Monad Transformer to do all BOLT actions in

connect :: MonadIO m => BoltCfg -> m Pipe Source #

Creates new Pipe instance to use all requests through

close :: MonadIO m => Pipe -> m () Source #

Closes Pipe

reset :: MonadIO m => Pipe -> m () Source #

Resets current sessions

run :: Pipe -> BoltActionT m a -> m a Source #

Runs BOLT action on selected pipe

queryP :: MonadIO m => Text -> Map Text Value -> BoltActionT m [Record] Source #

Runs Cypher query with parameters and returns list of obtained Records. Strict version

query :: MonadIO m => Text -> BoltActionT m [Record] Source #

Runs Cypher query and returns list of obtained Records. Strict version

queryP_ :: MonadIO m => Text -> Map Text Value -> BoltActionT m () Source #

Runs Cypher query with parameters and ignores response

query_ :: MonadIO m => Text -> BoltActionT m () Source #

Runs Cypher query and ignores response

transact :: (MonadError e m, MonadIO m) => BoltActionT m a -> BoltActionT m a Source #

Runs a sequence of actions as transaction. All queries would be rolled back in case of any exception inside the block.

data BoltCfg Source #

Configuration of driver connection

Constructors

BoltCfg 

Fields

Instances
Default BoltCfg Source # 
Instance details

Defined in Database.Bolt.Connection.Type

Methods

def :: BoltCfg #

data Value Source #

The Value datatype generalizes all primitive BoltValues

Constructors

N () 
B Bool 
I Int 
F Double 
T Text 
L [Value] 
M (Map Text Value) 
S Structure 
Instances
Eq Value Source # 
Instance details

Defined in Database.Bolt.Value.Type

Methods

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

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

Show Value Source # 
Instance details

Defined in Database.Bolt.Value.Type

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

BoltValue Value Source # 
Instance details

Defined in Database.Bolt.Value.Instances

RecordValue (Map Text Value) Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m (Map Text Value) Source #

data Structure Source #

The Structure datatype describes Neo4j structure for BOLT protocol

Constructors

Structure 

Fields

type Record = Map Text Value Source #

Result type for query requests

class RecordValue a where Source #

Get exact type from Value

Methods

exact :: Monad m => Value -> m a Source #

Instances
RecordValue Bool Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m Bool Source #

RecordValue Double Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m Double Source #

RecordValue Int Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m Int Source #

RecordValue () Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m () Source #

RecordValue Text Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m Text Source #

RecordValue Path Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m Path Source #

RecordValue URelationship Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m URelationship Source #

RecordValue Relationship Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m Relationship Source #

RecordValue Node Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m Node Source #

RecordValue a => RecordValue [a] Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m [a] Source #

RecordValue a => RecordValue (Maybe a) Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m (Maybe a) Source #

RecordValue (Map Text Value) Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m (Map Text Value) Source #

at :: Monad m => Record -> Text -> m Value Source #

data Node Source #

Constructors

Node 

Fields

Instances
Eq Node Source # 
Instance details

Defined in Database.Bolt.Value.Type

Methods

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

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

Show Node Source # 
Instance details

Defined in Database.Bolt.Value.Type

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

FromStructure Node Source # 
Instance details

Defined in Database.Bolt.Value.Structure

RecordValue Node Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m Node Source #

data Relationship Source #

Constructors

Relationship 

Fields

data URelationship Source #

Constructors

URelationship 

Fields

data Path Source #

Constructors

Path 

Fields

Instances
Eq Path Source # 
Instance details

Defined in Database.Bolt.Value.Type

Methods

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

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

Show Path Source # 
Instance details

Defined in Database.Bolt.Value.Type

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

FromStructure Path Source # 
Instance details

Defined in Database.Bolt.Value.Structure

RecordValue Path Source # 
Instance details

Defined in Database.Bolt.Record

Methods

exact :: Monad m => Value -> m Path Source #