Hello community,
here is the log from the commit of package ghc-conduit-combinators for
openSUSE:Factory checked in at 2017-03-03 17:48:53
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-conduit-combinators (Old)
and /work/SRC/openSUSE:Factory/.ghc-conduit-combinators.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "ghc-conduit-combinators"
Fri Mar 3 17:48:53 2017 rev:9 rq:461617 version:1.1.0
Changes:
--------
---
/work/SRC/openSUSE:Factory/ghc-conduit-combinators/ghc-conduit-combinators.changes
2017-01-12 15:47:58.682098866 +0100
+++
/work/SRC/openSUSE:Factory/.ghc-conduit-combinators.new/ghc-conduit-combinators.changes
2017-03-03 17:48:54.104112306 +0100
@@ -1,0 +2,5 @@
+Sun Feb 12 14:12:30 UTC 2017 - [email protected]
+
+- Update to version 1.1.0 with cabal2obs.
+
+-------------------------------------------------------------------
Old:
----
conduit-combinators-1.0.8.3.tar.gz
New:
----
conduit-combinators-1.1.0.tar.gz
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Other differences:
------------------
++++++ ghc-conduit-combinators.spec ++++++
--- /var/tmp/diff_new_pack.8tyiHH/_old 2017-03-03 17:48:54.680030970 +0100
+++ /var/tmp/diff_new_pack.8tyiHH/_new 2017-03-03 17:48:54.684030405 +0100
@@ -1,7 +1,7 @@
#
# spec file for package ghc-conduit-combinators
#
-# Copyright (c) 2016 SUSE LINUX GmbH, Nuernberg, Germany.
+# Copyright (c) 2017 SUSE LINUX GmbH, Nuernberg, Germany.
#
# All modifications and additions to the file contributed by third parties
# remain the property of their copyright owners, unless otherwise agreed
@@ -19,7 +19,7 @@
%global pkg_name conduit-combinators
%bcond_with tests
Name: ghc-%{pkg_name}
-Version: 1.0.8.3
+Version: 1.1.0
Release: 0
Summary: Commonly used conduit functions, for both chunked and
unchunked data
License: MIT
++++++ conduit-combinators-1.0.8.3.tar.gz -> conduit-combinators-1.1.0.tar.gz
++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/conduit-combinators-1.0.8.3/ChangeLog.md
new/conduit-combinators-1.1.0/ChangeLog.md
--- old/conduit-combinators-1.0.8.3/ChangeLog.md 2016-11-28
11:23:00.000000000 +0100
+++ new/conduit-combinators-1.1.0/ChangeLog.md 2017-01-22 10:30:06.000000000
+0100
@@ -1,3 +1,9 @@
+# 1.1.0
+
+* Don't generalize I/O functions to `IOData`, instead specialize to
+ `ByteString`. See:
+ http://www.snoyman.com/blog/2016/12/beware-of-readfile#real-world-failures
+
# 1.0.8.3
* Fix version bounds for chunked-data/mono-traversable combos
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore'
old/conduit-combinators-1.0.8.3/Data/Conduit/Combinators/Stream.hs
new/conduit-combinators-1.1.0/Data/Conduit/Combinators/Stream.hs
--- old/conduit-combinators-1.0.8.3/Data/Conduit/Combinators/Stream.hs
2016-11-28 11:23:00.000000000 +0100
+++ new/conduit-combinators-1.1.0/Data/Conduit/Combinators/Stream.hs
2017-01-22 10:30:06.000000000 +0100
@@ -12,7 +12,6 @@
( yieldManyS
, repeatMS
, repeatWhileMS
- , sourceHandleS
, foldl1S
, allS
, anyS
@@ -43,12 +42,10 @@
import Control.Monad (liftM)
import Control.Monad.Base (MonadBase (liftBase))
-import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Primitive (PrimMonad)
import Data.Builder
import Data.Conduit.Internal.Fusion
import Data.Conduit.Internal.List.Stream (foldS)
-import Data.IOData
import Data.Maybe (isNothing, isJust)
import Data.MonoTraversable
#if ! MIN_VERSION_base(4,8,0)
@@ -59,7 +56,6 @@
import qualified Data.Vector.Generic as V
import qualified Data.Vector.Generic.Mutable as VM
import Prelude
-import System.IO (Handle)
#if MIN_VERSION_mono_traversable(1,0,0)
import Data.Sequences (LazySequence (..))
@@ -102,17 +98,6 @@
else Stop ()
{-# INLINE repeatWhileMS #-}
-sourceHandleS :: (MonadIO m, MonoFoldable a, IOData a) => Handle ->
StreamProducer m a
-sourceHandleS h _ =
- Stream step (return ())
- where
- step () = do
- x <- liftIO (hGetChunk h)
- return $ if onull x
- then Stop ()
- else Emit () x
-{-# INLINE sourceHandleS #-}
-
foldl1S :: Monad m
=> (a -> a -> a)
-> StreamConsumer a m (Maybe a)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore'
old/conduit-combinators-1.0.8.3/Data/Conduit/Combinators/Unqualified.hs
new/conduit-combinators-1.1.0/Data/Conduit/Combinators/Unqualified.hs
--- old/conduit-combinators-1.0.8.3/Data/Conduit/Combinators/Unqualified.hs
2016-11-28 11:23:00.000000000 +0100
+++ new/conduit-combinators-1.1.0/Data/Conduit/Combinators/Unqualified.hs
2017-01-22 10:30:06.000000000 +0100
@@ -24,10 +24,10 @@
, replicateMC
-- *** I\/O
- , sourceFile
+ , CC.sourceFile
, CC.sourceFileBS
- , sourceHandle
- , sourceIOHandle
+ , CC.sourceHandle
+ , CC.sourceIOHandle
, stdinC
-- *** Random numbers
@@ -109,10 +109,10 @@
, foldMapMCE
-- *** I\/O
- , sinkFile
+ , CC.sinkFile
, CC.sinkFileBS
- , sinkHandle
- , sinkIOHandle
+ , CC.sinkHandle
+ , CC.sinkIOHandle
, printC
, stdoutC
, stderrC
@@ -187,19 +187,11 @@
import Data.Builder
import qualified Data.NonNull as NonNull
import qualified Data.Traversable
-#if ! MIN_VERSION_base(4,8,0)
-import Control.Applicative ((<$>))
-#else
-import Prelude ((<$>))
-#endif
import Control.Monad.Base (MonadBase (..))
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Primitive (PrimMonad, PrimState)
import Control.Monad.Trans.Resource (MonadResource, MonadThrow)
import Data.Conduit
-import qualified Data.Conduit.List as CL
-import Data.IOData
-import Data.Maybe (fromMaybe)
import Data.Monoid (Monoid (..))
import Data.MonoTraversable
import qualified Data.Sequences as Seq
@@ -209,8 +201,6 @@
Ord (..), Functor (..), Either
(..),
Enum, Show, Char, FilePath)
import Data.Word (Word8)
-import qualified Prelude
-import System.IO (Handle)
import qualified System.IO as SIO
import Data.ByteString (ByteString)
import Data.Text (Text)
@@ -324,39 +314,10 @@
replicateMC = CC.replicateM
{-# INLINE replicateMC #-}
--- | Read all data from the given file.
---
--- This function automatically opens and closes the file handle, and ensures
--- exception safety via @MonadResource. It works for all instances of @IOData@,
--- including @ByteString@ and @Text@.
---
--- Since 1.0.0
-sourceFile :: (MonadResource m, IOData a, MonoFoldable a) => FilePath ->
Producer m a
-sourceFile = CC.sourceFile
-{-# INLINE sourceFile #-}
-
--- | Read all data from the given @Handle@.
---
--- Does not close the @Handle@ at any point.
---
--- Since 1.0.0
-sourceHandle :: (MonadIO m, IOData a, MonoFoldable a) => Handle -> Producer m a
-sourceHandle = CC.sourceHandle
-{-# INLINE sourceHandle #-}
-
--- | Open a @Handle@ using the given function and stream data from it.
---
--- Automatically closes the file at completion.
---
--- Since 1.0.0
-sourceIOHandle :: (MonadResource m, IOData a, MonoFoldable a) => SIO.IO Handle
-> Producer m a
-sourceIOHandle = CC.sourceIOHandle
-{-# INLINE sourceIOHandle #-}
-
-- | @sourceHandle@ applied to @stdin@.
--
-- Since 1.0.0
-stdinC :: (MonadIO m, IOData a, MonoFoldable a) => Producer m a
+stdinC :: MonadIO m => Producer m ByteString
stdinC = CC.stdin
{-# INLINE stdinC #-}
@@ -1007,35 +968,6 @@
foldMapMCE = CC.foldMapME
{-# INLINE foldMapMCE #-}
--- | Write all data to the given file.
---
--- This function automatically opens and closes the file handle, and ensures
--- exception safety via @MonadResource. It works for all instances of @IOData@,
--- including @ByteString@ and @Text@.
---
--- Since 1.0.0
-sinkFile :: (MonadResource m, IOData a) => FilePath -> Consumer a m ()
-sinkFile = CC.sinkFile
-{-# INLINE sinkFile #-}
-
--- | Write all data to the given @Handle@.
---
--- Does not close the @Handle@ at any point.
---
--- Since 1.0.0
-sinkHandle :: (MonadIO m, IOData a) => Handle -> Consumer a m ()
-sinkHandle = CC.sinkHandle
-{-# INLINE sinkHandle #-}
-
--- | Open a @Handle@ using the given function and stream data to it.
---
--- Automatically closes the file at completion.
---
--- Since 1.0.0
-sinkIOHandle :: (MonadResource m, IOData a) => SIO.IO Handle -> Consumer a m ()
-sinkIOHandle = CC.sinkIOHandle
-{-# INLINE sinkIOHandle #-}
-
-- | Print all incoming values to stdout.
--
-- Since 1.0.0
@@ -1046,14 +978,14 @@
-- | @sinkHandle@ applied to @stdout@.
--
-- Since 1.0.0
-stdoutC :: (MonadIO m, IOData a) => Consumer a m ()
+stdoutC :: MonadIO m => Consumer ByteString m ()
stdoutC = CC.stdout
{-# INLINE stdoutC #-}
-- | @sinkHandle@ applied to @stderr@.
--
-- Since 1.0.0
-stderrC :: (MonadIO m, IOData a) => Consumer a m ()
+stderrC :: MonadIO m => Consumer ByteString m ()
stderrC = CC.stderr
{-# INLINE stderrC #-}
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore'
old/conduit-combinators-1.0.8.3/Data/Conduit/Combinators.hs
new/conduit-combinators-1.1.0/Data/Conduit/Combinators.hs
--- old/conduit-combinators-1.0.8.3/Data/Conduit/Combinators.hs 2016-11-28
11:23:00.000000000 +0100
+++ new/conduit-combinators-1.1.0/Data/Conduit/Combinators.hs 2017-01-22
10:30:06.000000000 +0100
@@ -214,10 +214,11 @@
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Resource (MonadResource, MonadThrow)
import Data.Conduit
+import Data.Conduit.Binary (sourceFile, sourceHandle,
sourceIOHandle,
+ sinkFile, sinkHandle,
sinkIOHandle)
import qualified Data.Conduit.Filesystem as CF
import Data.Conduit.Internal (ConduitM (..), Pipe (..))
import qualified Data.Conduit.List as CL
-import Data.IOData
import Data.Maybe (fromMaybe, isNothing, isJust)
import Data.Monoid (Monoid (..))
import Data.MonoTraversable
@@ -414,17 +415,6 @@
-> Producer m a
INLINE_RULE(replicateM, n m, CL.replicateM n m)
--- | Read all data from the given file.
---
--- This function automatically opens and closes the file handle, and ensures
--- exception safety via @MonadResource@. It works for all instances of
@IOData@,
--- including @ByteString@ and @Text@.
---
--- Since 1.0.0
-sourceFile :: (MonadResource m, IOData a, MonoFoldable a) => FilePath ->
Producer m a
-sourceFile fp = sourceIOHandle (SIO.openFile fp SIO.ReadMode)
-{-# INLINE sourceFile #-}
-
-- | 'sourceFile' specialized to 'ByteString' to help with type
-- inference.
--
@@ -433,40 +423,12 @@
sourceFileBS = sourceFile
{-# INLINE sourceFileBS #-}
--- | Read all data from the given @Handle@.
---
--- Does not close the @Handle@ at any point.
---
--- Subject to fusion
---
--- Since 1.0.0
-sourceHandle, sourceHandleC :: (MonadIO m, IOData a, MonoFoldable a) => Handle
-> Producer m a
-sourceHandleC h =
- loop
- where
- loop = do
- x <- liftIO (hGetChunk h)
- if onull x
- then return ()
- else yield x >> loop
-{-# INLINEABLE sourceHandleC #-}
-STREAMING(sourceHandle, sourceHandleC, sourceHandleS, h)
-
--- | Open a @Handle@ using the given function and stream data from it.
---
--- Automatically closes the file at completion.
---
--- Since 1.0.0
-sourceIOHandle :: (MonadResource m, IOData a, MonoFoldable a) => SIO.IO Handle
-> Producer m a
-sourceIOHandle alloc = bracketP alloc SIO.hClose sourceHandle
-{-# INLINE sourceIOHandle #-}
-
-- | @sourceHandle@ applied to @stdin@.
--
-- Subject to fusion
--
-- Since 1.0.0
-stdin :: (MonadIO m, IOData a, MonoFoldable a) => Producer m a
+stdin :: MonadIO m => Producer m ByteString
INLINE_RULE0(stdin, sourceHandle SIO.stdin)
-- | Create an infinite stream of random values, seeding from the system random
@@ -1321,17 +1283,6 @@
-> Consumer mono m w
INLINE_RULE(foldMapME, f, CL.foldM (ofoldlM (\accum e -> mappend accum `liftM`
f e)) mempty)
--- | Write all data to the given file.
---
--- This function automatically opens and closes the file handle, and ensures
--- exception safety via @MonadResource@. It works for all instances of
@IOData@,
--- including @ByteString@ and @Text@.
---
--- Since 1.0.0
-sinkFile :: (MonadResource m, IOData a) => FilePath -> Consumer a m ()
-sinkFile fp = sinkIOHandle (SIO.openFile fp SIO.WriteMode)
-{-# INLINE sinkFile #-}
-
-- | 'sinkFile' specialized to 'ByteString' to help with type
-- inference.
--
@@ -1353,7 +1304,7 @@
-- Subject to fusion
--
-- Since 1.0.0
-stdout :: (MonadIO m, IOData a) => Consumer a m ()
+stdout :: MonadIO m => Consumer ByteString m ()
INLINE_RULE0(stdout, sinkHandle SIO.stdout)
-- | @sinkHandle@ applied to @stderr@.
@@ -1361,28 +1312,9 @@
-- Subject to fusion
--
-- Since 1.0.0
-stderr :: (MonadIO m, IOData a) => Consumer a m ()
+stderr :: MonadIO m => Consumer ByteString m ()
INLINE_RULE0(stderr, sinkHandle SIO.stderr)
--- | Write all data to the given @Handle@.
---
--- Does not close the @Handle@ at any point.
---
--- Subject to fusion
---
--- Since 1.0.0
-sinkHandle :: (MonadIO m, IOData a) => Handle -> Consumer a m ()
-INLINE_RULE(sinkHandle, h, CL.mapM_ (hPut h))
-
--- | Open a @Handle@ using the given function and stream data to it.
---
--- Automatically closes the file at completion.
---
--- Since 1.0.0
-sinkIOHandle :: (MonadResource m, IOData a) => SIO.IO Handle -> Consumer a m ()
-sinkIOHandle alloc = bracketP alloc SIO.hClose sinkHandle
-{-# INLINE sinkIOHandle #-}
-
-- | Apply a transformation to all values in a stream.
--
-- Subject to fusion
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore'
old/conduit-combinators-1.0.8.3/conduit-combinators.cabal
new/conduit-combinators-1.1.0/conduit-combinators.cabal
--- old/conduit-combinators-1.0.8.3/conduit-combinators.cabal 2016-11-28
11:23:00.000000000 +0100
+++ new/conduit-combinators-1.1.0/conduit-combinators.cabal 2017-01-22
10:30:06.000000000 +0100
@@ -1,5 +1,5 @@
name: conduit-combinators
-version: 1.0.8.3
+version: 1.1.0
synopsis: Commonly used conduit functions, for both chunked and
unchunked data
description: Provides a replacement for Data.Conduit.List, as well as
a convenient Conduit module.
homepage: https://github.com/snoyberg/mono-traversable
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/conduit-combinators-1.0.8.3/test/Spec.hs
new/conduit-combinators-1.1.0/test/Spec.hs
--- old/conduit-combinators-1.0.8.3/test/Spec.hs 2016-11-28
11:23:00.000000000 +0100
+++ new/conduit-combinators-1.1.0/test/Spec.hs 2017-01-22 10:30:06.000000000
+0100
@@ -15,6 +15,7 @@
import Test.Hspec.QuickCheck
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
+import qualified Data.Text.Lazy.Encoding as TL
import Data.IORef
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as VU
@@ -112,20 +113,20 @@
fp = "tmp"
writeFile fp contents
res <- runResourceT $ sourceFile fp $$ sinkLazy
- res `shouldBe` TL.pack contents
+ res `shouldBe` TL.encodeUtf8 (TL.pack contents)
it "sourceHandle" $ do
let contents = concat $ replicate 10000 $ "this is some content\n"
fp = "tmp"
writeFile fp contents
res <- IO.withBinaryFile "tmp" IO.ReadMode $ \h -> sourceHandle h $$
sinkLazy
- res `shouldBe` TL.pack contents
+ res `shouldBe` TL.encodeUtf8 (TL.pack contents)
it "sourceIOHandle" $ do
let contents = concat $ replicate 10000 $ "this is some content\n"
fp = "tmp"
writeFile fp contents
let open = IO.openBinaryFile "tmp" IO.ReadMode
res <- runResourceT $ sourceIOHandle open $$ sinkLazy
- res `shouldBe` TL.pack contents
+ res `shouldBe` TL.encodeUtf8 (TL.pack contents)
prop "stdin" $ \(S.pack -> content) -> do
S.writeFile "tmp" content
IO.withBinaryFile "tmp" IO.ReadMode $ \h -> do
@@ -326,23 +327,23 @@
res = runIdentity $ src $$ foldMapMCE (return . return)
in res `shouldBe` [1..10]
it "sinkFile" $ do
- let contents = concat $ replicate 1000 $ "this is some content\n"
+ let contents = mconcat $ replicate 1000 $ "this is some content\n"
fp = "tmp"
runResourceT $ yield contents $$ sinkFile fp
- res <- readFile fp
+ res <- S.readFile fp
res `shouldBe` contents
it "sinkHandle" $ do
- let contents = concat $ replicate 1000 $ "this is some content\n"
+ let contents = mconcat $ replicate 1000 $ "this is some content\n"
fp = "tmp"
IO.withBinaryFile "tmp" IO.WriteMode $ \h -> yield contents $$
sinkHandle h
- res <- readFile fp
+ res <- S.readFile fp
res `shouldBe` contents
it "sinkIOHandle" $ do
- let contents = concat $ replicate 1000 $ "this is some content\n"
+ let contents = mconcat $ replicate 1000 $ "this is some content\n"
fp = "tmp"
open = IO.openBinaryFile "tmp" IO.WriteMode
runResourceT $ yield contents $$ sinkIOHandle open
- res <- readFile fp
+ res <- S.readFile fp
res `shouldBe` contents
prop "print" $ \vals -> do
let expected = Prelude.unlines $ map showInt vals
@@ -350,11 +351,11 @@
actual `shouldBe` expected
prop "stdout" $ \ (vals :: [String]) -> do
let expected = concat vals
- (actual, ()) <- hCapture [IO.stdout] $ yieldMany vals $$ stdoutC
+ (actual, ()) <- hCapture [IO.stdout] $ yieldMany (map T.pack vals) $$
encodeUtf8C =$ stdoutC
actual `shouldBe` expected
prop "stderr" $ \ (vals :: [String]) -> do
let expected = concat vals
- (actual, ()) <- hCapture [IO.stderr] $ yieldMany vals $$ stderrC
+ (actual, ()) <- hCapture [IO.stderr] $ yieldMany (map T.pack vals) $$
encodeUtf8C =$ stderrC
actual `shouldBe` expected
prop "map" $ \input ->
runIdentity (yieldMany input $$ mapC succChar =$ sinkList)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/conduit-combinators-1.0.8.3/test/StreamSpec.hs
new/conduit-combinators-1.1.0/test/StreamSpec.hs
--- old/conduit-combinators-1.0.8.3/test/StreamSpec.hs 2016-11-28
11:23:00.000000000 +0100
+++ new/conduit-combinators-1.1.0/test/StreamSpec.hs 2017-01-22
10:30:06.000000000 +0100
@@ -42,14 +42,6 @@
spec :: Spec
spec = do
- it "sourceHandleS works" $ do
- let contents = Prelude.concat $ Prelude.replicate 10000 $ "this is
some content\n"
- fp = "tmp"
- IO.writeFile fp contents
- (res, ()) <- IO.withBinaryFile "tmp" IO.ReadMode $ \h ->
- evalStream $ sourceHandleS h emptyStream
- (TL.concat res) `shouldBe` TL.pack contents
- removeFile "tmp"
describe "Comparing list function to" $ do
qit "yieldMany" $
\(mono :: Seq Int) ->