Skip to content

Commit

Permalink
Type error on upsert (#885)
Browse files Browse the repository at this point in the history
* Test suite compiles

* Move putMany into upsert specs

* Update documentation

* update changelogs

* Drop 7.10.3 support

* clean up postgres test warnings
  • Loading branch information
parsonsmatt committed Apr 11, 2019
1 parent ccb6dce commit 04d03e9
Show file tree
Hide file tree
Showing 46 changed files with 350 additions and 177 deletions.
1 change: 0 additions & 1 deletion .travis.yml
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,6 @@ services:

matrix:
include:
- env: ARGS="--resolver lts-6 --stack-yaml stack_lts-10.yaml"
- env: ARGS="--resolver lts-9 --stack-yaml stack_lts-10.yaml"
- env: ARGS="--resolver lts-11"
- env: ARGS="--resolver lts-12"
Expand Down
1 change: 1 addition & 0 deletions persistent-mongoDB/test/EmbedTestMongo.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# OPTIONS_GHC -fno-warn-unused-binds -fno-warn-orphans -O0 #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
Expand Down
1 change: 1 addition & 0 deletions persistent-mongoDB/test/EntityEmbedTestMongo.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE EmptyDataDecls #-}
Expand Down
4 changes: 1 addition & 3 deletions persistent-mongoDB/test/MongoInit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,7 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}

module MongoInit (
isTravis
, BackendMonad
BackendMonad
, runConn
, MonadIO
, persistSettings
Expand Down Expand Up @@ -71,7 +70,6 @@ import qualified Data.ByteString as BS
import Data.Text (Text)
import Database.Persist
import Database.Persist.TH ()
import System.Environment (getEnvironment)

import Database.Persist.Sql (PersistFieldSql(..))
import Database.Persist.TH (mkPersistSettings)
Expand Down
1 change: 1 addition & 0 deletions persistent-mongoDB/test/main.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# language RankNTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
Expand Down
1 change: 1 addition & 0 deletions persistent-mysql/test/InsertDuplicateUpdate.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# OPTIONS_GHC -fno-warn-unused-binds -fno-warn-orphans -O0 #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE EmptyDataDecls #-}
Expand Down
1 change: 1 addition & 0 deletions persistent-mysql/test/main.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}
Expand Down
8 changes: 2 additions & 6 deletions persistent-postgresql/test/ArrayAggTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,20 +18,16 @@

module ArrayAggTest where

import PgInit

import qualified Data.Text as T
import Data.List (sort)
import Control.Monad.IO.Class (MonadIO)
import Data.Aeson
import qualified Data.Vector as V (fromList)
import Test.Hspec.Expectations ()

import PersistentTestModels

import Database.Persist
import Database.Persist.Postgresql.JSON

import PgInit

share [mkPersist persistSettings, mkMigrate "jsonTestMigrate"] [persistLowerCase|
TestValue
json Value
Expand Down
1 change: 1 addition & 0 deletions persistent-postgresql/test/EquivalentTypeTestPostgres.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
Expand Down
26 changes: 3 additions & 23 deletions persistent-postgresql/test/PgInit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,7 @@
{-# LANGUAGE TemplateHaskell #-}

module PgInit (
BackendMonad
, runConn
runConn

, MonadIO
, persistSettings
Expand All @@ -17,7 +16,6 @@ module PgInit (
, BackendKey(..)
, GenerateKey(..)

, RunDb
-- re-exports
, (A.<$>), (A.<*>)
, module Database.Persist
Expand All @@ -33,13 +31,7 @@ module PgInit (
, module Database.Persist.Sql
, BS.ByteString
, SomeException
, MonadFail
, TestFn(..)
, truncateTimeOfDay
, truncateToMicro
, truncateUTCTime
, arbText
, liftA2
, module Init
) where

Expand All @@ -52,12 +44,7 @@ import Init
)

-- re-exports
import Control.Applicative (liftA2)
import Test.QuickCheck.Instances ()
import Data.Char (generalCategory, GeneralCategory(..))
import qualified Data.Text as T
import Data.Fixed (Pico,Micro)
import Data.Time
import Control.Applicative as A ((<$>), (<*>))
import Control.Exception (SomeException)
import Control.Monad (void, replicateM, liftM, when, forM_)
Expand All @@ -66,15 +53,15 @@ import Database.Persist.TH (mkPersist, mkMigrate, share, sqlSettings, persistLow
import Database.Persist.Sql.Raw.QQ
import Test.Hspec
import Data.Aeson (Value(..))
import Database.Persist.Postgresql.JSON
import Database.Persist.Postgresql.JSON ()
import qualified Data.HashMap.Strict as HM

-- testing
import Test.HUnit ((@?=),(@=?), Assertion, assertFailure, assertBool)
import Test.QuickCheck

import qualified Data.ByteString as BS
import Data.Text (Text, unpack)
import Data.Text (Text)
import Database.Persist
import Database.Persist.TH ()
import System.Environment (getEnvironment)
Expand All @@ -87,8 +74,6 @@ import System.Log.FastLogger (fromLogStr)
import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
import Database.Persist.Postgresql
import Data.IORef (newIORef, IORef, writeIORef, readIORef)
import System.IO.Unsafe (unsafePerformIO)

import Control.Monad (unless, (>=>))
import Control.Monad.IO.Unlift (MonadUnliftIO)
Expand All @@ -111,7 +96,6 @@ dockerPg = do

persistSettings :: MkPersistSettings
persistSettings = sqlSettings { mpsGeneric = True }
type BackendMonad = SqlBackend

runConn :: MonadUnliftIO m => SqlPersistT (LoggingT m) t -> m ()
runConn f = do
Expand All @@ -130,10 +114,6 @@ db :: SqlPersistT (LoggingT (ResourceT IO)) () -> Assertion
db actions = do
runResourceT $ runConn $ actions >> transactionUndo

keyCounter :: IORef Int64
keyCounter = unsafePerformIO $ newIORef 1
{-# NOINLINE keyCounter #-}

instance Arbitrary Value where
arbitrary = frequency [ (1, pure Null)
, (1, Bool <$> arbitrary)
Expand Down
1 change: 1 addition & 0 deletions persistent-postgresql/test/main.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}
Expand Down
7 changes: 4 additions & 3 deletions persistent-redis/tests/basic-test.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
{-# LANGUAGE TypeFamilies, EmptyDataDecls, GADTs #-}
{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, GeneralizedNewtypeDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
module Main where

import qualified Database.Redis as R
Expand All @@ -12,7 +13,7 @@ import Control.Monad.IO.Class (liftIO)
import Data.Text (Text, pack, unpack)

let redisSettings = mkPersistSettings (ConT ''RedisBackend)
in share [mkPersist redisSettings] [persistLowerCase|
in share [mkPersist redisSettings] [persistLowerCase|
Person
name String
age Int
Expand All @@ -34,7 +35,7 @@ mkKey s = case keyFromValues [PersistText s] of
Left a -> fail (unpack a)

main :: IO ()
main =
main =
withRedisConn redisConf $ runRedisPool $ do
_ <- liftIO $ print "Inserting..."
s <- insert $ Person "Test" 12
Expand All @@ -45,4 +46,4 @@ main =
g <- get key :: RedisT IO (Maybe Person)
liftIO $ print g
delete s
return ()
return ()
12 changes: 2 additions & 10 deletions persistent-sqlite/test/SqliteInit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ module SqliteInit (
, truncateUTCTime
, arbText
, liftA2
, MonadFail
) where

import Init
Expand All @@ -57,12 +58,7 @@ import Init
)

-- re-exports
import Control.Applicative (liftA2)
import Test.QuickCheck.Instances ()
import Data.Char (generalCategory, GeneralCategory(..))
import qualified Data.Text as T
import Data.Fixed (Pico,Micro)
import Data.Time
import Control.Applicative as A ((<$>), (<*>))
import Control.Exception (SomeException)
import Control.Monad (void, replicateM, liftM, when, forM_)
Expand All @@ -72,22 +68,18 @@ import Test.Hspec

-- testing
import Test.HUnit ((@?=),(@=?), Assertion, assertFailure, assertBool)
import Test.QuickCheck

import qualified Data.ByteString as BS
import Data.Text (Text, unpack)
import Data.Text (Text)
import Database.Persist
import Database.Persist.TH ()
import System.Environment (getEnvironment)

import Control.Monad.Logger
import Control.Monad.Trans.Resource (ResourceT, runResourceT)
import Database.Persist.Sql
import System.Log.FastLogger (fromLogStr)

import Database.Persist.Sqlite
import Data.IORef (newIORef, IORef, writeIORef, readIORef)
import System.IO.Unsafe (unsafePerformIO)

import Control.Monad (unless, (>=>))
import Control.Monad.IO.Unlift (MonadUnliftIO)
Expand Down
1 change: 1 addition & 0 deletions persistent-sqlite/test/main.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}
Expand Down
4 changes: 4 additions & 0 deletions persistent-template/ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
## 2.7.0

* Depends on `persistent-2.10.0` which provides the `OnlyOneUniqueKey` and `AtLeastOneUniqueKey` classes. Automatically generates instances for these classes based on how many unique keys the entity definition gets. This changes requires `UndecidableInstances` to be enabled on each module that generates entity definitions. [#885](https://github.com/yesodweb/persistent/pull/885)

## 2.6.0
* [persistent#846](https://github.com/yesodweb/persistent/pull/846): Improve error message when marshalling fails
* [persistent#826](https://github.com/yesodweb/persistent/pull/826): Change `Unique` derive `Show`
Expand Down
Loading

0 comments on commit 04d03e9

Please sign in to comment.