Script 'mail_helper' called by obssrc Hello community, here is the log from the commit of package ghc-persistent for openSUSE:Factory checked in at 2021-07-10 22:54:31 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/ghc-persistent (Old) and /work/SRC/openSUSE:Factory/.ghc-persistent.new.2625 (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "ghc-persistent" Sat Jul 10 22:54:31 2021 rev:30 rq:905305 version:2.13.1.1 Changes: -------- --- /work/SRC/openSUSE:Factory/ghc-persistent/ghc-persistent.changes 2021-06-23 17:38:34.524499838 +0200 +++ /work/SRC/openSUSE:Factory/.ghc-persistent.new.2625/ghc-persistent.changes 2021-07-10 22:55:01.139519369 +0200 @@ -1,0 +2,25 @@ +Thu Jul 1 12:50:46 UTC 2021 - psim...@suse.com + +- Update persistent to version 2.13.1.1. + ## 2.13.1.1 + + * [#1294](https://github.com/yesodweb/persistent/pull/1294) + * Fix an issue where documentation comments on fields are in reverse line + order. + + ## 2.13.1.0 + + * [#1264](https://github.com/yesodweb/persistent/pull/1264) + * Support declaring Maybe before the type in model definitions + +------------------------------------------------------------------- +Thu Jun 24 11:30:26 UTC 2021 - psim...@suse.com + +- Update persistent to version 2.13.0.4. + ## 2.13.0.4 + + * [#1277](https://github.com/yesodweb/persistent/pull/1277) + * Corrected the documentation of `addMigration` to match the actual + behaviour - this will not change the behaviour of your code. + +------------------------------------------------------------------- Old: ---- persistent-2.13.0.3.tar.gz New: ---- persistent-2.13.1.1.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ ghc-persistent.spec ++++++ --- /var/tmp/diff_new_pack.Y4q26G/_old 2021-07-10 22:55:01.507516529 +0200 +++ /var/tmp/diff_new_pack.Y4q26G/_new 2021-07-10 22:55:01.511516498 +0200 @@ -19,7 +19,7 @@ %global pkg_name persistent %bcond_with tests Name: ghc-%{pkg_name} -Version: 2.13.0.3 +Version: 2.13.1.1 Release: 0 Summary: Type-safe, multi-backend data serialization License: MIT ++++++ persistent-2.13.0.3.tar.gz -> persistent-2.13.1.1.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/ChangeLog.md new/persistent-2.13.1.1/ChangeLog.md --- old/persistent-2.13.0.3/ChangeLog.md 2021-06-19 00:03:31.000000000 +0200 +++ new/persistent-2.13.1.1/ChangeLog.md 2021-06-29 19:52:18.000000000 +0200 @@ -1,5 +1,22 @@ # Changelog for persistent +## 2.13.1.1 + +* [#1294](https://github.com/yesodweb/persistent/pull/1294) + * Fix an issue where documentation comments on fields are in reverse line + order. + +## 2.13.1.0 + +* [#1264](https://github.com/yesodweb/persistent/pull/1264) + * Support declaring Maybe before the type in model definitions + +## 2.13.0.4 + +* [#1277](https://github.com/yesodweb/persistent/pull/1277) + * Corrected the documentation of `addMigration` to match the actual + behaviour - this will not change the behaviour of your code. + ## 2.13.0.3 * [#1287](https://github.com/yesodweb/persistent/pull/1287) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/FieldDef.hs new/persistent-2.13.1.1/Database/Persist/FieldDef.hs --- old/persistent-2.13.0.3/Database/Persist/FieldDef.hs 2021-05-05 23:10:13.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/FieldDef.hs 2021-06-29 16:23:53.000000000 +0200 @@ -9,6 +9,8 @@ , overFieldAttrs , addFieldAttr -- ** Helpers + , isFieldNullable + , isFieldMaybe , isFieldNotGenerated , isHaskellField -- * 'FieldCascade' @@ -22,9 +24,12 @@ import Database.Persist.FieldDef.Internal import Database.Persist.Types.Base - ( isHaskellField - , FieldAttr - ) + ( FieldAttr(..) + , FieldType(..) + , IsNullable(..) + , fieldAttrsContainsNullable + , isHaskellField + ) -- | Replace the 'FieldDef' 'FieldAttr' with the new list. -- @@ -43,3 +48,21 @@ -- @since 2.13.0.0 addFieldAttr :: FieldAttr -> FieldDef -> FieldDef addFieldAttr fa = overFieldAttrs (fa :) + +-- | Check if the field definition is nullable +-- +-- @since 2.13.0.0 +isFieldNullable :: FieldDef -> IsNullable +isFieldNullable = + fieldAttrsContainsNullable . fieldAttrs + +-- | Check if the field is `Maybe a` +-- +-- @since 2.13.0.0 +isFieldMaybe :: FieldDef -> Bool +isFieldMaybe field = + case fieldType field of + FTApp (FTTypeCon _ "Maybe") _ -> + True + _ -> + False diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/Quasi/Internal.hs new/persistent-2.13.1.1/Database/Persist/Quasi/Internal.hs --- old/persistent-2.13.0.3/Database/Persist/Quasi/Internal.hs 2021-06-19 00:03:31.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/Quasi/Internal.hs 2021-06-29 19:52:18.000000000 +0200 @@ -19,7 +19,6 @@ , upperCaseSettings , lowerCaseSettings , toFKNameInfixed - , nullable , Token (..) , Line (..) , preparse @@ -40,6 +39,7 @@ , UnboundCompositeDef(..) , UnboundIdDef(..) , unbindFieldDef + , isUnboundFieldNullable , unboundIdDefToFieldDef , PrimarySpec(..) , mkAutoIdField' @@ -77,6 +77,7 @@ PSFail err -> Left $ "PSFail " ++ err other -> Left $ show other where + parseApplyFT :: Text -> ParseState FieldType parseApplyFT t = case goMany id t of PSSuccess (ft:fts) t' -> PSSuccess (foldl' FTApp ft fts) t' @@ -93,6 +94,7 @@ (x, y) -> PSFail $ show (b, x, y) x -> PSFail $ show x + parse1 :: Text -> ParseState FieldType parse1 t = case T.uncons t of Nothing -> PSDone @@ -105,6 +107,7 @@ in PSSuccess (parseFieldTypePiece c a) b | otherwise -> PSFail $ show (c, t') + goMany :: ([FieldType] -> a) -> Text -> ParseState a goMany front t = case parse1 t of PSSuccess x t' -> goMany (front . (x:)) t' @@ -217,12 +220,14 @@ let (token, rest) = T.break isSpace t in Token token : tokenize rest where + findMidToken :: Text -> Maybe (Text, Text) findMidToken t' = case T.break (== '=') t' of (x, T.drop 1 -> y) | "\"" `T.isPrefixOf` y || "(" `T.isPrefixOf` y -> Just (x, y) _ -> Nothing + quotes :: Text -> ([Text] -> [Text]) -> [Token] quotes t' front | T.null t' = error $ T.unpack $ T.concat $ "Unterminated quoted string starting with " : front [] @@ -232,6 +237,8 @@ | otherwise = let (x, y) = T.break (`elem` ['\\','\"']) t' in quotes y (front . (x:)) + + parens :: Int -> Text -> ([Text] -> [Text]) -> [Token] parens count t' front | T.null t' = error $ T.unpack $ T.concat $ "Unterminated parens string starting with " : front [] @@ -376,7 +383,7 @@ else lwc : lwc' : lwcs - + minimumIndentOf :: LinesWithComments -> Int minimumIndentOf = lowestIndent . lwcLines -- | An 'EntityDef' produced by the QuasiQuoter. It contains information that @@ -563,6 +570,10 @@ fieldGenerated fd } +isUnboundFieldNullable :: UnboundFieldDef -> IsNullable +isUnboundFieldNullable = + fieldAttrsContainsNullable . unboundFieldAttrs + -- | The specification for how an entity's primary key should be formed. -- -- Persistent requires that every table have a primary key. By default, an @@ -691,22 +702,13 @@ textAttribs cols :: [UnboundFieldDef] - cols = reverse . fst . foldr k ([], []) $ reverse attribs - - k x (!acc, !comments) = - case listToMaybe x of - Just (DocComment comment) -> - (acc, comment : comments) - _ -> - case (setFieldComments comments <$> takeColsEx ps (tokenText <$> x)) of - Just sm -> - (sm : acc, []) - Nothing -> - (acc, []) + cols = reverse . fst . foldr (associateComments ps) ([], []) $ reverse attribs + autoIdField :: FieldDef autoIdField = mkAutoIdField ps entNameHS idSqlType + idSqlType :: SqlType idSqlType = maybe SqlInt64 (const $ SqlOther "Primary Key") primaryComposite @@ -777,6 +779,22 @@ Just $ fieldType fd } +associateComments + :: PersistSettings + -> [Token] + -> ([UnboundFieldDef], [Text]) + -> ([UnboundFieldDef], [Text]) +associateComments ps x (!acc, !comments) = + case listToMaybe x of + Just (DocComment comment) -> + (acc, comment : comments) + _ -> + case (setFieldComments (reverse comments) <$> takeColsEx ps (tokenText <$> x)) of + Just sm -> + (sm : acc, []) + Nothing -> + (acc, []) + setFieldComments :: [Text] -> UnboundFieldDef -> UnboundFieldDef setFieldComments xs fld = case xs of @@ -1359,13 +1377,6 @@ takeDerives ("deriving":rest) = Just rest takeDerives _ = Nothing -nullable :: [FieldAttr] -> IsNullable -nullable s - | FieldAttrMaybe `elem` s = Nullable ByMaybeAttr - | FieldAttrNullable `elem` s = Nullable ByNullableAttr - | otherwise = NotNullable - - -- | Returns 'True' if the 'UnboundFieldDef' does not have a 'MigrationOnly' or -- 'SafeToRemove' flag from the QuasiQuoter. -- diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/Quasi.hs new/persistent-2.13.1.1/Database/Persist/Quasi.hs --- old/persistent-2.13.0.3/Database/Persist/Quasi.hs 2021-05-05 23:10:13.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/Quasi.hs 2021-06-29 16:23:53.000000000 +0200 @@ -366,6 +366,37 @@ Foreign User fk_noti_user sentToFirst sentToSecond References emailFirst emailSecond @ += Nullable Fields + +As illustrated in the example at the beginning of this page, we are able to represent nullable +fields by including 'Maybe' at the end of the type declaration: + +> TableName +> fieldName FieldType +> otherField String +> nullableField Int Maybe + +Alternatively we can specify the keyword nullable: + +> TableName +> fieldName FieldType +> otherField String +> nullableField Int nullable + +However the difference here is in the first instance the Haskell type will be 'Maybe Int', +but in the second it will be 'Int'. Be aware that this will cause runtime errors if the +database returns `NULL` and the `PersistField` instance does not handle `PersistNull`. + +If you wish to define your Maybe types in a way that is similar to the actual Haskell +definition, you can define 'Maybe Int' like so: + +> TableName +> fieldName FieldType +> otherField String +> nullableField (Maybe Int) + +However, note, the field _must_ be enclosed in parenthesis. + = Documentation Comments The quasiquoter supports ordinary comments with @--@ and @#@. @@ -417,7 +448,6 @@ , PersistSettings , upperCaseSettings , lowerCaseSettings - , nullable -- ** Getters and Setters , module Database.Persist.Quasi ) where diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/Sql/Class.hs new/persistent-2.13.1.1/Database/Persist/Sql/Class.hs --- old/persistent-2.13.0.3/Database/Persist/Sql/Class.hs 2021-05-24 17:18:53.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/Sql/Class.hs 2021-06-29 16:23:53.000000000 +0200 @@ -1237,6 +1237,8 @@ sqlType _ = SqlTime instance PersistFieldSql UTCTime where sqlType _ = SqlDayTime +instance PersistFieldSql a => PersistFieldSql (Maybe a) where + sqlType _ = sqlType (Proxy :: Proxy a) instance {-# OVERLAPPABLE #-} PersistFieldSql a => PersistFieldSql [a] where sqlType _ = SqlString instance PersistFieldSql a => PersistFieldSql (V.Vector a) where diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/Sql/Internal.hs new/persistent-2.13.1.1/Database/Persist/Sql/Internal.hs --- old/persistent-2.13.0.3/Database/Persist/Sql/Internal.hs 2021-05-05 23:10:13.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/Sql/Internal.hs 2021-06-29 16:23:53.000000000 +0200 @@ -20,7 +20,6 @@ import Data.Maybe (fromMaybe, listToMaybe, mapMaybe) import Database.Persist.EntityDef -import Database.Persist.Quasi import Database.Persist.Sql.Types import Database.Persist.Types @@ -140,7 +139,10 @@ go fd = Column { cName = fieldDB fd - , cNull = nullable (fieldAttrs fd) /= NotNullable || isEntitySum t + , cNull = + case isFieldNullable fd of + Nullable _ -> True + NotNullable -> isFieldMaybe fd || isEntitySum t , cSqlType = fieldSqlType fd , cDefault = defaultAttribute $ fieldAttrs fd , cGenerated = fieldGenerated fd diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/Sql/Migration.hs new/persistent-2.13.1.1/Database/Persist/Sql/Migration.hs --- old/persistent-2.13.0.3/Database/Persist/Sql/Migration.hs 2021-05-05 23:10:13.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/Sql/Migration.hs 2021-06-23 23:48:21.000000000 +0200 @@ -22,20 +22,20 @@ import Control.Exception (throwIO) import Control.Monad (liftM, unless) import Control.Monad.IO.Unlift -import Control.Monad.Trans.Class (MonadTrans (..)) -import Control.Monad.Trans.Reader (ReaderT (..), ask) +import Control.Monad.Trans.Class (MonadTrans(..)) +import Control.Monad.Trans.Reader (ReaderT(..), ask) import Control.Monad.Trans.Writer -import Data.Text (Text, unpack, snoc, isPrefixOf, pack) +import Data.Text (Text, isPrefixOf, pack, snoc, unpack) import qualified Data.Text.IO +import GHC.Stack import System.IO import System.IO.Silently (hSilence) -import GHC.Stack +import Database.Persist.Sql.Orphan.PersistStore () +import Database.Persist.Sql.Raw import Database.Persist.Sql.Types import Database.Persist.Sql.Types.Internal -import Database.Persist.Sql.Raw import Database.Persist.Types -import Database.Persist.Sql.Orphan.PersistStore() allSql :: CautiousMigration -> [Sql] allSql = map snd @@ -195,12 +195,14 @@ -- @since 2.9.2 addMigration :: Bool - -- ^ Is the migration safe to run? (eg a non-destructive and idempotent - -- update on the schema) + -- ^ Is the migration unsafe to run? (eg a destructive or non-idempotent + -- update on the schema). If 'True', the migration is *unsafe*, and will + -- need to be run manually later. If 'False', the migration is *safe*, and + -- can be run any number of times. -> Sql -- ^ A 'Text' value representing the command to run on the database. -> Migration -addMigration isSafe sql = lift (tell [(isSafe, sql)]) +addMigration isUnsafe sql = lift (tell [(isUnsafe, sql)]) -- | Add a 'CautiousMigration' (aka a @[('Bool', 'Text')]@) to the -- migration plan. diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/Sql/Types.hs new/persistent-2.13.1.1/Database/Persist/Sql/Types.hs --- old/persistent-2.13.0.3/Database/Persist/Sql/Types.hs 2021-05-24 17:18:53.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/Sql/Types.hs 2021-06-23 23:48:21.000000000 +0200 @@ -63,7 +63,10 @@ type Sql = Text --- Bool indicates if the Sql is safe +-- | A list of SQL operations, marked with a safety flag. If the 'Bool' is +-- 'True', then the operation is *unsafe* - it might be destructive, or +-- otherwise not idempotent. If the 'Bool' is 'False', then the operation +-- is *safe*, and can be run repeatedly without issues. type CautiousMigration = [(Bool, Sql)] -- | A 'Migration' is a four level monad stack consisting of: diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/TH.hs new/persistent-2.13.1.1/Database/Persist/TH.hs --- old/persistent-2.13.0.3/Database/Persist/TH.hs 2021-06-19 00:03:31.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/TH.hs 2021-06-29 16:23:53.000000000 +0200 @@ -71,8 +71,6 @@ import Prelude hiding (concat, exp, splitAt, take, (++)) -import GHC.Stack (HasCallStack) -import Data.Coerce import Control.Monad import Data.Aeson ( FromJSON(parseJSON) @@ -86,6 +84,7 @@ ) import qualified Data.ByteString as BS import Data.Char (toLower, toUpper) +import Data.Coerce import Data.Data (Data) import Data.Either import qualified Data.HashMap.Strict as HM @@ -104,6 +103,7 @@ import qualified Data.Text.Encoding as TE import Data.Typeable (Typeable) import GHC.Generics (Generic) +import GHC.Stack (HasCallStack) import GHC.TypeLits import Instances.TH.Lift () -- Bring `Lift (fmap k v)` instance into scope, as well as `Lift Text` @@ -387,14 +387,14 @@ , withDbName parentFieldStore ffrTargetField ) fixForeignNullable = - all ((NotNullable /=) . isFieldNullable) foreignFieldNames + all ((NotNullable /=) . isForeignNullable) foreignFieldNames where - isFieldNullable fieldNameHS = + isForeignNullable fieldNameHS = case getFieldDef fieldNameHS fieldStore of Nothing -> error "Field name not present in map" Just a -> - nullable (unboundFieldAttrs a) + isUnboundFieldNullable a fieldStore = mkFieldStore unboundEnt @@ -1093,7 +1093,7 @@ error $ unpack $ "Column not found: " ++ s ++ " in unique " ++ unConstraintNameHS constr lookup3 x (fd:rest) | x == unFieldNameHS (unboundFieldNameHS fd) = - (fd, nullable $ unboundFieldAttrs fd) + (fd, isUnboundFieldNullable fd) | otherwise = lookup3 x rest @@ -2273,7 +2273,7 @@ { depTarget = name , depSourceTable = entityHaskell (unboundEntityDef def) , depSourceField = unboundFieldNameHS field - , depSourceNull = nullable (unboundFieldAttrs field) + , depSourceNull = isUnboundFieldNullable field } Nothing -> [] @@ -2607,7 +2607,7 @@ entityName = mkEntityNameHSName (getUnboundEntityNameHS ued) maybeNullable :: UnboundFieldDef -> Bool -maybeNullable fd = nullable (unboundFieldAttrs fd) == Nullable ByMaybeAttr +maybeNullable fd = isUnboundFieldNullable fd == Nullable ByMaybeAttr ftToType :: FieldType -> Type ftToType = \case @@ -3125,7 +3125,7 @@ nullSetting = isNull fd isNull = - (NotNullable /=) . nullable . unboundFieldAttrs + (NotNullable /=) . isUnboundFieldNullable in if all ((nullSetting ==) . isNull) fds then nullSetting diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/Types/Base.hs new/persistent-2.13.1.1/Database/Persist/Types/Base.hs --- old/persistent-2.13.0.3/Database/Persist/Types/Base.hs 2021-05-05 23:10:13.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/Types/Base.hs 2021-06-29 16:23:53.000000000 +0200 @@ -108,6 +108,12 @@ | NotNullable deriving (Eq, Show) +fieldAttrsContainsNullable :: [FieldAttr] -> IsNullable +fieldAttrsContainsNullable s + | FieldAttrMaybe `elem` s = Nullable ByMaybeAttr + | FieldAttrNullable `elem` s = Nullable ByNullableAttr + | otherwise = NotNullable + -- | The reason why a field is 'nullable' is very important. A -- field that is nullable because of a @Maybe@ tag will have its -- type changed from @A@ to @Maybe A@. OTOH, a field that is diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/Database/Persist/Types.hs new/persistent-2.13.1.1/Database/Persist/Types.hs --- old/persistent-2.13.0.3/Database/Persist/Types.hs 2021-05-05 23:10:13.000000000 +0200 +++ new/persistent-2.13.1.1/Database/Persist/Types.hs 2021-06-29 16:23:53.000000000 +0200 @@ -16,43 +16,43 @@ , OverflowNatural(..) ) where -import Database.Persist.Names -import Database.Persist.Class.PersistField import Database.Persist.Class.PersistEntity +import Database.Persist.Class.PersistField import Database.Persist.EntityDef import Database.Persist.FieldDef +import Database.Persist.Names import Database.Persist.PersistValue -- this module is a bit of a kitchen sink of types and concepts. the guts of -- persistent, just strewn across the table. in 2.13 let's get this cleaned up -- and a bit more tidy. import Database.Persist.Types.Base - ( FieldCascade(..) - , ForeignDef(..) - , CascadeAction(..) - , FieldDef(..) - , UniqueDef(..) - , FieldAttr(..) - , IsNullable(..) - , WhyNullable(..) - , ExtraLine - , Checkmark(..) - , FieldType(..) - , PersistException(..) - , ForeignFieldDef - , Attr - , CompositeDef(..) - , SqlType(..) - , ReferenceDef(..) - , noCascade - , parseFieldAttrs - , keyAndEntityFields - , PersistException(..) - , UpdateException(..) - , PersistValue(..) - , PersistFilter(..) - , PersistUpdate(..) - , EmbedEntityDef(..) - , EmbedFieldDef(..) - , LiteralType(..) - ) + ( Attr + , CascadeAction(..) + , Checkmark(..) + , CompositeDef(..) + , EmbedEntityDef(..) + , EmbedFieldDef(..) + , ExtraLine + , FieldAttr(..) + , FieldCascade(..) + , FieldDef(..) + , FieldType(..) + , ForeignDef(..) + , ForeignFieldDef + , IsNullable(..) + , LiteralType(..) + , PersistException(..) + , PersistFilter(..) + , PersistUpdate(..) + , PersistValue(..) + , ReferenceDef(..) + , SqlType(..) + , UniqueDef(..) + , UpdateException(..) + , WhyNullable(..) + , fieldAttrsContainsNullable + , keyAndEntityFields + , noCascade + , parseFieldAttrs + ) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/persistent.cabal new/persistent-2.13.1.1/persistent.cabal --- old/persistent-2.13.0.3/persistent.cabal 2021-06-19 00:03:31.000000000 +0200 +++ new/persistent-2.13.1.1/persistent.cabal 2021-06-29 19:52:18.000000000 +0200 @@ -1,5 +1,5 @@ name: persistent -version: 2.13.0.3 +version: 2.13.1.1 license: MIT license-file: LICENSE author: Michael Snoyman <mich...@snoyman.com> @@ -167,11 +167,13 @@ Database.Persist.TH.PersistWith.Model Database.Persist.TH.PersistWith.Model2 Database.Persist.TH.PersistWithSpec + Database.Persist.TH.CommentSpec Database.Persist.TH.ImplicitIdColSpec Database.Persist.TH.JsonEncodingSpec Database.Persist.TH.KindEntitiesSpec Database.Persist.TH.KindEntitiesSpecImports Database.Persist.TH.MigrationOnlySpec + Database.Persist.TH.MaybeFieldDefsSpec Database.Persist.TH.MultiBlockSpec Database.Persist.TH.MultiBlockSpec.Model Database.Persist.TH.OverloadedLabelSpec diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/test/Database/Persist/TH/CommentSpec.hs new/persistent-2.13.1.1/test/Database/Persist/TH/CommentSpec.hs --- old/persistent-2.13.0.3/test/Database/Persist/TH/CommentSpec.hs 1970-01-01 01:00:00.000000000 +0100 +++ new/persistent-2.13.1.1/test/Database/Persist/TH/CommentSpec.hs 2021-06-29 19:52:18.000000000 +0200 @@ -0,0 +1,64 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ExistentialQuantification #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} + +module Database.Persist.TH.CommentSpec where + +import TemplateTestImports + +import Database.Persist.EntityDef.Internal (EntityDef(..)) +import Database.Persist.FieldDef.Internal (FieldDef(..)) + +mkPersist sqlSettings [persistLowerCase| + +-- | Doc comments work. +-- | Has multiple lines. +CommentModel + -- | First line of comment on column. + -- | Second line of comment on column. + name String + + deriving Eq Show + +|] + +pass :: IO () +pass = pure () + +asIO :: IO a -> IO a +asIO = id + +spec :: Spec +spec = describe "CommentSpec" $ do + let + ed = + entityDef (Proxy @CommentModel) + it "has entity comments" $ do + entityComments ed + `shouldBe` do + Just $ mconcat + [ "Doc comments work.\n" + , "Has multiple lines.\n" + ] + + describe "fieldComments" $ do + let + [nameComments] = + map fieldComments $ entityFields ed + it "has the right name comments" $ do + nameComments + `shouldBe` do + Just $ mconcat + [ "First line of comment on column.\n" + , "Second line of comment on column.\n" + ] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/test/Database/Persist/TH/MaybeFieldDefsSpec.hs new/persistent-2.13.1.1/test/Database/Persist/TH/MaybeFieldDefsSpec.hs --- old/persistent-2.13.0.3/test/Database/Persist/TH/MaybeFieldDefsSpec.hs 1970-01-01 01:00:00.000000000 +0100 +++ new/persistent-2.13.1.1/test/Database/Persist/TH/MaybeFieldDefsSpec.hs 2021-06-29 16:23:53.000000000 +0200 @@ -0,0 +1,30 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE OverloadedLabels #-} +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE UndecidableInstances #-} + +module Database.Persist.TH.MaybeFieldDefsSpec where + +import TemplateTestImports + +mkPersist sqlSettings [persistLowerCase| +Account + name (Maybe String) + email String +|] + +spec :: Spec +spec = describe "MaybeFieldDefs" $ do + it "should support literal `Maybe` declaration in entity definition" $ do + let mkAccount :: Maybe String -> String -> Account + mkAccount = Account + compiles + +compiles :: Expectation +compiles = True `shouldBe` True diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/persistent-2.13.0.3/test/Database/Persist/THSpec.hs new/persistent-2.13.1.1/test/Database/Persist/THSpec.hs --- old/persistent-2.13.0.3/test/Database/Persist/THSpec.hs 2021-06-19 00:03:31.000000000 +0200 +++ new/persistent-2.13.1.1/test/Database/Persist/THSpec.hs 2021-06-29 19:52:18.000000000 +0200 @@ -53,16 +53,14 @@ import qualified Database.Persist.TH.ImplicitIdColSpec as ImplicitIdColSpec import qualified Database.Persist.TH.JsonEncodingSpec as JsonEncodingSpec import qualified Database.Persist.TH.KindEntitiesSpec as KindEntitiesSpec +import qualified Database.Persist.TH.MaybeFieldDefsSpec as MaybeFieldDefsSpec import qualified Database.Persist.TH.MigrationOnlySpec as MigrationOnlySpec import qualified Database.Persist.TH.MultiBlockSpec as MultiBlockSpec import qualified Database.Persist.TH.OverloadedLabelSpec as OverloadedLabelSpec import qualified Database.Persist.TH.SharedPrimaryKeyImportedSpec as SharedPrimaryKeyImportedSpec import qualified Database.Persist.TH.SharedPrimaryKeySpec as SharedPrimaryKeySpec import qualified Database.Persist.TH.ToFromPersistValuesSpec as ToFromPersistValuesSpec -import qualified Database.Persist.TH.KindEntitiesSpec as KindEntitiesSpec -import qualified Database.Persist.TH.OverloadedLabelSpec as OverloadedLabelSpec -import qualified Database.Persist.TH.SharedPrimaryKeyImportedSpec as SharedPrimaryKeyImportedSpec -import qualified Database.Persist.TH.SharedPrimaryKeySpec as SharedPrimaryKeySpec +import qualified Database.Persist.TH.CommentSpec as CommentSpec -- test to ensure we can have types ending in Id that don't trash the TH -- machinery @@ -179,6 +177,7 @@ SharedPrimaryKeySpec.spec SharedPrimaryKeyImportedSpec.spec ImplicitIdColSpec.spec + MaybeFieldDefsSpec.spec MigrationOnlySpec.spec EmbedSpec.spec DiscoverEntitiesSpec.spec @@ -186,6 +185,7 @@ ForeignRefSpec.spec ToFromPersistValuesSpec.spec JsonEncodingSpec.spec + CommentSpec.spec describe "TestDefaultKeyCol" $ do let EntityIdField FieldDef{..} = entityId (entityDef (Proxy @TestDefaultKeyCol))