hasbolt-extras-0.0.0.21: Extras for hasbolt library

Safe HaskellNone
LanguageHaskell2010

Database.Bolt.Extras.DSL

Contents

Synopsis

Selectors for nodes, relations and paths

These data types let you specify Cypher queries.

With OverloadedLabels and operators you can write selectors in very concise Cypher-like form:

(#n .: "Name" .# ["name" =: "C42"]) -: (defR .: "NAME_OF") :!->: (#m .: "Molecule")
(n:Name{name:"C42"})-[:NAME_OF]->(m:Molecule)

data NodeSelector Source #

Selector for Nodes.

This datatype has OverloadedLabels instance to simplify specifying nodes. Labels produce empty nodes.

#foo :: NodeSelector
-- foo = NodeSelector (Just "foo") [] []

(.:) :: SelectorLike a => a -> Text -> a infixl 9 Source #

Operator version of withLabel. To be used with OverloadedLabels instances.

#foo .: "Foo" :: NodeSelector

(.#) :: SelectorLike a => a -> [(Text, Value)] -> a infixl 9 Source #

Operator version of withProp. To be used with OverloadedLabels instances.

See also =: from Database.Bolt package.

#foo .# ["bar" =: 42, "baz" =: "baz"] :: NodeSelector

data PathSelector Source #

Constructors

PathSelector :-!: PathPart infixl 1

not directed relation

PathSelector :<-!: PathPart infixl 1

directed relation

P NodeSelector

starting node of Path

data PathPart Source #

Selector for paths.

Constructors

RelSelector :!->: NodeSelector infixl 2

directed relation

RelSelector :!-: NodeSelector infixl 2

not directed relation

(-:) :: NodeSelector -> PathPart -> PathSelector infixl 1 Source #

Combined version of :-!: and P for specifying the first node of path.

(<-:) :: NodeSelector -> PathPart -> PathSelector infixl 1 Source #

Combined version of :<-!: and P for specifying the first node of path.

data Selector Source #

Constructors

PS PathSelector

path selector

TS Text

free text selector

Default selectors

defN :: NodeSelector Source #

Shorter synonym for defaultRel.

defR :: RelSelector Source #

Shorter synonym for defaultRel.

Cypher conditions

data Cond Source #

Conditions.

Constructors

ID Text BoltId

ID(txt) = boltId

IDs Text [BoltId]

ID(txt) IN [boltId1, boltId2, ... ]

IN Text [Text]

txt IN [txt1, txt2, ... ]

TC Text

free text condition

Instances
Eq Cond Source # 
Instance details

Defined in Database.Bolt.Extras.DSL.Internal.Types

Methods

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

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

Show Cond Source # 
Instance details

Defined in Database.Bolt.Extras.DSL.Internal.Types

Methods

showsPrec :: Int -> Cond -> ShowS #

show :: Cond -> String #

showList :: [Cond] -> ShowS #

ToCypher Cond Source # 
Instance details

Defined in Database.Bolt.Extras.DSL.Internal.Instances

Methods

toCypher :: Cond -> Text Source #

data Conds Source #

Constructors

Conds :&&: Conds infixr 3

condition AND condition

Conds :||: Conds infixr 2

condition OR condition

C Cond

single condition

Not Conds

NOT condition

Instances
Eq Conds Source # 
Instance details

Defined in Database.Bolt.Extras.DSL.Internal.Types

Methods

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

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

Show Conds Source # 
Instance details

Defined in Database.Bolt.Extras.DSL.Internal.Types

Methods

showsPrec :: Int -> Conds -> ShowS #

show :: Conds -> String #

showList :: [Conds] -> ShowS #

ToCypher Conds Source # 
Instance details

Defined in Database.Bolt.Extras.DSL.Internal.Instances

Methods

toCypher :: Conds -> Text Source #

DSL for Cypher

The free-monadic DSL lets you write Cypher queries in Haskell like this:

formQuery $ do
   matchF [
     PS $ (#n .: "Name" .# ["name" =: "C42"]) -: (defR .: "NAME_OF") :!->: (#m .: "Molecule")
   ]
   returnF ["n", "m"]

DSL operations

type CypherDSL a = Free Expr () Source #

A synonym for Free DSL.

createF :: Selectors -> Free Expr () Source #

Prepare CREATE query

matchF :: Selectors -> Free Expr () Source #

Prepare MATCH query

optionalMatchF :: Selectors -> Free Expr () Source #

Prepare 'OPTIONAL MATCH' query

mergeF :: Selectors -> Free Expr () Source #

Prepare MERGE query

whereF :: Conds -> Free Expr () Source #

Prepare WHERE query

setF :: [Text] -> Free Expr () Source #

Prepare SET query

deleteF :: [Text] -> Free Expr () Source #

Prepare DELETE query

detachDeleteF :: [Text] -> Free Expr () Source #

Prepare 'DETACH DELETE' query

removeF :: [Text] -> Free Expr () Source #

Prepare REMOVE query

returnF :: [Text] -> Free Expr () Source #

Prepare RETURN query

withF :: [Text] -> Free Expr () Source #

Prepare WITH query

textF :: Text -> Free Expr () Source #

Prepare query with custom text

Rendering Cypher queries

Implementation details

data Expr next Source #

Expression in Cypher language.

Constructors

Create Selectors next

CREATE query

Match Selectors next

MATCH query

OptionalMatch Selectors next

OPTIONAL MATCH query

Merge Selectors next

MERGE query

Where Conds next

WHERE query

Set [Text] next

SET query

Delete [Text] next

DELETE query

DetachDelete [Text] next

DETACH DELETE query

Remove [Text] next

REMOVE query

Return [Text] next

RETURN query

With [Text] next

WITH query

Text Text next

free text query

Instances
Functor Expr Source # 
Instance details

Defined in Database.Bolt.Extras.DSL.Internal.Types

Methods

fmap :: (a -> b) -> Expr a -> Expr b #

(<$) :: a -> Expr b -> Expr a #

Eq next => Eq (Expr next) Source # 
Instance details

Defined in Database.Bolt.Extras.DSL.Internal.Types

Methods

(==) :: Expr next -> Expr next -> Bool #

(/=) :: Expr next -> Expr next -> Bool #

Show next => Show (Expr next) Source # 
Instance details

Defined in Database.Bolt.Extras.DSL.Internal.Types

Methods

showsPrec :: Int -> Expr next -> ShowS #

show :: Expr next -> String #

showList :: [Expr next] -> ShowS #