Skip to content

Commit

Permalink
version 0.0.1.2: =: type synonym (#37)
Browse files Browse the repository at this point in the history
  • Loading branch information
maksbotan authored and ozzzzz committed Jan 22, 2020
1 parent 4573614 commit cdc3368
Show file tree
Hide file tree
Showing 5 changed files with 20 additions and 5 deletions.
4 changes: 4 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,10 @@ and this project adheres to [Semantic Versioning](http://semver.org/spec/v2.0.0.

## [Unreleased]

## [0.0.1.2] - 2020-01-17
### Added
- `=:` type synonym to avoid ticks in type-level tuples.

## [0.0.1.1] - 2019-12-31
### Added
- `param` combinator to add named parameters to selectors;
Expand Down
2 changes: 1 addition & 1 deletion hasbolt-extras.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: hasbolt-extras
version: 0.0.1.1
version: 0.0.1.2
synopsis: Extras for hasbolt library
description: Extras for hasbolt library
homepage: https://github.com/biocad/hasbolt-extras#readme
Expand Down
10 changes: 7 additions & 3 deletions src/Database/Bolt/Extras/DSL/Typed.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE ExplicitNamespaces #-}

{- | Type-safe DSL for Cypher
This module extends selectors from 'Database.Bolt.Extras.DSL.DSL' with extra type-level
Expand All @@ -24,6 +26,7 @@ module Database.Bolt.Extras.DSL.Typed
, prop
, propMaybe
, param
, type (=:)
, (=:)
, NodeSelector, RelSelector
, nodeSelector, relSelector
Expand Down Expand Up @@ -53,16 +56,17 @@ module Database.Bolt.Extras.DSL.Typed
) where


import Database.Bolt.Extras.DSL.Typed.Instances ()
import Database.Bolt.Extras.DSL.Typed.Types
import Database.Bolt.Extras.DSL.Typed.Instances ()
import Database.Bolt.Extras.DSL.Typed.Parameters
import Database.Bolt.Extras.DSL.Typed.Types

{- $setup
>>> :set -XDeriveGeneric
>>> :set -XTypeApplications
>>> :set -XOverloadedLabels
>>> :set -XOverloadedStrings
>>> :set -XDataKinds
>>> :set -XTypeOperators
>>> :load Database.Bolt.Extras.Graph Database.Bolt.Extras.DSL.Typed Database.Bolt.Extras.DSL
>>> import Database.Bolt.Extras.DSL.Typed
>>> import Data.Text (Text, unpack)
Expand Down Expand Up @@ -267,7 +271,7 @@ Here is an example of a path constructed this way:
There is an option to annotate queries ('Database.Bolt.Extras.DSL.CypherDSL') with parameters they accept,
like this:
> fooQ :: CypherDSLParams '[ '("foo", Int), '("bar", Text) ]
> fooQ :: CypherDSLParams '["foo" =: Int, "bar" =: Text]
> fooQ = CypherDSLParams $ do
> matchF [ PS $ p $ #n .& lbl @Foo .& param (#foo =: "foo") .& param (#bar =: "bar")
> returnF ["n"]
Expand Down
5 changes: 4 additions & 1 deletion src/Database/Bolt/Extras/DSL/Typed/Parameters.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@ import Database.Bolt.Extras.DSL.Typed.Types (SymbolS (..))
>>> :set -XOverloadedLabels
>>> :set -XDataKinds
>>> :set -XOverloadedStrings
>>> :set -XTypeOperators
>>> :load Database.Bolt.Extras.DSL.Typed.Instances Database.Bolt.Extras.DSL.Typed.Parameters
>>> import Control.Monad.IO.Class
>>> import Database.Bolt (BoltActionT, Record)
Expand All @@ -39,6 +40,8 @@ import Database.Bolt.Extras.DSL.Typed.Types (SymbolS (..))

-- | 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.
newtype CypherDSLParams (params :: [(Symbol, Type)]) (a :: Type)
= CypherDSLParams (CypherDSL a)

Expand Down Expand Up @@ -68,7 +71,7 @@ instance (IsValue typ, QueryWithParams rest m fun)
--
-- A couple of examples:
--
-- >>> dsl = CypherDSLParams (returnF []) :: CypherDSLParams '[ '("foo", Int), '("bar", Text) ] ()
-- >>> dsl = CypherDSLParams (returnF []) :: CypherDSLParams '["foo" =: Int, "bar" =: Text] ()
-- >>> :t queryWithParams dsl
-- queryWithParams dsl
-- :: MonadIO m =>
Expand Down
4 changes: 4 additions & 0 deletions src/Database/Bolt/Extras/DSL/Typed/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}

module Database.Bolt.Extras.DSL.Typed.Types where

Expand Down Expand Up @@ -147,6 +148,9 @@ param
-> a types -> a types
param = withParam

-- | Smart constructor for type-level tuples, to avoid writing @'("foo", Int)@ with extra tick.
type (=:) (a :: k) (b :: l) = '(a, b)

-- | Smart constructor for a pair of field name and its value. To be used with @OverloadedLabels@:
--
-- > #uuid =: "123"
Expand Down

0 comments on commit cdc3368

Please sign in to comment.