hasbolt-extras-0.0.1.9: Extras for hasbolt library
Safe HaskellNone
LanguageHaskell2010

Database.Bolt.Extras.DSL.Typed

Description

Type-safe DSL for Cypher

This module extends selectors from DSL with extra type-level information to make them more type-safe to use.

None of additional type information exists at runtime, so using this module does not degrade performance at all.

Synopsis

Selecting Nodes and Relations

There are types for Node and Relationship selectors: NodeSelector and RelSelector. Both of them carry extra type-level information about labels assigned to Cypher variables.

Empty selectors may be constructed with defN and defR respectively. Selectors can be extended with the following combinators:

  • withIdentifier adds an identifier (variable name)
  • lbl adds a label represented by some Haskell type
  • prop adds a new property, making sure that this property exists in one of the labels and has correct type
  • param adds a new property with named parameter ($foo syntax in Cypher), making sure that this property exists in one of the labels

Typically selectors are chained by .& starting from defN or defR like this:

>>> toCypherN $ defN .& withIdentifier "binder" .& lbl @Binder .& prop (#uuid =: "123-456")
(binder:Binder{uuid:"123-456"})

Alternatively, OverloadedLabels may be used to create an empty selector with an identifier:

>>> toCypherN $ #binder .& lbl @Binder .& prop (#uuid =: "123-456")
(binder:Binder{uuid:"123-456"})

This syntax is more concise and makes it obvious what is going on. Thus, it is the preferred one.

The type used with lbl should have Generic instance.

Nodes may have multiple labels:

>>> toCypherN $ defN .& lbl @Binder .& lbl @Foo
(:Foo:Binder)

But relations have at most one:

>>> defR .& lbl @PLACE .& lbl @ELEMENT
...
... Can't add a new label to relationship selector that already has label PLACE!
...

Complex queries

These selectors are fully compatible with the Database.Bolt.Extras.DSL:

>>> :{
toCypherQ $ do
   mergeF
     [ PS $ p $ #name .& lbl @Name .& prop (#name =: "CT42")
     ]
   mergeF
     [ PS $ p $ #user .& lbl @User .& prop (#user =: "123-456")
     ]
   createF
     [ PS $ p $ #lib .& lbl @Library .& lbl @BinderLibrary
     , PS $ #name -: defR .& lbl @NAME_OF !->: #lib
     , PS $ #user -: defR .& lbl @USER_CREATED .& prop (#timestamp =: 1572340394000) !->: #lib
     ]
   returnF ["lib"]
:}
MERGE (name:Name{name:"CT42"}) MERGE (user:User{user:"123-456"}) CREATE (lib:BinderLibrary:Library), (name)-[:NAME_OF]->(lib), (user)-[:USER_CREATED{timestamp:1572340394000}]->(lib) RETURN lib

Dropping types

It is possible to convert typed selectors to untyped ones from Database.Bolt.Extras.DSL using nodeSelector and relSelector funcions.

Using with Graph api

This module is also interopable with Database.Bolt.Extras.Graph API. Here is an example of graph query using typed selectors.

>>> import Database.Bolt.Extras.Graph
>>> nToG = ngFromDSL . nodeSelector
>>> rToG = rgFromDSL . relSelector
>>> :{
formQueryG $ emptyGraph
 & addNode "binder"
   (nToG
      (defN .& lbl @Binder .& prop (#uuid =: "123-456"))
      & isReturned
      & withReturn allProps
   )
 & addNode "user"
   (nToG
      (defN .& lbl @User .& prop (#user =: "098-765"))
      & isReturned
      & withReturn allProps
   )
 & addRelation "user" "binder"
   (rToG
      (defR .& lbl @USER_CREATED)
      & isReturned
      & withReturn allProps
   )
:}
MATCH (user)-[user0binder :USER_CREATED {}]->(binder), (binder :Binder {uuid:"123-456"}), (user :User {user:"098-765"})

WITH DISTINCT binder, user, user0binder
RETURN { id: id(binder),
  labels: labels(binder),
  props: properties(binder)
} as binder, { id: id(user),
  labels: labels(user),
  props: properties(user)
} as user, { id: id(user0binder),
  label: type(user0binder),
  props: properties(user0binder)
} as user0binder

Type safety

Obviosuly, if you try to use lbl @Foo syntax with undefined type Foo, GHC itself will report the error.

Here are more interesting cases:

>>> -- Properties are looked for in all labels
>>> toCypherN $ defN .& lbl @Binder .& lbl @Foo .& prop (#foo =: 42) .& prop (#uuid =: "123-456")
(:Foo:Binder{uuid:"123-456",foo:42})
>>> -- Adding a property to node without any labels
>>> defN .& prop (#uuid =: "123-456")
...
... There is no field "uuid" in any of the records
... '[]
...
>>> -- Adding a property that does not exist in the label
>>> defN .& lbl @Binder .& prop (#foo =: 42)
...
... There is no field "foo" in any of the records
... '[Binder]
...
>>> -- Adding a property with wrong type
>>> defN .& lbl @Binder .& prop (#uuid =: 42)
...
... No instance for (Num Text) arising from the literal ‘42’
...

Here we see that GHC undestands that the property should have type Text and tries to unify it with the type of literal 42, which is Num a => a.

>>> -- Adding a property to relationship without a label
>>> defR .& prop (#foo =: 42)
...
... Tried to set property "foo" on a relationship without label!
...

class SelectorLike (a :: k -> Type) where Source #

Class for Selectors that know type of their labels. This class is kind-polymorphic, so that instances may select a specific collection of labels they support.

NOTE: Due to the way GHC orders type variables for class methods, it's more convenient to use lbl and prop synonyms defined below, and withLabel and withProp methods should be considered an implementation detail.

Associated Types

type CanAddType (types :: k) :: Constraint Source #

This constraint checks that current collection of types supports adding one more.

type AddType (types :: k) (typ :: Type) = (result :: k) | result -> types typ Source #

This type family implements adding a new type (of label) to the collection.

Injectivity annotation is required to make type inference possible.

type HasField (types :: k) (field :: Symbol) (typ :: Type) :: Constraint Source #

This constraint checks that field with this name has correct type in the collection of labels.

type HasField' (types :: k) (field :: Symbol) :: Constraint Source #

This constraint checks that field with this name exists in the collection, with any type.

Methods

withIdentifier :: Text -> a types -> a types Source #

Set an identifier — Cypher variable name.

withLabel :: CanAddType types => KnownSymbol (GetTypeName (Rep typ)) => a types -> a (AddType types typ) Source #

Add a new label, if possible.

withProp :: HasField types field typ => IsValue typ => (SymbolS field, typ) -> a types -> a types Source #

Add a property with value, checking that such property exists.

withParam :: HasField' types field => (SymbolS field, Text) -> a types -> a types Source #

Add a property as named parameter ($foo). Only checks that given property exists, no matter its type.

Instances

Instances details
SelectorLike NodeSelector Source # 
Instance details

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

Associated Types

type CanAddType types Source #

type AddType types typ = (result :: k) Source #

type HasField types field typ Source #

type HasField' types field Source #

Methods

withIdentifier :: forall (types :: k). Text -> NodeSelector types -> NodeSelector types Source #

withLabel :: forall (types :: k) typ. (CanAddType types, KnownSymbol (GetTypeName (Rep typ))) => NodeSelector types -> NodeSelector (AddType types typ) Source #

withProp :: forall (types :: k) (field :: Symbol) typ. (HasField types field typ, IsValue typ) => (SymbolS field, typ) -> NodeSelector types -> NodeSelector types Source #

withParam :: forall (types :: k) (field :: Symbol). HasField' types field => (SymbolS field, Text) -> NodeSelector types -> NodeSelector types Source #

SelectorLike RelSelector Source # 
Instance details

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

Associated Types

type CanAddType types Source #

type AddType types typ = (result :: k) Source #

type HasField types field typ Source #

type HasField' types field Source #

Methods

withIdentifier :: forall (types :: k). Text -> RelSelector types -> RelSelector types Source #

withLabel :: forall (types :: k) typ. (CanAddType types, KnownSymbol (GetTypeName (Rep typ))) => RelSelector types -> RelSelector (AddType types typ) Source #

withProp :: forall (types :: k) (field :: Symbol) typ. (HasField types field typ, IsValue typ) => (SymbolS field, typ) -> RelSelector types -> RelSelector types Source #

withParam :: forall (types :: k) (field :: Symbol). HasField' types field => (SymbolS field, Text) -> RelSelector types -> RelSelector types Source #

type LabelConstraint (typ :: Type) = KnownSymbol (GetTypeName (Rep typ)) Source #

Constraint for types that may be used with lbl.

lbl :: forall (typ :: Type) k (types :: k) (a :: k -> Type). SelectorLike a => CanAddType types => KnownSymbol (GetTypeName (Rep typ)) => a types -> a (AddType types typ) Source #

Synonym for withLabel with label type variable as first one, enabling lbl @Foo type application syntax.

prop Source #

Arguments

:: forall (field :: Symbol) k (a :: k -> Type) (types :: k) (typ :: Type). SelectorLike a 
=> HasField types field typ 
=> IsValue typ 
=> (SymbolS field, typ)

Field name along with its value. This pair should be constructed with =:.

-> a types 
-> a types 

Shorter synonym for withProp.

Properties of type Maybe a are treated as properties of type a, since there is no difference between the two in Cypher.

>>> data Foo = Foo { foo :: Int, bar :: Maybe String } deriving Generic
>>> toCypherN $ defN .& lbl @Foo .& prop (#foo =: 42)
(:Foo{foo:42})
>>> toCypherN $ defN .& lbl @Foo .& prop (#bar =: "hello")
(:Foo{bar:"hello"})

propMaybe :: forall (field :: Symbol) k (a :: k -> Type) (types :: k) (typ :: Type). SelectorLike a => HasField types field typ => IsValue typ => (SymbolS field, Maybe typ) -> a types -> a types Source #

A variant of prop that accepts values in Maybe. If given Nothing, does nothing.

This works both for properties with Maybe and without.

>>> data Foo = Foo { foo :: Int, bar :: Maybe String } deriving Generic
>>> toCypherN $ defN .& lbl @Foo .& propMaybe (#foo =: Just 42)
(:Foo{foo:42})
>>> toCypherN $ defN .& lbl @Foo .& propMaybe (#bar =: Nothing)
(:Foo)

param :: forall (field :: Symbol) k (a :: k -> Type) (types :: k). SelectorLike a => HasField' types field => (SymbolS field, Text) -> a types -> a types Source #

Shorter synonym for withParam.

>>> data Foo = Foo { foo :: Int, bar :: Maybe String } deriving Generic
>>> toCypherN $ defN .& lbl @Foo .& param (#foo =: "foo")
(:Foo{foo:$foo})
>>> toCypherN $ defN .& lbl @Foo .& prop (#foo =: 42) .& param (#bar =: "bar")
(:Foo{foo:42,bar:$bar})
>>> toCypherN $ defN .& lbl @Foo .& param (#baz =: "baz")
...
... There is no field "baz" in any of the records
... '[Foo]
...

NOTE: this will add $ symbol to parameter name automatically.

type (=:) (a :: k) (b :: l) = '(a, b) Source #

Smart constructor for type-level tuples, to avoid writing '("foo", Int) with extra tick.

(=:) :: forall (field :: Symbol) (typ :: Type). SymbolS field -> typ -> (SymbolS field, typ) Source #

Smart constructor for a pair of field name and its value. To be used with OverloadedLabels:

#uuid =: "123"

data NodeSelector (typ :: [Type]) Source #

A wrapper around NodeSelector with phantom type.

Node selectors remember arbitrary number of labels in a type-level list.

Instances

Instances details
(KnownSymbol x, types ~ ('[] :: [Type])) => IsLabel x (NodeSelector types) Source # 
Instance details

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

Methods

fromLabel :: NodeSelector types #

Eq (NodeSelector typ) Source # 
Instance details

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

Methods

(==) :: NodeSelector typ -> NodeSelector typ -> Bool #

(/=) :: NodeSelector typ -> NodeSelector typ -> Bool #

Show (NodeSelector typ) Source # 
Instance details

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

SelectorLike NodeSelector Source # 
Instance details

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

Associated Types

type CanAddType types Source #

type AddType types typ = (result :: k) Source #

type HasField types field typ Source #

type HasField' types field Source #

Methods

withIdentifier :: forall (types :: k). Text -> NodeSelector types -> NodeSelector types Source #

withLabel :: forall (types :: k) typ. (CanAddType types, KnownSymbol (GetTypeName (Rep typ))) => NodeSelector types -> NodeSelector (AddType types typ) Source #

withProp :: forall (types :: k) (field :: Symbol) typ. (HasField types field typ, IsValue typ) => (SymbolS field, typ) -> NodeSelector types -> NodeSelector types Source #

withParam :: forall (types :: k) (field :: Symbol). HasField' types field => (SymbolS field, Text) -> NodeSelector types -> NodeSelector types Source #

data RelSelector (typ :: Maybe Type) Source #

A wrapper around RelSelector with phantom type.

Relationship selectors remember at most one label in a type-level Maybe.

Instances

Instances details
(KnownSymbol x, types ~ ('Nothing :: Maybe Type)) => IsLabel x (RelSelector types) Source # 
Instance details

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

Methods

fromLabel :: RelSelector types #

Eq (RelSelector typ) Source # 
Instance details

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

Methods

(==) :: RelSelector typ -> RelSelector typ -> Bool #

(/=) :: RelSelector typ -> RelSelector typ -> Bool #

Show (RelSelector typ) Source # 
Instance details

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

Methods

showsPrec :: Int -> RelSelector typ -> ShowS #

show :: RelSelector typ -> String #

showList :: [RelSelector typ] -> ShowS #

SelectorLike RelSelector Source # 
Instance details

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

Associated Types

type CanAddType types Source #

type AddType types typ = (result :: k) Source #

type HasField types field typ Source #

type HasField' types field Source #

Methods

withIdentifier :: forall (types :: k). Text -> RelSelector types -> RelSelector types Source #

withLabel :: forall (types :: k) typ. (CanAddType types, KnownSymbol (GetTypeName (Rep typ))) => RelSelector types -> RelSelector (AddType types typ) Source #

withProp :: forall (types :: k) (field :: Symbol) typ. (HasField types field typ, IsValue typ) => (SymbolS field, typ) -> RelSelector types -> RelSelector types Source #

withParam :: forall (types :: k) (field :: Symbol). HasField' types field => (SymbolS field, Text) -> RelSelector types -> RelSelector types Source #

relSelector :: RelSelector typ -> RelSelector Source #

Convert to untyped RelSelector.

Building paths

This module is completely interopable with path selectors from Database.Bolt.Extras.DSL — adding a NodeSelector or RelSelector to path simply drops all type information, converting it into untyped variant.

Due to limitation of what symbols are allowed in operators and operator-like data constructors, this module renames some of the path constructors. Precedence of the operators allow them to be combined in the same expression with .& and $ without any extra parentheses.

Here is an example of a path constructed this way:

>>> toCypherP (#binder .& lbl @Binder .& prop (#uuid =: "123") -: defR .& lbl @ELEMENT !->: #el)
(binder:Binder{uuid:"123"})-[:ELEMENT]->(el)

(.&) :: a -> (a -> b) -> b infixl 3 Source #

This is the same as &, but with higher precedence, so that it binds before path combinators.

(!->:) :: RelSelector a -> NodeSelector b -> PathPart infixl 2 Source #

See :!->:. This combinator forgets type-level information from the selectors.

(!-:) :: RelSelector a -> NodeSelector b -> PathPart infixl 2 Source #

See :!-:. This combinator forgets type-level information from the selectors.

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

See -:. This combinator forgets type-level information from the selectors.

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

See <-:. This combinator forgets type-level information from the selectors.

p :: NodeSelector a -> PathSelector Source #

See P. This combinator forgets type-level information from the selectors.

Queries with parameters

There is an option to annotate queries (CypherDSL) with parameters they accept, like this:

fooQ :: CypherDSLParams '["foo" =: Int, "bar" =: Text]
fooQ = CypherDSLParams $ do
    matchF [ PS $ p $ #n .& lbl @Foo .& param (#foo =: "foo") .& param (#bar =: "bar")
    returnF ["n"]

This will render to the following Cypher expression:

match (n: Foo {foo: $foo, bar: $bar}) return n

To make sure that all parameters are filled, use queryWithParams function:

records <- queryWithParams fooQ (#foo =: 42) (#bar =: "Hello")

See below for more examples.

newtype CypherDSLParams (params :: [(Symbol, Type)]) (a :: Type) Source #

A wrapper around arbitrary CypherDSL expression which stores type-level list of named parameters ($foo) with their types.

It is convenient to write signatures using (=:) type synonym.

Constructors

CypherDSLParams (CypherDSL a) 

queryWithParams :: forall params m fun. MonadIO m => QueryWithParams params m fun => HasCallStack => CypherDSLParams params () -> fun Source #

Run a query (in the form of CypherDSLParams). This is a function of variable number of arguments. Actual number will be determined by type-level list params.

A couple of examples:

>>> dsl = CypherDSLParams (returnF []) :: CypherDSLParams '["foo" =: Int, "bar" =: Text] ()
>>> :t queryWithParams dsl
queryWithParams dsl
  :: MonadIO m =>
     (SymbolS "foo", Int)
     -> (SymbolS "bar", Text) -> BoltActionT m [Record]
>>> :t queryWithParams dsl (#foo =: 42)
queryWithParams dsl (#foo =: 42)
  :: MonadIO m => (SymbolS "bar", Text) -> BoltActionT m [Record]
>>> :t queryWithParams dsl (#foo =: 42) (#bar =: "Hello")
queryWithParams dsl (#foo =: 42) (#bar =: "Hello")
  :: MonadIO m => BoltActionT m [Record]
>>> :t queryWithParams dsl (#foo =: True)
...
... Couldn't match type ‘Int’ with ‘Bool’
...
>>> :t queryWithParams dsl (#bar =: 42)
...
... Couldn't match type ‘"bar"’ with ‘"foo"’
...

Implementation details

class QueryWithParams (params :: [(Symbol, Type)]) (m :: Type -> Type) fun | params m -> fun where Source #

This type class ensures safety of queries with parameters by checking in compile time that all parameters are supplied and have correct type.

Instances of this class will add more arguments to fun, one for each element in params.

This should be considered an implementation detail.

Methods

collectParams :: HasCallStack => CypherDSL () -> [(Text, Value)] -> fun Source #

Internal function that accumulates parameters from type-level list.

Instances

Instances details
MonadIO m => QueryWithParams ('[] :: [(Symbol, Type)]) m (BoltActionT m [Record]) Source #

Base case: if there are no parameters, perform query with queryP.

Instance details

Defined in Database.Bolt.Extras.DSL.Typed.Parameters