| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.Bolt
Synopsis
- type BoltActionT = ReaderT Pipe
- connect :: MonadIO m => BoltCfg -> m Pipe
- close :: MonadIO m => Pipe -> m ()
- reset :: MonadIO m => Pipe -> m ()
- run :: Pipe -> BoltActionT m a -> m a
- queryP :: MonadIO m => Text -> Map Text Value -> BoltActionT m [Record]
- query :: MonadIO m => Text -> BoltActionT m [Record]
- queryP_ :: MonadIO m => Text -> Map Text Value -> BoltActionT m ()
- query_ :: MonadIO m => Text -> BoltActionT m ()
- transact :: (MonadError e m, MonadIO m) => BoltActionT m a -> BoltActionT m a
- (=:) :: IsValue a => Text -> a -> (Text, Value)
- props :: [(Text, Value)] -> Map Text Value
- data Pipe
- data BoltCfg = BoltCfg {}
- data Value
- class IsValue a where
- toValue :: a -> Value
- toValueList :: [a] -> Value
- data Structure = Structure {}
- type Record = Map Text Value
- class RecordValue a where
- at :: Monad m => Record -> Text -> m Value
- data Node = Node {}
- data Relationship = Relationship {}
- data URelationship = URelationship {}
- data Path = Path {
- pathNodes :: [Node]
- pathRelationships :: [URelationship]
- pathSequence :: [Int]
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
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
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.
Configuration of driver connection
Constructors
| BoltCfg | |
Fields
| |
class IsValue a where Source #
Every datatype that can be represented as BOLT protocol value
Minimal complete definition
Methods
toValue :: a -> Value Source #
Wraps value with Value constructor
toValueList :: [a] -> Value Source #
How to represent a list of values
Instances
| IsValue Bool Source # | |
| IsValue Char Source # | |
| IsValue Double Source # | |
| IsValue Float Source # | |
| IsValue Int Source # | |
| IsValue Integer Source # | |
| IsValue () Source # | |
Defined in Database.Bolt.Value.Type | |
| IsValue Text Source # | |
| IsValue a => IsValue [a] Source # | |
Defined in Database.Bolt.Value.Type | |
| IsValue (Map Text Value) Source # | |
The Structure datatype describes Neo4j structure for BOLT protocol
class RecordValue a where Source #
Get exact type from Value
Instances
| RecordValue Bool Source # | |
| RecordValue Double Source # | |
| RecordValue Int Source # | |
| RecordValue () Source # | |
| RecordValue Text Source # | |
| RecordValue Path Source # | |
| RecordValue URelationship Source # | |
Defined in Database.Bolt.Record | |
| RecordValue Relationship Source # | |
Defined in Database.Bolt.Record | |
| RecordValue Node Source # | |
| RecordValue a => RecordValue [a] Source # | |
| RecordValue a => RecordValue (Maybe a) Source # | |
| RecordValue (Map Text Value) Source # | |
Constructors
| Node | |
data Relationship Source #
Constructors
| Relationship | |
Instances
| Eq Relationship Source # | |
Defined in Database.Bolt.Value.Type | |
| Show Relationship Source # | |
Defined in Database.Bolt.Value.Type Methods showsPrec :: Int -> Relationship -> ShowS # show :: Relationship -> String # showList :: [Relationship] -> ShowS # | |
| FromStructure Relationship Source # | |
Defined in Database.Bolt.Value.Structure Methods fromStructure :: Monad m => Structure -> m Relationship Source # | |
| RecordValue Relationship Source # | |
Defined in Database.Bolt.Record | |
data URelationship Source #
Constructors
| URelationship | |
Instances
| Eq URelationship Source # | |
Defined in Database.Bolt.Value.Type Methods (==) :: URelationship -> URelationship -> Bool # (/=) :: URelationship -> URelationship -> Bool # | |
| Show URelationship Source # | |
Defined in Database.Bolt.Value.Type Methods showsPrec :: Int -> URelationship -> ShowS # show :: URelationship -> String # showList :: [URelationship] -> ShowS # | |
| FromStructure URelationship Source # | |
Defined in Database.Bolt.Value.Structure Methods fromStructure :: Monad m => Structure -> m URelationship Source # | |
| RecordValue URelationship Source # | |
Defined in Database.Bolt.Record | |
Constructors
| Path | |
Fields
| |