Skip to content

Commit

Permalink
Merge branch 'master' into persist-entity-type-lits
Browse files Browse the repository at this point in the history
  • Loading branch information
danbroooks committed Mar 16, 2022
2 parents 929bc97 + aeaa4f6 commit cc95228
Show file tree
Hide file tree
Showing 30 changed files with 459 additions and 120 deletions.
3 changes: 2 additions & 1 deletion .github/workflows/haskell.yml
Original file line number Diff line number Diff line change
Expand Up @@ -45,13 +45,14 @@ jobs:
runs-on: ubuntu-latest
strategy:
matrix:
cabal: ["3.4"]
cabal: ["3.6"]
ghc:
- "8.4.4"
- "8.6.5"
- "8.8.4"
- "8.10.3"
- "9.0"
- "9.2.2"

env:
CONFIG: "--enable-tests --enable-benchmarks"
Expand Down
8 changes: 8 additions & 0 deletions persistent-mongoDB/ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,13 @@
# Changelog for persistent-mongoDB

## 2.13.0.1

* [#1367](https://github.com/yesodweb/persistent/pull/1367),
[#1366](https://github.com/yesodweb/persistent/pull/1367),
[#1338](https://github.com/yesodweb/persistent/pull/1338),
[#1335](https://github.com/yesodweb/persistent/pull/1335)
* Support GHC 9.2

## 2.13.0.0

* Fix persistent 2.13 changes [#1286](https://github.com/yesodweb/persistent/pull/1286)
Expand Down
2 changes: 1 addition & 1 deletion persistent-mongoDB/persistent-mongoDB.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: persistent-mongoDB
version: 2.13.0.0
version: 2.13.0.1
license: MIT
license-file: LICENSE
author: Greg Weber <greg@gregweber.info>
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 @@
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE DataKinds, ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
Expand Down
1 change: 1 addition & 0 deletions persistent-mongoDB/test/EntityEmbedTestMongo.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE DataKinds, ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuasiQuotes #-}
Expand Down
1 change: 1 addition & 0 deletions persistent-mongoDB/test/main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
Expand Down
13 changes: 13 additions & 0 deletions persistent-mysql/ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,18 @@
# Changelog for persistent-mysql

## 2.13.1.2

* [#1367](https://github.com/yesodweb/persistent/pull/1367),
[#1366](https://github.com/yesodweb/persistent/pull/1367),
[#1338](https://github.com/yesodweb/persistent/pull/1338),
[#1335](https://github.com/yesodweb/persistent/pull/1335)
* Support GHC 9.2

## 2.13.1.1

* [#1360](https://github.com/yesodweb/persistent/pull/1360)
* Fix anomalies in migration of integer columns in MySQL 8

## 2.13.1.0

* [#1341](https://github.com/yesodweb/persistent/pull/1341)
Expand Down
22 changes: 18 additions & 4 deletions persistent-mysql/Database/Persist/MySQL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -827,9 +827,19 @@ data ColumnInfo = ColumnInfo
-- @INFORMATION_SCHEMA@ tables.
parseColumnType :: Text -> ColumnInfo -> ExceptT String IO (SqlType, Maybe Integer)
-- Ints
parseColumnType "tinyint" ci | ciColumnType ci == "tinyint(1)" = return (SqlBool, Nothing)
parseColumnType "int" ci | ciColumnType ci == "int(11)" = return (SqlInt32, Nothing)
parseColumnType "bigint" ci | ciColumnType ci == "bigint(20)" = return (SqlInt64, Nothing)
-- The display width is deprecated and being removed in MySQL 8.X. To be
-- consistent with earlier versions, which do report it, accept either
-- the bare type in `ciColumnType ci`, or the type adorned with the expected
-- value for the display width (ie the defaults for int and bigint, or the
-- value explicitly set in `showSqlType` for SqlBool).
--
parseColumnType "tinyint" ci
| ciColumnType ci == "tinyint" || ciColumnType ci == "tinyint(1)" = return (SqlBool, Nothing)
parseColumnType "int" ci
| ciColumnType ci == "int" || ciColumnType ci == "int(11)" = return (SqlInt32, Nothing)
parseColumnType "bigint" ci
| ciColumnType ci == "bigint" || ciColumnType ci == "bigint(20)" = return (SqlInt64, Nothing)

-- Double
parseColumnType x@("double") ci | ciColumnType ci == x = return (SqlReal, Nothing)
parseColumnType "decimal" ci =
Expand Down Expand Up @@ -1013,10 +1023,14 @@ showSqlType :: SqlType
-> String
showSqlType SqlBlob Nothing _ = "BLOB"
showSqlType SqlBlob (Just i) _ = "VARBINARY(" ++ show i ++ ")"
-- "tinyint(1)" has been used historically here. In MySQL 8, the display width
-- is deprecated, and in the future it may need to be removed here. However,
-- "(1)" is not the default in older MySQL versions, so for them omitting it
-- would alter the exact form of the column type in the information_schema.
showSqlType SqlBool _ _ = "TINYINT(1)"
showSqlType SqlDay _ _ = "DATE"
showSqlType SqlDayTime _ _ = "DATETIME"
showSqlType SqlInt32 _ _ = "INT(11)"
showSqlType SqlInt32 _ _ = "INT"
showSqlType SqlInt64 _ _ = "BIGINT"
showSqlType SqlReal _ _ = "DOUBLE"
showSqlType (SqlNumeric s prec) _ _ = "NUMERIC(" ++ show s ++ "," ++ show prec ++ ")"
Expand Down
2 changes: 1 addition & 1 deletion persistent-mysql/persistent-mysql.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: persistent-mysql
version: 2.13.1.0
version: 2.13.1.2
license: MIT
license-file: LICENSE
author: Felipe Lessa <felipe.lessa@gmail.com>, Michael Snoyman
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 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
Expand Down
13 changes: 13 additions & 0 deletions persistent-postgresql/ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,18 @@
# Changelog for persistent-postgresql

## 2.13.5.0

* [#1362](https://github.com/yesodweb/persistent/pull/1362/)
* Define `withPostgresqlPoolModifiedWithVersion`

## 2.13.4.1

* [#1367](https://github.com/yesodweb/persistent/pull/1367),
[#1366](https://github.com/yesodweb/persistent/pull/1367),
[#1338](https://github.com/yesodweb/persistent/pull/1338),
[#1335](https://github.com/yesodweb/persistent/pull/1335)
* Support GHC 9.2

## 2.13.4.0

* [#1341](https://github.com/yesodweb/persistent/pull/1341)
Expand Down
35 changes: 34 additions & 1 deletion persistent-postgresql/Database/Persist/Postgresql.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,9 +26,14 @@
module Database.Persist.Postgresql
( withPostgresqlPool
, withPostgresqlPoolWithVersion
, withPostgresqlPoolWithConf

, withPostgresqlPoolModified
, withPostgresqlPoolModifiedWithVersion

, withPostgresqlConn
, withPostgresqlConnWithVersion
, withPostgresqlPoolWithConf

, createPostgresqlPool
, createPostgresqlPoolModified
, createPostgresqlPoolModifiedWithVersion
Expand Down Expand Up @@ -195,6 +200,34 @@ withPostgresqlPoolWithConf conf hooks = do
let logFuncToBackend = open' modConn getVer id (pgConnStr conf)
withSqlPoolWithConfig logFuncToBackend (postgresConfToConnectionPoolConfig conf)

-- | Same as 'withPostgresqlPool', but with the 'createPostgresqlPoolModified'
-- feature.
--
-- @since 2.13.5.0
withPostgresqlPoolModified
:: (MonadUnliftIO m, MonadLoggerIO m)
=> (PG.Connection -> IO ()) -- ^ Action to perform after connection is created.
-> ConnectionString -- ^ Connection string to the database.
-> Int -- ^ Number of connections to be kept open in the pool.
-> (Pool SqlBackend -> m t)
-> m t
withPostgresqlPoolModified = withPostgresqlPoolModifiedWithVersion getServerVersion

-- | Same as 'withPostgresqlPool', but with the
-- 'createPostgresqlPoolModifiedWithVersion' feature.
--
-- @since 2.13.5.0
withPostgresqlPoolModifiedWithVersion
:: (MonadUnliftIO m, MonadLoggerIO m)
=> (PG.Connection -> IO (Maybe Double)) -- ^ Action to perform to get the server version.
-> (PG.Connection -> IO ()) -- ^ Action to perform after connection is created.
-> ConnectionString -- ^ Connection string to the database.
-> Int -- ^ Number of connections to be kept open in the pool.
-> (Pool SqlBackend -> m t)
-> m t
withPostgresqlPoolModifiedWithVersion getVerDouble modConn ci = do
withSqlPool (open' modConn (oldGetVersionToNew getVerDouble) id ci)

-- | Create a PostgreSQL connection pool. Note that it's your
-- responsibility to properly close the connection pool when
-- unneeded. Use 'withPostgresqlPool' for an automatic resource
Expand Down
2 changes: 1 addition & 1 deletion persistent-postgresql/persistent-postgresql.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: persistent-postgresql
version: 2.13.4.0
version: 2.13.5.0
license: MIT
license-file: LICENSE
author: Felipe Lessa, Michael Snoyman <michael@snoyman.com>
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 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
Expand Down
8 changes: 8 additions & 0 deletions persistent-redis/ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,11 @@
## 2.13.0.1

* [#1367](https://github.com/yesodweb/persistent/pull/1367),
[#1366](https://github.com/yesodweb/persistent/pull/1367),
[#1338](https://github.com/yesodweb/persistent/pull/1338),
[#1335](https://github.com/yesodweb/persistent/pull/1335)
* Support GHC 9.2

## 2.13.0.0

* [#1123](https://github.com/yesodweb/persistent/pull/1223):
Expand Down
28 changes: 14 additions & 14 deletions persistent-redis/persistent-redis.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: persistent-redis
version: 2.13.0.0
version: 2.13.0.1
license: BSD3
license-file: LICENSE
author: Pavel Ryzhov <paul@paulrz.cz>
Expand All @@ -21,7 +21,7 @@ library
, persistent >= 2.12 && < 3.0
, aeson >= 1.0
, binary >= 0.8 && < 0.9
, bytestring >= 0.10.8 && < 0.11
, bytestring >= 0.10.8 && < 0.12
, hedis >= 0.9
, http-api-data
, mtl >= 2.2.1 && < 2.3
Expand All @@ -47,22 +47,22 @@ library
test-suite basic
type: exitcode-stdio-1.0
main-is: tests/basic-test.hs
build-depends: base >= 4.9 && < 5
, persistent >= 2.10 && < 3.0
build-depends: base
, persistent
, persistent-redis
, aeson >= 1.0
, bytestring >= 0.10.8 && < 0.11
, binary >= 0.8 && < 0.9
, hedis >= 0.9
, aeson
, bytestring
, binary
, hedis
, http-api-data
, mtl >= 2.2.1 && < 2.3
, path-pieces >= 0.2
, mtl
, path-pieces
, scientific
, template-haskell
, text >= 1.2
, time >= 1.6
, transformers >= 0.5 && < 0.6
, utf8-string >= 1.0 && < 1.1
, text
, time
, transformers
, utf8-string

other-modules: Database.Persist.Redis
Database.Persist.Redis.Config
Expand Down
9 changes: 9 additions & 0 deletions persistent-test/ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,14 @@
## Unreleased changes

## 2.13.1.2

* [#1367](https://github.com/yesodweb/persistent/pull/1367),
[#1366](https://github.com/yesodweb/persistent/pull/1367),
[#1338](https://github.com/yesodweb/persistent/pull/1338),
[#1335](https://github.com/yesodweb/persistent/pull/1335)
* Support GHC 9.2
* Test migration idempotency on additional integer types [#1359](https://github.com/yesodweb/persistent/pull/1359)

## 2.13.1.0

* Support `persistent-2.13.3.0` [#1341](https://github.com/yesodweb/persistent/pull/1341)
Expand Down
2 changes: 1 addition & 1 deletion persistent-test/persistent-test.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: persistent-test
version: 2.13.1.0
version: 2.13.1.2
license: MIT
license-file: LICENSE
author: Michael Snoyman <michael@snoyman.com>
Expand Down
2 changes: 1 addition & 1 deletion persistent-test/src/DataTypeTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ cleanDB'
cleanDB' = deleteWhere ([] :: [Filter (DataTypeTableGeneric backend)])

roundFn :: RealFrac a => a -> Integer
roundFn = round
roundFn = truncate

roundTime :: TimeOfDay -> TimeOfDay
roundTime t = timeToTimeOfDay $ fromIntegral $ roundFn $ timeOfDayToTime t
Expand Down
5 changes: 4 additions & 1 deletion persistent-test/src/MigrationIdempotencyTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,20 +2,23 @@
{-# LANGUAGE UndecidableInstances #-}
module MigrationIdempotencyTest where

import Data.Int (Int32, Int64)
import qualified Data.Text as T

import Database.Persist.TH
import Init

share [mkPersist sqlSettings, mkMigrate "migration"] [persistLowerCase|
Idempotency
field1 Int
field1 Int64
field2 T.Text sqltype=varchar(5)
field3 T.Text sqltype=mediumtext
field4 T.Text sqltype=longtext
field5 T.Text sqltype=mediumblob
field6 T.Text sqltype=longblob
field7 Double sqltype=double(6,5)
field8 Int32
field9 Bool
|]

specsWith :: (MonadIO m) => RunDb SqlBackend m -> Spec
Expand Down
22 changes: 22 additions & 0 deletions persistent/ChangeLog.md
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,28 @@

* [#1264](https://github.com/yesodweb/persistent/pull/1264)
* Support declaring Maybe before the type in model definitions
* [#1370](https://github.com/yesodweb/persistent/pull/1370)
* Add spec to assert Persistent.TH is the only import required when defining entities

## 2.13.3.3

* [#1369](https://github.com/yesodweb/persistent/pull/1369)
* Fix `withObject` needing to be imported

## 2.13.3.2

* [#1315](https://github.com/yesodweb/persistent/pull/1315)
* Refactor entity constraint parsing in Quasi module

## 2.13.3.1

* [#1367](https://github.com/yesodweb/persistent/pull/1367),
[#1366](https://github.com/yesodweb/persistent/pull/1367),
[#1338](https://github.com/yesodweb/persistent/pull/1338),
[#1335](https://github.com/yesodweb/persistent/pull/1335)
* Support GHC 9.2
* [#1356](https://github.com/yesodweb/persistent/pull/1356)
* Improve parse errors in generated FromJSON instances

## 2.13.3.0

Expand Down
Loading

0 comments on commit cc95228

Please sign in to comment.