Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class SelectorLike (a :: k -> Type) where
- type CanAddType (types :: k) :: Constraint
- type AddType (types :: k) (typ :: Type) = (result :: k) | result -> types typ
- type HasField (types :: k) (field :: Symbol) (typ :: Type) :: Constraint
- withIdentifier :: Text -> a types -> a types
- withLabel :: CanAddType types => KnownSymbol (GetTypeName (Rep typ)) => a types -> a (AddType types typ)
- withProp :: HasField types field typ => IsValue typ => (SymbolS field, typ) -> a types -> a types
- lbl :: forall (typ :: Type) k (types :: k) (a :: k -> Type). SelectorLike a => CanAddType types => KnownSymbol (GetTypeName (Rep typ)) => a types -> a (AddType types typ)
- prop :: forall (field :: Symbol) (a :: k -> Type) (types :: k) (typ :: Type). SelectorLike a => HasField types field typ => IsValue typ => (SymbolS field, typ) -> a types -> a types
- (=:) :: forall (field :: Symbol) (typ :: Type). SymbolS field -> typ -> (SymbolS field, typ)
- data NodeSelector (typ :: [Type])
- data RelSelector (typ :: Maybe Type)
- defN :: NodeSelector '[]
- defR :: RelSelector Nothing
- (.&) :: a -> (a -> b) -> b
- (!->:) :: RelSelector a -> NodeSelector b -> PathPart
- (!-:) :: RelSelector a -> NodeSelector b -> PathPart
- (-:) :: NodeSelector a -> PathPart -> PathSelector
- (<-:) :: NodeSelector a -> PathPart -> PathSelector
- p :: NodeSelector a -> PathSelector
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 typeprop
adds a new property, making sure that this property exists in one of the labels and has correct type
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 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
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.
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.
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.
Instances
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.
:: forall (field :: Symbol) (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
.
(=:) :: 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
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
defN :: NodeSelector '[] Source #
An empty NodeSelector
.
defR :: RelSelector Nothing Source #
An empty RelSelector
.
Building paths
This module is completely interopable with path selectors from 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.