Script 'mail_helper' called by obssrc
Hello community,

here is the log from the commit of package ghc-unix-time for openSUSE:Factory 
checked in at 2023-07-12 17:27:38
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-unix-time (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-unix-time.new.8922 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-unix-time"

Wed Jul 12 17:27:38 2023 rev:20 rq:1098252 version:0.4.10

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-unix-time/ghc-unix-time.changes      
2023-04-04 21:24:36.810621659 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-unix-time.new.8922/ghc-unix-time.changes    
2023-07-12 17:28:06.570817706 +0200
@@ -1,0 +2,6 @@
+Tue Jul  4 02:47:47 UTC 2023 - Peter Simons <psim...@suse.com>
+
+- Update unix-time to version 0.4.10.
+  Upstream does not provide a change log file.
+
+-------------------------------------------------------------------

Old:
----
  unix-time-0.4.9.tar.gz

New:
----
  unix-time-0.4.10.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-unix-time.spec ++++++
--- /var/tmp/diff_new_pack.luDHd4/_old  2023-07-12 17:28:07.162821805 +0200
+++ /var/tmp/diff_new_pack.luDHd4/_new  2023-07-12 17:28:07.166821833 +0200
@@ -20,7 +20,7 @@
 %global pkgver %{pkg_name}-%{version}
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        0.4.9
+Version:        0.4.10
 Release:        0
 Summary:        Unix time parser/formatter and utilities
 License:        BSD-3-Clause
@@ -44,6 +44,8 @@
 BuildRequires:  ghc-hspec-prof
 BuildRequires:  ghc-old-locale-devel
 BuildRequires:  ghc-old-locale-prof
+BuildRequires:  ghc-template-haskell-devel
+BuildRequires:  ghc-template-haskell-prof
 BuildRequires:  ghc-time-devel
 BuildRequires:  ghc-time-prof
 %endif

++++++ unix-time-0.4.9.tar.gz -> unix-time-0.4.10.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/unix-time-0.4.9/Data/UnixTime/Conv.hs 
new/unix-time-0.4.10/Data/UnixTime/Conv.hs
--- old/unix-time-0.4.9/Data/UnixTime/Conv.hs   2001-09-09 03:46:40.000000000 
+0200
+++ new/unix-time-0.4.10/Data/UnixTime/Conv.hs  2001-09-09 03:46:40.000000000 
+0200
@@ -2,12 +2,17 @@
 {-# LANGUAGE OverloadedStrings #-}
 
 module Data.UnixTime.Conv (
-    formatUnixTime, formatUnixTimeGMT
-  , parseUnixTime, parseUnixTimeGMT
-  , webDateFormat, mailDateFormat
-  , fromEpochTime, toEpochTime
-  , fromClockTime, toClockTime
-  ) where
+    formatUnixTime,
+    formatUnixTimeGMT,
+    parseUnixTime,
+    parseUnixTimeGMT,
+    webDateFormat,
+    mailDateFormat,
+    fromEpochTime,
+    toEpochTime,
+    fromClockTime,
+    toClockTime,
+) where
 
 import Control.Applicative
 import Data.ByteString.Char8
@@ -18,23 +23,23 @@
 import Foreign.Marshal.Alloc
 import System.IO.Unsafe (unsafePerformIO)
 import System.Posix.Types (EpochTime)
-import System.Time (ClockTime(..))
+import System.Time (ClockTime (..))
 
 -- $setup
 -- >>> import Data.Function (on)
 -- >>> :set -XOverloadedStrings
 
 foreign import ccall unsafe "c_parse_unix_time"
-        c_parse_unix_time :: CString -> CString -> IO CTime
+    c_parse_unix_time :: CString -> CString -> IO CTime
 
 foreign import ccall unsafe "c_parse_unix_time_gmt"
-        c_parse_unix_time_gmt :: CString -> CString -> IO CTime
+    c_parse_unix_time_gmt :: CString -> CString -> IO CTime
 
 foreign import ccall unsafe "c_format_unix_time"
-        c_format_unix_time :: CString -> CTime -> CString -> CInt -> IO CSize
+    c_format_unix_time :: CString -> CTime -> CString -> CInt -> IO CSize
 
 foreign import ccall unsafe "c_format_unix_time_gmt"
-        c_format_unix_time_gmt :: CString -> CTime -> CString -> CInt -> IO 
CSize
+    c_format_unix_time_gmt :: CString -> CTime -> CString -> CInt -> IO CSize
 
 ----------------------------------------------------------------
 
@@ -44,13 +49,13 @@
 -- Many implementations of strptime_l() do not support %Z and
 -- some implementations of strptime_l() do not support %z, either.
 -- 'utMicroSeconds' is always set to 0.
-
 parseUnixTime :: Format -> ByteString -> UnixTime
 parseUnixTime fmt str = unsafePerformIO $
     useAsCString fmt $ \cfmt ->
         useAsCString str $ \cstr -> do
             sec <- c_parse_unix_time cfmt cstr
             return $ UnixTime sec 0
+
 -- |
 -- Parsing 'ByteString' to 'UnixTime' interpreting as GMT.
 -- This is a wrapper for strptime_l().
@@ -58,7 +63,6 @@
 --
 -- >>> parseUnixTimeGMT webDateFormat "Thu, 01 Jan 1970 00:00:00 GMT"
 -- UnixTime {utSeconds = 0, utMicroSeconds = 0}
-
 parseUnixTimeGMT :: Format -> ByteString -> UnixTime
 parseUnixTimeGMT fmt str = unsafePerformIO $
     useAsCString fmt $ \cfmt ->
@@ -73,8 +77,6 @@
 -- This is a wrapper for strftime_l().
 -- 'utMicroSeconds' is ignored.
 -- The result depends on the TZ environment variable.
---
-
 formatUnixTime :: Format -> UnixTime -> IO ByteString
 formatUnixTime fmt t =
     formatUnixTimeHelper c_format_unix_time fmt t
@@ -94,7 +96,6 @@
 -- True
 -- >>> ((==) `on` utMicroSeconds) ut ut'
 -- False
-
 formatUnixTimeGMT :: Format -> UnixTime -> ByteString
 formatUnixTimeGMT fmt t =
     unsafePerformIO $ formatUnixTimeHelper c_format_unix_time_gmt fmt t
@@ -102,7 +103,6 @@
 
 -- |
 -- Helper handling memory allocation for formatUnixTime and formatUnixTimeGMT.
-
 formatUnixTimeHelper
     :: (CString -> CTime -> CString -> CInt -> IO CSize)
     -> Format
@@ -111,8 +111,8 @@
 formatUnixTimeHelper formatFun fmt (UnixTime sec _) =
     useAsCString fmt $ \cfmt -> do
         let siz = 80
-        ptr  <- mallocBytes siz
-        len  <- fromIntegral <$> formatFun cfmt sec ptr (fromIntegral siz)
+        ptr <- mallocBytes siz
+        len <- fromIntegral <$> formatFun cfmt sec ptr (fromIntegral siz)
         ptr' <- reallocBytes ptr (len + 1)
         unsafePackMallocCString ptr' -- FIXME: Use unsafePackMallocCStringLen 
from bytestring-0.10.2.0
 
@@ -122,7 +122,6 @@
 -- Format for web (RFC 2616).
 -- The value is \"%a, %d %b %Y %H:%M:%S GMT\".
 -- This should be used with 'formatUnixTimeGMT' and 'parseUnixTimeGMT'.
-
 webDateFormat :: Format
 webDateFormat = "%a, %d %b %Y %H:%M:%S GMT"
 
@@ -130,7 +129,6 @@
 -- Format for e-mail (RFC 5322).
 -- The value is \"%a, %d %b %Y %H:%M:%S %z\".
 -- This should be used with 'formatUnixTime' and 'parseUnixTime'.
-
 mailDateFormat :: Format
 mailDateFormat = "%a, %d %b %Y %H:%M:%S %z"
 
@@ -138,19 +136,16 @@
 
 -- |
 -- From 'EpochTime' to 'UnixTime' setting 'utMicroSeconds' to 0.
-
 fromEpochTime :: EpochTime -> UnixTime
 fromEpochTime sec = UnixTime sec 0
 
 -- |
 -- From 'UnixTime' to 'EpochTime' ignoring 'utMicroSeconds'.
-
 toEpochTime :: UnixTime -> EpochTime
 toEpochTime (UnixTime sec _) = sec
 
 -- |
 -- From 'ClockTime' to 'UnixTime'.
-
 fromClockTime :: ClockTime -> UnixTime
 fromClockTime (TOD sec psec) = UnixTime sec' usec'
   where
@@ -159,7 +154,6 @@
 
 -- |
 -- From 'UnixTime' to 'ClockTime'.
-
 toClockTime :: UnixTime -> ClockTime
 toClockTime (UnixTime sec usec) = TOD sec' psec'
   where
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/unix-time-0.4.9/Data/UnixTime/Diff.hs 
new/unix-time-0.4.10/Data/UnixTime/Diff.hs
--- old/unix-time-0.4.9/Data/UnixTime/Diff.hs   2001-09-09 03:46:40.000000000 
+0200
+++ new/unix-time-0.4.10/Data/UnixTime/Diff.hs  2001-09-09 03:46:40.000000000 
+0200
@@ -1,14 +1,14 @@
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 
 module Data.UnixTime.Diff (
-    diffUnixTime
-  , addUnixDiffTime
-  , secondsToUnixDiffTime
-  , microSecondsToUnixDiffTime
-  ) where
+    diffUnixTime,
+    addUnixDiffTime,
+    secondsToUnixDiffTime,
+    microSecondsToUnixDiffTime,
+) where
 
-import Data.UnixTime.Types
 import Data.Int
+import Data.UnixTime.Types
 import Foreign.C.Types
 
 -- $setup
@@ -33,23 +33,22 @@
 -- UnixDiffTime {udtSeconds = -3, udtMicroSeconds = 0}
 -- >>> (3 :: UnixDiffTime) * 2
 -- UnixDiffTime {udtSeconds = 6, udtMicroSeconds = 0}
-
 instance Num UnixDiffTime where
-    UnixDiffTime s1 u1 + UnixDiffTime s2 u2 = calc (s1+s2) (u1+u2)
-    UnixDiffTime s1 u1 - UnixDiffTime s2 u2 = calc (s1-s2) (u1-u2)
-    UnixDiffTime s1 u1 * UnixDiffTime s2 u2 = calc' (s1*s2) (u1*u2)
+    UnixDiffTime s1 u1 + UnixDiffTime s2 u2 = calc (s1 + s2) (u1 + u2)
+    UnixDiffTime s1 u1 - UnixDiffTime s2 u2 = calc (s1 - s2) (u1 - u2)
+    UnixDiffTime s1 u1 * UnixDiffTime s2 u2 = calc' (s1 * s2) (u1 * u2)
     negate (UnixDiffTime s u) = UnixDiffTime (-s) (-u)
     abs (UnixDiffTime s u) = UnixDiffTime (abs s) (abs u)
     signum (UnixDiffTime s u)
-         | s == 0 && u == 0 = 0
-         | s > 0            = 1
-         | otherwise        = -1
+        | s == 0 && u == 0 = 0
+        | s > 0 = 1
+        | otherwise = -1
     fromInteger i = UnixDiffTime (fromInteger i) 0
 
 {-# RULES "Integral->UnixDiffTime" fromIntegral = secondsToUnixDiffTime #-}
 
 instance Real UnixDiffTime where
-        toRational = toFractional
+    toRational = toFractional
 
 {-# RULES "UnixDiffTime->Fractional" realToFrac = toFractional #-}
 
@@ -59,25 +58,21 @@
 --
 -- >>> UnixTime 100 2000 `diffUnixTime` UnixTime 98 2100
 -- UnixDiffTime {udtSeconds = 1, udtMicroSeconds = 999900}
---
-
 diffUnixTime :: UnixTime -> UnixTime -> UnixDiffTime
-diffUnixTime (UnixTime s1 u1) (UnixTime s2 u2) = calc (s1-s2) (u1-u2)
+diffUnixTime (UnixTime s1 u1) (UnixTime s2 u2) = calc (s1 - s2) (u1 - u2)
 
 -- | Adding difference to 'UnixTime'.
 --
 -- >>> UnixTime 100 2000 `addUnixDiffTime` microSecondsToUnixDiffTime 
((-1003000) :: Int)
 -- UnixTime {utSeconds = 98, utMicroSeconds = 999000}
-
 addUnixDiffTime :: UnixTime -> UnixDiffTime -> UnixTime
-addUnixDiffTime (UnixTime s1 u1) (UnixDiffTime s2 u2) = calcU (s1+s2) (u1+u2)
+addUnixDiffTime (UnixTime s1 u1) (UnixDiffTime s2 u2) = calcU (s1 + s2) (u1 + 
u2)
 
 -- | Creating difference from seconds.
 --
 -- >>> secondsToUnixDiffTime (100 :: Int)
 -- UnixDiffTime {udtSeconds = 100, udtMicroSeconds = 0}
-
-secondsToUnixDiffTime :: (Integral a) => a -> UnixDiffTime
+secondsToUnixDiffTime :: Integral a => a -> UnixDiffTime
 secondsToUnixDiffTime sec = UnixDiffTime (fromIntegral sec) 0
 {-# INLINE secondsToUnixDiffTime #-}
 
@@ -88,37 +83,36 @@
 --
 -- >>> microSecondsToUnixDiffTime ((-12345678) :: Int)
 -- UnixDiffTime {udtSeconds = -12, udtMicroSeconds = -345678}
-
-microSecondsToUnixDiffTime :: (Integral a) => a -> UnixDiffTime
+microSecondsToUnixDiffTime :: Integral a => a -> UnixDiffTime
 microSecondsToUnixDiffTime usec = calc (fromIntegral s) (fromIntegral u)
   where
-    (s,u) = secondMicro usec
+    (s, u) = secondMicro usec
 {-# INLINE microSecondsToUnixDiffTime #-}
 
 ----------------------------------------------------------------
 
 adjust :: CTime -> Int32 -> (CTime, Int32)
 adjust sec usec
-  | sec >= 0  = ajp
-  | otherwise = ajm
+    | sec >= 0 = ajp
+    | otherwise = ajm
   where
-    micro  = 1000000
-    mmicro = - micro
+    micro = 1000000
+    mmicro = -micro
     ajp
-     | usec >= micro  = (sec + 1, usec - micro)
-     | usec >= 0      = (sec, usec)
-     | otherwise      = (sec - 1, usec + micro)
+        | usec >= micro = (sec + 1, usec - micro)
+        | usec >= 0 = (sec, usec)
+        | otherwise = (sec - 1, usec + micro)
     ajm
-     | usec <= mmicro = (sec - 1, usec + micro)
-     | usec <= 0      = (sec, usec)
-     | otherwise      = (sec + 1, usec - micro)
+        | usec <= mmicro = (sec - 1, usec + micro)
+        | usec <= 0 = (sec, usec)
+        | otherwise = (sec + 1, usec - micro)
 
 slowAdjust :: CTime -> Int32 -> (CTime, Int32)
 slowAdjust sec usec = (sec + fromIntegral s, usec - u)
   where
-    (s,u) = secondMicro usec
+    (s, u) = secondMicro usec
 
-secondMicro :: Integral a => a -> (a,a)
+secondMicro :: Integral a => a -> (a, a)
 secondMicro usec = usec `quotRem` 1000000
 
 toFractional :: Fractional a => UnixDiffTime -> a
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/unix-time-0.4.9/Data/UnixTime.hs 
new/unix-time-0.4.10/Data/UnixTime.hs
--- old/unix-time-0.4.9/Data/UnixTime.hs        2001-09-09 03:46:40.000000000 
+0200
+++ new/unix-time-0.4.10/Data/UnixTime.hs       2001-09-09 03:46:40.000000000 
+0200
@@ -1,31 +1,36 @@
 module Data.UnixTime (
-  -- * Data structure
-    UnixTime(..)
-  -- * Getting time
-  , getUnixTime
-  -- * Parsing and formatting time
-  , parseUnixTime
-  , parseUnixTimeGMT
-  , formatUnixTime
-  , formatUnixTimeGMT
-  -- * Format
-  , Format
-  , webDateFormat
-  , mailDateFormat
-  -- * Difference time
-  , UnixDiffTime(..)
-  , diffUnixTime
-  , addUnixDiffTime
-  , secondsToUnixDiffTime
-  , microSecondsToUnixDiffTime
-  -- * Translating time
-  , fromEpochTime
-  , toEpochTime
-  , fromClockTime
-  , toClockTime
-  ) where
+    -- * Data structure
+    UnixTime (..),
+
+    -- * Getting time
+    getUnixTime,
+
+    -- * Parsing and formatting time
+    parseUnixTime,
+    parseUnixTimeGMT,
+    formatUnixTime,
+    formatUnixTimeGMT,
+
+    -- * Format
+    Format,
+    webDateFormat,
+    mailDateFormat,
+
+    -- * Difference time
+    UnixDiffTime (..),
+    diffUnixTime,
+    addUnixDiffTime,
+    secondsToUnixDiffTime,
+    microSecondsToUnixDiffTime,
+
+    -- * Translating time
+    fromEpochTime,
+    toEpochTime,
+    fromClockTime,
+    toClockTime,
+) where
 
 import Data.UnixTime.Conv
+import Data.UnixTime.Diff
 import Data.UnixTime.Sys
 import Data.UnixTime.Types
-import Data.UnixTime.Diff
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/unix-time-0.4.9/test/UnixTimeSpec.hs 
new/unix-time-0.4.10/test/UnixTimeSpec.hs
--- old/unix-time-0.4.9/test/UnixTimeSpec.hs    2001-09-09 03:46:40.000000000 
+0200
+++ new/unix-time-0.4.10/test/UnixTimeSpec.hs   2001-09-09 03:46:40.000000000 
+0200
@@ -1,4 +1,7 @@
-{-# LANGUAGE OverloadedStrings, FlexibleInstances, CPP #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE TemplateHaskell #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 
 module UnixTimeSpec (main, spec) where
@@ -9,9 +12,10 @@
 import Data.Time
 import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
 import Data.UnixTime
-import Foreign.Ptr (Ptr)
 import Foreign.Marshal.Alloc (alloca)
+import Foreign.Ptr (Ptr)
 import Foreign.Storable (peek, poke)
+import qualified Language.Haskell.TH as TH (runIO)
 import Test.Hspec
 import Test.Hspec.QuickCheck (prop)
 import Test.QuickCheck hiding ((===))
@@ -25,12 +29,13 @@
 
 instance Arbitrary UnixTime where
     arbitrary = do
-        a <- choose (0,4294967295) :: Gen Int
-        b <- choose (0,999999) :: Gen Int
-        let ut = UnixTime {
-                utSeconds = abs (fromIntegral a)
-              , utMicroSeconds = fromIntegral b
-              }
+        a <- choose (0, 4294967295) :: Gen Int
+        b <- choose (0, 999999) :: Gen Int
+        let ut =
+                UnixTime
+                    { utSeconds = abs (fromIntegral a)
+                    , utMicroSeconds = fromIntegral b
+                    }
         return ut
 
 spec :: Spec
@@ -46,32 +51,44 @@
     describe "parseUnixTimeGMT & formatUnixTimeGMT" $ do
         let (===) = (==) `on` utSeconds
         prop "inverses the result" $ \ut ->
-            let dt  = formatUnixTimeGMT webDateFormat ut
-                ut' = parseUnixTimeGMT  webDateFormat dt
+            let dt = formatUnixTimeGMT webDateFormat ut
+                ut' = parseUnixTimeGMT webDateFormat dt
                 dt' = formatUnixTimeGMT webDateFormat ut'
-            in ut === ut' && dt == dt'
+             in ut === ut' && dt == dt'
         prop "inverses the result (2)" $ \ut ->
             let str = formatUnixTimeGMT "%s" ut
                 ut' = parseUnixTimeGMT "%s" str
-            in ut === ut'
+             in ut === ut'
 
     describe "addUnixDiffTime & diffUnixTime" $
         prop "invrses the result" $ \(ut0, ut1) ->
             let ut0' = addUnixDiffTime ut1 $ diffUnixTime ut0 ut1
                 ut1' = addUnixDiffTime ut0 $ diffUnixTime ut1 ut0
-            in ut0' == ut0 && ut1' == ut1
+             in ut0' == ut0 && ut1' == ut1
 
     describe "UnixTime Storable instance" $
         prop "peek . poke = id" $ \ut ->
             let pokePeek :: Ptr UnixTime -> IO UnixTime
                 pokePeek ptr = poke ptr ut >> peek ptr
-            in shouldReturn (alloca pokePeek) ut
+             in shouldReturn (alloca pokePeek) ut
+
+    describe "getUnixTime" $ do
+        it "works well" $ do
+            x <- getUnixTime
+            x `shouldBe` x
+        it "should work in Template Haskell" $
+            $( do
+                time <- TH.runIO getUnixTime
+                let b = time == time
+                [|b|]
+             )
+                `shouldBe` True
 
 formatMailModel :: UTCTime -> TimeZone -> ByteString
 formatMailModel ut zone = BS.pack $ formatTime defaultTimeLocale fmt zt
   where
-   zt = utcToZonedTime zone ut
-   fmt = BS.unpack mailDateFormat
+    zt = utcToZonedTime zone ut
+    fmt = BS.unpack mailDateFormat
 
 toUTCTime :: UnixTime -> UTCTime
 toUTCTime = posixSecondsToUTCTime . realToFrac . toEpochTime
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/unix-time-0.4.9/unix-time.cabal 
new/unix-time-0.4.10/unix-time.cabal
--- old/unix-time-0.4.9/unix-time.cabal 2001-09-09 03:46:40.000000000 +0200
+++ new/unix-time-0.4.10/unix-time.cabal        2001-09-09 03:46:40.000000000 
+0200
@@ -1,6 +1,6 @@
 cabal-version:      1.18
 name:               unix-time
-version:            0.4.9
+version:            0.4.10
 license:            BSD3
 license-file:       LICENSE
 maintainer:         Kazu Yamamoto <k...@iij.ad.jp>
@@ -51,6 +51,19 @@
     if impl(ghc >=7.8)
         cc-options: -fPIC
 
+    -- GHC 9.4.5, 9.6.1, and 9.6.2 on Windows do not link against mingwex, but
+    -- unix-time implicitly depends on this library due to the use of the
+    -- gettimeofday() function, which comes from mingwex on Windows. To avoid
+    -- linker errors in the absence of a mingwex dependency (see
+    -- https://gitlab.haskell.org/ghc/ghc/-/issues/23533 for an example of
+    -- this), we depend on mingwex explicitly here.
+    --
+    -- Other versions of GHC on Windows already depend on mingwex, so we guard
+    -- this behind appropriate conditionals.
+    if os(windows)
+        if (impl(ghc >= 9.4.5) && !impl(ghc >= 9.4.6)) || (impl(ghc >= 9.6.1) 
&& !impl(ghc >= 9.6.3))
+            extra-libraries: mingwex
+
     if os(windows)
         c-sources:
             cbits/strftime.c
@@ -71,6 +84,7 @@
         old-locale,
         old-time,
         QuickCheck,
+        template-haskell,
         time,
         unix-time,
         hspec >=2.6

Reply via email to