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

Safe HaskellNone
LanguageHaskell98

Database.Neo4j.Types

Synopsis

Documentation

(<>) :: Monoid a => a -> a -> a Source #

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

urlPath :: Text -> Text Source #

Tries to get the path from a URL, we try our best otherwise return the url as is

urlMinPath :: Text -> Text Source #

Path without the dbdata part, useful for batch paths and such

newtype NodeUrl Source #

Constructors

NodeUrl 

Fields

Instances

data Node Source #

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

Constructors

Node 

getNodeProperties :: Node -> Properties Source #

Get the properties 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)))

type RelationshipType = Text Source #

Type for a relationship type description

data Direction Source #

Relationship direction

Constructors

Outgoing 
Incoming 
Any 

newtype RelUrl Source #

Type for a relationship location

Constructors

RelUrl 

Fields

Instances

Eq RelUrl Source # 

Methods

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

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

Show RelUrl Source # 
Generic RelUrl Source # 

Associated Types

type Rep RelUrl :: * -> * #

Methods

from :: RelUrl -> Rep RelUrl x #

to :: Rep RelUrl x -> RelUrl #

Hashable RelUrl Source # 

Methods

hashWithSalt :: Int -> RelUrl -> Int #

hash :: RelUrl -> Int #

EntityIdentifier RelUrl Source # 
RelIdentifier RelUrl Source # 
RelBatchIdentifier RelUrl Source # 
BatchEntity RelUrl Source # 
type Rep RelUrl Source # 
type Rep RelUrl = D1 (MetaData "RelUrl" "Database.Neo4j.Types" "haskell-neo4j-client-0.3.2.4-4isldq71xo3IrcS9ULR5fU" True) (C1 (MetaCons "RelUrl" PrefixI True) (S1 (MetaSel (Just Symbol "runRelUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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 # 

getRelProperties :: Relationship -> Properties Source #

Get the properties of a relationship

getRelType :: Relationship -> RelationshipType Source #

Get the type of a relationship

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

type Label = Text Source #

Type for a label

data Index Source #

Type for an index

Constructors

Index 

Instances

data Connection Source #

Type for a connection

type Port = Int Source #

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 α #