Skip to content

Commit

Permalink
Update to hasbolt-0.1.4.0 (#35)
Browse files Browse the repository at this point in the history
  • Loading branch information
maksbotan authored and ozzzzz committed Dec 17, 2019
1 parent b240e1a commit 1002b7a
Show file tree
Hide file tree
Showing 5 changed files with 22 additions and 11 deletions.
6 changes: 6 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,12 @@ and this project adheres to [Semantic Versioning](http://semver.org/spec/v2.0.0.

## [Unreleased]

## [0.0.1.0] - 2019-12-17
### Changed
- Use `hasbolt` 0.1.4.0.
### Added
- Compatibility function `exact` from older `hasbolt`.

## [0.0.0.25] - 2019-12-07
### Added
- `makeNodeLikeWith` and `makeURelationLikeWith` functions.
Expand Down
4 changes: 2 additions & 2 deletions hasbolt-extras.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: hasbolt-extras
version: 0.0.0.25
version: 0.0.1.0
synopsis: Extras for hasbolt library
description: Extras for hasbolt library
homepage: https://github.com/biocad/hasbolt-extras#readme
Expand Down Expand Up @@ -56,7 +56,7 @@ library
, aeson-casing >= 0.1.0.5
, containers >= 0.5.10.2
, free >= 5.0
, hasbolt >= 0.1.3.5
, hasbolt >= 0.1.4.0
, lens >= 4.16
, mtl >= 2.2.0
, neat-interpolation >= 0.3.2.0
Expand Down
9 changes: 4 additions & 5 deletions src/Database/Bolt/Extras/Graph/Internal/Put.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-orphans -Wno-deprecations #-}

module Database.Bolt.Extras.Graph.Internal.Put
(
Expand All @@ -19,10 +19,8 @@ import Data.Monoid ((<>))
import Data.Text (Text,
intercalate,
pack)
import Database.Bolt (Node (..), RecordValue (..),
URelationship (..),
Value (..),
exact)
import Database.Bolt (Node (..), URelationship (..),
Value (..))
import Database.Bolt.Extras (BoltId, ToCypher (..),
fromInt)
import Database.Bolt.Extras.Graph.Internal.AbstractGraph (Graph (..),
Expand All @@ -31,6 +29,7 @@ import Database.Bolt.Extras.Graph.Internal.AbstractGraph (Graph (..),
import Database.Bolt.Extras.Graph.Internal.Class (Extractable (..),
Requestable (..),
Returnable (..))
import Database.Bolt.Extras.Utils (exact)
import NeatInterpolation (text)

------------------------------------------------------------------------------------------------
Expand Down
12 changes: 9 additions & 3 deletions src/Database/Bolt/Extras/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,15 +7,16 @@ module Database.Bolt.Extras.Utils
, currentLoc
, exactValues
, exactValuesM
, exact
) where

import Control.Monad.IO.Class (MonadIO)
import Control.Monad.IO.Class (MonadIO (..))
import Data.List (nub)
import Data.Map.Strict as M ((!), (!?))
import qualified Data.Map.Strict as M (union)
import Data.Text (Text)
import Database.Bolt as B (BoltActionT, Node (..), Record,
RecordValue, Value (..), exact)
RecordValue (..), Value (..))
import Language.Haskell.TH (Exp (..), Lit (..), Loc (..), Q,
location)
import Text.Printf (printf)
Expand All @@ -42,9 +43,14 @@ currentLoc = do
loc <- location
pure $ LitE $ StringL $ printf "%s:%d: " (loc_module loc) (fst $ loc_start loc)

-- | Unpack a value, using 'fail' in 'IO` to report errors.
{-# DEPRECATED exact "This function exists for compatibility, consider using pure exactEither or exactMaybe instead." #-}
exact :: (MonadIO m, RecordValue a) => Value -> m a
exact = either (liftIO . fail . show) pure . exactEither

-- | Extract values
--
exactValues :: (Monad m, RecordValue a) => Text -> [Record] -> m [a]
exactValues :: (MonadIO m, RecordValue a) => Text -> [Record] -> m [a]
exactValues var = mapM (exact . (! var))

-- | Extract values (maybe)
Expand Down
2 changes: 1 addition & 1 deletion stack.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ packages:
- '.'

extra-deps:
- hasbolt-0.1.3.5
- hasbolt-0.1.4.0

# https://github.com/commercialhaskell/stack/issues/3520
ignore-revision-mismatch: true
Expand Down

0 comments on commit 1002b7a

Please sign in to comment.