Skip to content

Commit

Permalink
Add Newtypes module
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Nov 15, 2020
1 parent cf8a91b commit 5bebb26
Show file tree
Hide file tree
Showing 4 changed files with 98 additions and 0 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Expand Up @@ -16,6 +16,9 @@
* Fix spurious aborts when retrying transactions
Thanks to Elliot Cameron for the implementation
https://github.com/haskellari/postgresql-simple/pull/34
* Add `Database.PostgreSQL.Simple.Newtypes` module
with `Aeson` newtype.
https://github.com/haskellari/postgresql-simple/pull/55

### Version 0.6.2 (2019-04-26)

Expand Down
1 change: 1 addition & 0 deletions postgresql-simple.cabal
Expand Up @@ -48,6 +48,7 @@ library
Database.PostgreSQL.Simple.HStore.Internal
Database.PostgreSQL.Simple.Internal
Database.PostgreSQL.Simple.LargeObjects
Database.PostgreSQL.Simple.Newtypes
Database.PostgreSQL.Simple.Notification
Database.PostgreSQL.Simple.Ok
Database.PostgreSQL.Simple.Range
Expand Down
49 changes: 49 additions & 0 deletions src/Database/PostgreSQL/Simple/Newtypes.hs
@@ -0,0 +1,49 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveDataTypeable #-}
-- | Module with newtypes suitable to usage with @DerivingVia@ or standalone.
--
-- The newtypes are named after packages they wrap.
module Database.PostgreSQL.Simple.Newtypes (
Aeson (..), getAeson,
) where

import Data.Typeable (Typeable)
import Database.PostgreSQL.Simple.ToField (ToField (..))
import Database.PostgreSQL.Simple.FromField (FromField (..), fromJSONField)

import qualified Data.Aeson as Aeson

-------------------------------------------------------------------------------
-- aeson
-------------------------------------------------------------------------------

-- | A newtype wrapper with 'ToField' and 'FromField' instances
-- based on 'Aeson.ToJSON' and 'Aeson.FromJSON' type classes from @aeson@.
--
-- Example using @DerivingVia@:
--
-- @
-- data Foo = Foo Int String
-- deriving stock (Eq, Show, Generic) -- GHC built int
-- deriving anyclass ('Aeson.FromJSON', 'Aeson.ToJSON') -- Derived using GHC Generics
-- deriving ('ToField', 'FromField') via 'Aeson' Foo -- DerivingVia
-- @
--
-- Example using 'Aeson' newtype directly, for more ad-hoc queries
--
-- @
-- execute conn "INSERT INTO tbl (fld) VALUES (?)" (Only ('Aeson' x))
-- @
--
-- @since 0.6.3
newtype Aeson a = Aeson a
deriving (Eq, Show, Read, Typeable, Functor)

getAeson :: Aeson a -> a
getAeson (Aeson a) = a

instance Aeson.ToJSON a => ToField (Aeson a) where
toField = toField . Aeson.encode . getAeson

instance (Aeson.FromJSON a, Typeable a) => FromField (Aeson a) where
fromField f bs = fmap Aeson (fromJSONField f bs)
45 changes: 45 additions & 0 deletions test/Main.hs
Expand Up @@ -3,10 +3,19 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DoAndIfThenElse #-}
{-# LANGUAGE ScopedTypeVariables #-}
#if __GLASGOW_HASKELL__ >= 806
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DeriveAnyClass #-}
#endif
module Main (main) where

import Common
import Database.PostgreSQL.Simple.Copy
import Database.PostgreSQL.Simple.ToField (ToField)
import Database.PostgreSQL.Simple.FromField (FromField)
import Database.PostgreSQL.Simple.HStore
import Database.PostgreSQL.Simple.Newtypes
import Database.PostgreSQL.Simple.Internal (breakOnSingleQuestionMark)
import Database.PostgreSQL.Simple.Types(Query(..),Values(..), PGArray(..))
import qualified Database.PostgreSQL.Simple.Transaction as ST
Expand Down Expand Up @@ -59,6 +68,8 @@ tests env = testGroup "tests"
, testCase "HStore" . testHStore
, testCase "citext" . testCIText
, testCase "JSON" . testJSON
, testCase "Aeson newtype" . testAeson
, testCase "DerivingVia" . testDerivingVia
, testCase "Question mark escape" . testQM
, testCase "Savepoint" . testSavepoint
, testCase "Unicode" . testUnicode
Expand Down Expand Up @@ -240,6 +251,40 @@ testJSON TestEnv{..} = do
js' <- query conn "SELECT ?::json" js
[js] @?= js'

testAeson :: TestEnv -> Assertion
testAeson TestEnv{..} = do
roundTrip (Map.fromList [] :: Map Text Text)
roundTrip (Map.fromList [("foo","bar"),("bar","baz"),("baz","hello")] :: Map Text Text)
roundTrip (Map.fromList [("fo\"o","bar"),("b\\ar","baz"),("baz","\"value\\with\"escapes")] :: Map Text Text)
roundTrip (V.fromList [1,2,3,4,5::Int])
roundTrip ("foo" :: Text)
roundTrip (42 :: Int)
where
roundTrip :: (Eq a, Show a, Typeable a, ToJSON a, FromJSON a)=> a -> Assertion
roundTrip x = do
y <- query conn "SELECT ?::json" (Only (Aeson x))
[Only (Aeson x)] @?= y

testDerivingVia :: TestEnv -> Assertion
testDerivingVia TestEnv{..} = do
#if __GLASGOW_HASKELL__ <806
return ()
#else
roundTrip $ DerivingVia1 42 "Meaning of Life"
where
roundTrip :: (Eq a, Show a, Typeable a, ToField a, FromField a)=> a -> Assertion
roundTrip x = do
y <- query conn "SELECT ?::json" (Only x)
[Only x] @?= y

data DerivingVia1 = DerivingVia1 Int String
deriving stock (Eq, Show, Generic)
deriving anyclass (FromJSON, ToJSON)
deriving (ToField, FromField) via Aeson DerivingVia1

#endif


testQM :: TestEnv -> Assertion
testQM TestEnv{..} = do
-- Just test on a single string
Expand Down

0 comments on commit 5bebb26

Please sign in to comment.