Hello community,

here is the log from the commit of package ghc-io-streams for openSUSE:Factory 
checked in at 2017-08-31 20:56:44
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-io-streams (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-io-streams.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-io-streams"

Thu Aug 31 20:56:44 2017 rev:4 rq:513406 version:1.4.0.0

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-io-streams/ghc-io-streams.changes    
2017-04-11 09:42:41.382045770 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-io-streams.new/ghc-io-streams.changes       
2017-08-31 20:56:45.640911193 +0200
@@ -1,0 +2,5 @@
+Thu Jul 27 14:07:26 UTC 2017 - [email protected]
+
+- Update to version 1.4.0.0.
+
+-------------------------------------------------------------------

Old:
----
  io-streams-1.3.6.1.tar.gz

New:
----
  io-streams-1.4.0.0.tar.gz

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

Other differences:
------------------
++++++ ghc-io-streams.spec ++++++
--- /var/tmp/diff_new_pack.nUZiQ6/_old  2017-08-31 20:56:46.508789254 +0200
+++ /var/tmp/diff_new_pack.nUZiQ6/_new  2017-08-31 20:56:46.508789254 +0200
@@ -19,7 +19,7 @@
 %global pkg_name io-streams
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        1.3.6.1
+Version:        1.4.0.0
 Release:        0
 Summary:        Simple, composable, and easy-to-use stream I/O
 License:        BSD-3-Clause

++++++ io-streams-1.3.6.1.tar.gz -> io-streams-1.4.0.0.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/io-streams-1.3.6.1/changelog.md 
new/io-streams-1.4.0.0/changelog.md
--- old/io-streams-1.3.6.1/changelog.md 2017-03-24 22:43:21.000000000 +0100
+++ new/io-streams-1.4.0.0/changelog.md 2017-05-09 20:33:10.000000000 +0200
@@ -1,3 +1,9 @@
+# Version 1.4.0.0
+
+- Added support for Text with Attoparsec, courtesy Kevin Brubeck Unhammer. Adds
+  modules `System.IO.Streams.Attoparsec.{ByteString, Text}` and deprecates
+  `System.IO.Streams.Attoparsec`, which is now a thin wrapper.
+
 # Version 1.3.6.1
 - Bumped dependencies on `time` and `process`.
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/io-streams-1.3.6.1/io-streams.cabal 
new/io-streams-1.4.0.0/io-streams.cabal
--- old/io-streams-1.3.6.1/io-streams.cabal     2017-03-24 22:43:21.000000000 
+0100
+++ new/io-streams-1.4.0.0/io-streams.cabal     2017-05-09 20:33:10.000000000 
+0200
@@ -1,5 +1,5 @@
 Name:                io-streams
-Version:             1.3.6.1
+Version:             1.4.0.0
 License:             BSD3
 License-file:        LICENSE
 Category:            Data, Network, IO-Streams
@@ -96,6 +96,8 @@
 
   Exposed-modules:   System.IO.Streams,
                      System.IO.Streams.Attoparsec,
+                     System.IO.Streams.Attoparsec.ByteString,
+                     System.IO.Streams.Attoparsec.Text,
                      System.IO.Streams.Builder,
                      System.IO.Streams.ByteString,
                      System.IO.Streams.Combinators,
@@ -153,7 +155,8 @@
   Main-is:           TestSuite.hs
   Default-language:  Haskell2010
 
-  Other-modules:     System.IO.Streams.Tests.Attoparsec,
+  Other-modules:     System.IO.Streams.Tests.Attoparsec.ByteString,
+                     System.IO.Streams.Tests.Attoparsec.Text,
                      System.IO.Streams.Tests.Builder,
                      System.IO.Streams.Tests.ByteString,
                      System.IO.Streams.Tests.Combinators,
@@ -170,7 +173,8 @@
                      System.IO.Streams.Tests.Vector,
                      System.IO.Streams.Tests.Zlib,
                      System.IO.Streams,
-                     System.IO.Streams.Attoparsec,
+                     System.IO.Streams.Attoparsec.ByteString,
+                     System.IO.Streams.Attoparsec.Text,
                      System.IO.Streams.Builder,
                      System.IO.Streams.ByteString,
                      System.IO.Streams.Combinators,
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/io-streams-1.3.6.1/src/System/IO/Streams/Attoparsec/ByteString.hs 
new/io-streams-1.4.0.0/src/System/IO/Streams/Attoparsec/ByteString.hs
--- old/io-streams-1.3.6.1/src/System/IO/Streams/Attoparsec/ByteString.hs       
1970-01-01 01:00:00.000000000 +0100
+++ new/io-streams-1.4.0.0/src/System/IO/Streams/Attoparsec/ByteString.hs       
2017-05-09 20:33:10.000000000 +0200
@@ -0,0 +1,75 @@
+-- | This module provides support for parsing values from ByteString
+-- 'InputStream's using @attoparsec@. /Since: 1.4.0.0./
+
+module System.IO.Streams.Attoparsec.ByteString
+  ( -- * Parsing
+    parseFromStream
+  , parserToInputStream
+  , ParseException(..)
+  ) where
+
+------------------------------------------------------------------------------
+import           Data.Attoparsec.ByteString.Char8      (Parser)
+import           Data.ByteString                       (ByteString)
+------------------------------------------------------------------------------
+import           System.IO.Streams.Internal            (InputStream)
+import qualified System.IO.Streams.Internal            as Streams
+import           System.IO.Streams.Internal.Attoparsec (ParseData (..), 
ParseException (..), parseFromStreamInternal)
+
+------------------------------------------------------------------------------
+-- | Supplies an @attoparsec@ 'Parser' with an 'InputStream', returning the
+-- final parsed value or throwing a 'ParseException' if parsing fails.
+--
+-- 'parseFromStream' consumes only as much input as necessary to satisfy the
+-- 'Parser': any unconsumed input is pushed back onto the 'InputStream'.
+--
+-- If the 'Parser' exhausts the 'InputStream', the end-of-stream signal is sent
+-- to attoparsec.
+--
+-- Example:
+--
+-- @
+-- ghci> import "Data.Attoparsec.ByteString.Char8"
+-- ghci> is <- 'System.IO.Streams.fromList' [\"12345xxx\" :: 'ByteString']
+-- ghci> 'parseFromStream' ('Data.Attoparsec.ByteString.Char8.takeWhile' 
'Data.Attoparsec.ByteString.Char8.isDigit') is
+-- \"12345\"
+-- ghci> 'System.IO.Streams.read' is
+-- Just \"xxx\"
+-- @
+parseFromStream :: Parser r
+                -> InputStream ByteString
+                -> IO r
+parseFromStream = parseFromStreamInternal parse feed
+
+------------------------------------------------------------------------------
+-- | Given a 'Parser' yielding values of type @'Maybe' r@, transforms an
+-- 'InputStream' over byte strings to an 'InputStream' yielding values of type
+-- @r@.
+--
+-- If the parser yields @Just x@, then @x@ will be passed along downstream, and
+-- if the parser yields @Nothing@, that will be interpreted as end-of-stream.
+--
+-- Upon a parse error, 'parserToInputStream' will throw a 'ParseException'.
+--
+-- Example:
+--
+-- @
+-- ghci> import "Control.Applicative"
+-- ghci> import "Data.Attoparsec.ByteString.Char8"
+-- ghci> is <- 'System.IO.Streams.fromList' [\"1 2 3 4 5\" :: 'ByteString']
+-- ghci> let parser = ('Data.Attoparsec.ByteString.Char8.endOfInput' >> 
'Control.Applicative.pure' 'Nothing') \<|\> (Just \<$\> 
('Data.Attoparsec.ByteString.Char8.skipWhile' 
'Data.Attoparsec.ByteString.Char8.isSpace' *> 
'Data.Attoparsec.ByteString.Char8.decimal'))
+-- ghci> 'parserToInputStream' parser is >>= 'System.IO.Streams.toList'
+-- [1,2,3,4,5]
+-- ghci> is' \<- 'System.IO.Streams.fromList' [\"1 2xx3 4 5\" :: 'ByteString'] 
>>= 'parserToInputStream' parser
+-- ghci> 'read' is'
+-- Just 1
+-- ghci> 'read' is'
+-- Just 2
+-- ghci> 'read' is'
+-- *** Exception: Parse exception: Failed reading: takeWhile1
+-- @
+parserToInputStream :: Parser (Maybe r)
+                    -> InputStream ByteString
+                    -> IO (InputStream r)
+parserToInputStream = (Streams.makeInputStream .) . parseFromStream
+{-# INLINE parserToInputStream #-}
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/io-streams-1.3.6.1/src/System/IO/Streams/Attoparsec/Text.hs 
new/io-streams-1.4.0.0/src/System/IO/Streams/Attoparsec/Text.hs
--- old/io-streams-1.3.6.1/src/System/IO/Streams/Attoparsec/Text.hs     
1970-01-01 01:00:00.000000000 +0100
+++ new/io-streams-1.4.0.0/src/System/IO/Streams/Attoparsec/Text.hs     
2017-05-09 20:33:10.000000000 +0200
@@ -0,0 +1,76 @@
+-- | This module provides support for parsing values from Text
+-- 'InputStream's using @attoparsec@. /Since: 1.4.0.0./
+
+module System.IO.Streams.Attoparsec.Text
+  ( -- * Parsing
+    parseFromStream
+  , parserToInputStream
+  , ParseException(..)
+  ) where
+
+------------------------------------------------------------------------------
+import           Data.Attoparsec.Text                  (Parser)
+import           Data.Text                             (Text)
+------------------------------------------------------------------------------
+import           System.IO.Streams.Internal            (InputStream)
+import qualified System.IO.Streams.Internal            as Streams
+import           System.IO.Streams.Internal.Attoparsec (ParseData (..), 
ParseException (..), parseFromStreamInternal)
+
+
+------------------------------------------------------------------------------
+-- | Supplies an @attoparsec@ 'Parser' with an 'InputStream', returning the
+-- final parsed value or throwing a 'ParseException' if parsing fails.
+--
+-- 'parseFromStream' consumes only as much input as necessary to satisfy the
+-- 'Parser': any unconsumed input is pushed back onto the 'InputStream'.
+--
+-- If the 'Parser' exhausts the 'InputStream', the end-of-stream signal is sent
+-- to attoparsec.
+--
+-- Example:
+--
+-- @
+-- ghci> import "Data.Attoparsec.Text"
+-- ghci> is <- 'System.IO.Streams.fromList' [\"12345xxx\" :: 'Text']
+-- ghci> 'parseFromStream' ('Data.Attoparsec.Text.takeWhile' 
'Data.Char.isDigit') is
+-- \"12345\"
+-- ghci> 'System.IO.Streams.read' is
+-- Just \"xxx\"
+-- @
+parseFromStream :: Parser r
+                -> InputStream Text
+                -> IO r
+parseFromStream = parseFromStreamInternal parse feed
+
+------------------------------------------------------------------------------
+-- | Given a 'Parser' yielding values of type @'Maybe' r@, transforms an
+-- 'InputStream' over byte strings to an 'InputStream' yielding values of type
+-- @r@.
+--
+-- If the parser yields @Just x@, then @x@ will be passed along downstream, and
+-- if the parser yields @Nothing@, that will be interpreted as end-of-stream.
+--
+-- Upon a parse error, 'parserToInputStream' will throw a 'ParseException'.
+--
+-- Example:
+--
+-- @
+-- ghci> import "Control.Applicative"
+-- ghci> import "Data.Attoparsec.Text"
+-- ghci> is <- 'System.IO.Streams.fromList' [\"1 2 3 4 5\" :: 'Text']
+-- ghci> let parser = ('Data.Attoparsec.Text.endOfInput' >> 
'Control.Applicative.pure' 'Nothing') \<|\> (Just \<$\> 
('Data.Attoparsec.Text.skipWhile' 'Data.Attoparsec.Text.isSpace' *> 
'Data.Attoparsec.Text.decimal'))
+-- ghci> 'parserToInputStream' parser is >>= 'System.IO.Streams.toList'
+-- [1,2,3,4,5]
+-- ghci> is' \<- 'System.IO.Streams.fromList' [\"1 2xx3 4 5\" :: 'Text'] >>= 
'parserToInputStream' parser
+-- ghci> 'read' is'
+-- Just 1
+-- ghci> 'read' is'
+-- Just 2
+-- ghci> 'read' is'
+-- *** Exception: Parse exception: Failed reading: takeWhile1
+-- @
+parserToInputStream :: Parser (Maybe r)
+                    -> InputStream Text
+                    -> IO (InputStream r)
+parserToInputStream = (Streams.makeInputStream .) . parseFromStream
+{-# INLINE parserToInputStream #-}
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/io-streams-1.3.6.1/src/System/IO/Streams/Attoparsec.hs 
new/io-streams-1.4.0.0/src/System/IO/Streams/Attoparsec.hs
--- old/io-streams-1.3.6.1/src/System/IO/Streams/Attoparsec.hs  2017-03-24 
22:43:21.000000000 +0100
+++ new/io-streams-1.4.0.0/src/System/IO/Streams/Attoparsec.hs  2017-05-09 
20:33:10.000000000 +0200
@@ -1,5 +1,6 @@
--- | This module provides support for parsing values from 'InputStream's using
--- @attoparsec@.
+-- | This module is deprecated -- use
+-- System.IO.Streams.Attoparsec.ByteString instead (this module simply
+-- re-exports that one).
 
 module System.IO.Streams.Attoparsec
   ( -- * Parsing
@@ -9,4 +10,4 @@
   ) where
 
 ------------------------------------------------------------------------------
-import           System.IO.Streams.Internal.Attoparsec (ParseException (..), 
parseFromStream, parserToInputStream)
+import           System.IO.Streams.Attoparsec.ByteString (ParseException (..), 
parseFromStream, parserToInputStream)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/io-streams-1.3.6.1/src/System/IO/Streams/Internal/Attoparsec.hs 
new/io-streams-1.4.0.0/src/System/IO/Streams/Internal/Attoparsec.hs
--- old/io-streams-1.3.6.1/src/System/IO/Streams/Internal/Attoparsec.hs 
2017-03-24 22:43:21.000000000 +0100
+++ new/io-streams-1.4.0.0/src/System/IO/Streams/Internal/Attoparsec.hs 
2017-05-09 20:33:10.000000000 +0200
@@ -8,9 +8,9 @@
 
 module System.IO.Streams.Internal.Attoparsec
   ( -- * Parsing
-    parseFromStream
-  , parseFromStreamInternal
-  , parserToInputStream
+    parseFromStreamInternal
+
+  , ParseData(..)
 
     -- * Parse Exceptions
   , ParseException(..)
@@ -20,14 +20,16 @@
 
 ------------------------------------------------------------------------------
 import           Control.Exception                (Exception, throwIO)
-import           Control.Monad                    (when)
-import           Data.Attoparsec.ByteString.Char8 (Parser, Result, feed, parse)
-import           Data.Attoparsec.Types            (IResult (..))
-import           Data.ByteString.Char8            (ByteString)
-import qualified Data.ByteString.Char8            as S
+import           Control.Monad                    (unless)
+import qualified Data.Attoparsec.ByteString.Char8 as S
+import qualified Data.Attoparsec.Text             as T
+import           Data.Attoparsec.Types            (IResult (..), Parser)
+import qualified Data.ByteString                  as S
 import           Data.List                        (intercalate)
+import           Data.String                      (IsString)
+import qualified Data.Text                        as T
 import           Data.Typeable                    (Typeable)
-import           Prelude                          hiding (read)
+import           Prelude                          hiding (null, read)
 ------------------------------------------------------------------------------
 import           System.IO.Streams.Internal       (InputStream)
 import qualified System.IO.Streams.Internal       as Streams
@@ -45,48 +47,43 @@
 
 
 ------------------------------------------------------------------------------
--- | Supplies an @attoparsec@ 'Parser' with an 'InputStream', returning the
--- final parsed value or throwing a 'ParseException' if parsing fails.
---
--- 'parseFromStream' consumes only as much input as necessary to satisfy the
--- 'Parser': any unconsumed input is pushed back onto the 'InputStream'.
---
--- If the 'Parser' exhausts the 'InputStream', the end-of-stream signal is sent
--- to attoparsec.
---
--- Example:
---
--- @
--- ghci> import "Data.Attoparsec.ByteString.Char8"
--- ghci> is <- 'System.IO.Streams.fromList' [\"12345xxx\" :: 'ByteString']
--- ghci> 'parseFromStream' ('Data.Attoparsec.ByteString.Char8.takeWhile' 
'Data.Attoparsec.ByteString.Char8.isDigit') is
--- \"12345\"
--- ghci> 'System.IO.Streams.read' is
--- Just \"xxx\"
--- @
-parseFromStream :: Parser r
-                -> InputStream ByteString
-                -> IO r
-parseFromStream = parseFromStreamInternal parse feed
-{-# INLINE parseFromStream #-}
+class (IsString i) => ParseData i where
+  parse :: Parser i a -> i -> IResult i a
+  feed :: IResult i r -> i -> IResult i r
+  null :: i -> Bool
+
+
+------------------------------------------------------------------------------
+instance ParseData S.ByteString where
+  parse = S.parse
+  feed = S.feed
+  null = S.null
+
+
+------------------------------------------------------------------------------
+instance ParseData T.Text where
+  parse = T.parse
+  feed = T.feed
+  null = T.null
 
 
 ------------------------------------------------------------------------------
 -- | Internal version of parseFromStream allowing dependency injection of the
 -- parse functions for testing.
-parseFromStreamInternal :: (Parser r -> ByteString -> Result r)
-                        -> (Result r -> ByteString -> Result r)
-                        -> Parser r
-                        -> InputStream ByteString
+parseFromStreamInternal :: ParseData i
+                        => (Parser i r -> i -> IResult i r)
+                        -> (IResult i r -> i -> IResult i r)
+                        -> Parser i r
+                        -> InputStream i
                         -> IO r
 parseFromStreamInternal parseFunc feedFunc parser is =
     Streams.read is >>=
     maybe (finish $ parseFunc parser "")
-          (\s -> if S.null s
+          (\s -> if null s
                    then parseFromStreamInternal parseFunc feedFunc parser is
                    else go $! parseFunc parser s)
   where
-    leftover x = when (not $ S.null x) $ Streams.unRead x is
+    leftover x = unless (null x) $ Streams.unRead x is
 
     finish k = let k' = feedFunc (feedFunc k "") ""
                in case k' of
@@ -104,49 +101,15 @@
     go (Done x r)     = leftover x >> return r
     go r              = Streams.read is >>=
                         maybe (finish r)
-                              (\s -> if S.null s
+                              (\s -> if null s
                                        then go r
                                        else go $! feedFunc r s)
 
 
 ------------------------------------------------------------------------------
--- | Given a 'Parser' yielding values of type @'Maybe' r@, transforms an
--- 'InputStream' over byte strings to an 'InputStream' yielding values of type
--- @r@.
---
--- If the parser yields @Just x@, then @x@ will be passed along downstream, and
--- if the parser yields @Nothing@, that will be interpreted as end-of-stream.
---
--- Upon a parse error, 'parserToInputStream' will throw a 'ParseException'.
---
--- Example:
---
--- @
--- ghci> import "Control.Applicative"
--- ghci> import "Data.Attoparsec.ByteString.Char8"
--- ghci> is <- 'System.IO.Streams.fromList' [\"1 2 3 4 5\" :: 'ByteString']
--- ghci> let parser = ('Data.Attoparsec.ByteString.Char8.endOfInput' >> 
'Control.Applicative.pure' 'Nothing') \<|\> (Just \<$\> 
('Data.Attoparsec.ByteString.Char8.skipWhile' 
'Data.Attoparsec.ByteString.Char8.isSpace' *> 
'Data.Attoparsec.ByteString.Char8.decimal'))
--- ghci> 'parserToInputStream' parser is >>= 'System.IO.Streams.toList'
--- [1,2,3,4,5]
--- ghci> is' \<- 'System.IO.Streams.fromList' [\"1 2xx3 4 5\" :: 'ByteString'] 
>>= 'parserToInputStream' parser
--- ghci> 'read' is'
--- Just 1
--- ghci> 'read' is'
--- Just 2
--- ghci> 'read' is'
--- *** Exception: Parse exception: Failed reading: takeWhile1
--- @
-parserToInputStream :: Parser (Maybe r)
-                    -> InputStream ByteString
-                    -> IO (InputStream r)
-parserToInputStream = (Streams.makeInputStream .) . parseFromStream
-{-# INLINE parserToInputStream #-}
-
-
-------------------------------------------------------------------------------
 -- A replacement for attoparsec's 'eitherResult', which discards information
 -- about the context of the failed parse.
-eitherResult :: Result r -> Either (ByteString, [String], String) r
+eitherResult :: IsString i => IResult i r -> Either (i, [String], String) r
 eitherResult (Done _ r)              = Right r
 eitherResult (Fail residual ctx msg) = Left (residual, ctx, msg)
 eitherResult _                       = Left ("", [], "Result: incomplete 
input")
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/io-streams-1.3.6.1/test/System/IO/Streams/Tests/Attoparsec/ByteString.hs 
new/io-streams-1.4.0.0/test/System/IO/Streams/Tests/Attoparsec/ByteString.hs
--- 
old/io-streams-1.3.6.1/test/System/IO/Streams/Tests/Attoparsec/ByteString.hs    
    1970-01-01 01:00:00.000000000 +0100
+++ 
new/io-streams-1.4.0.0/test/System/IO/Streams/Tests/Attoparsec/ByteString.hs    
    2017-05-09 20:33:10.000000000 +0200
@@ -0,0 +1,113 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module System.IO.Streams.Tests.Attoparsec.ByteString (tests) where
+
+------------------------------------------------------------------------------
+import           Control.Monad
+import           Data.Attoparsec.ByteString.Char8        hiding (eitherResult)
+import           Data.ByteString.Char8                   (ByteString)
+import           Prelude                                 hiding (takeWhile)
+import           System.IO.Streams
+import           System.IO.Streams.Attoparsec.ByteString
+import           System.IO.Streams.Internal.Attoparsec   (eitherResult, 
parseFromStreamInternal)
+import           System.IO.Streams.Tests.Common
+import           Test.Framework
+import           Test.Framework.Providers.HUnit
+import           Test.HUnit                              hiding (Test)
+------------------------------------------------------------------------------
+
+tests :: [Test]
+tests = [ testParseFromStream
+        , testParseFromStreamError
+        , testParseFromStreamError2
+        , testPartialParse
+        , testEmbeddedNull
+        , testTrivials
+        ]
+
+
+------------------------------------------------------------------------------
+testParser :: Parser (Maybe Int)
+testParser = do
+    end <- atEnd
+    if end
+      then return Nothing
+      else do
+          _ <- takeWhile (\c -> isSpace c || c == ',')
+          liftM Just decimal
+
+
+------------------------------------------------------------------------------
+testParser2 :: Parser (Maybe ByteString)
+testParser2 = do
+    end <- atEnd
+    if end
+      then return Nothing
+      else liftM Just $ string "bork"
+
+
+------------------------------------------------------------------------------
+testParseFromStream :: Test
+testParseFromStream = testCase "attoparsec/parseFromStream" $ do
+    is <- fromList ["1", "23", ", 4", ", 5, 6, 7"]
+    x0 <- parseFromStream testParser is
+
+    assertEqual "first parse" (Just 123) x0
+
+    l  <- parserToInputStream testParser is >>= toList
+
+    assertEqual "rest" [4, 5, 6, 7] l
+    toList is >>= assertEqual "double eof" []
+
+
+------------------------------------------------------------------------------
+testParseFromStreamError :: Test
+testParseFromStreamError = testCase "attoparsec/parseFromStreamError" $ do
+    is <- fromList ["1", "23", ", 4", ",xxxx 5, 6, 7"] >>=
+          parserToInputStream testParser
+
+    expectExceptionH $ toList is
+
+
+------------------------------------------------------------------------------
+testParseFromStreamError2 :: Test
+testParseFromStreamError2 = testCase "attoparsec/parseFromStreamError2" $ do
+    l <- fromList ["borkbork", "bork"] >>= p
+    assertEqual "ok" ["bork", "bork", "bork"] l
+
+    expectExceptionH $ fromList ["bork", "bo"] >>= p
+    expectExceptionH $ fromList ["xxxxx"] >>= p
+
+  where
+    p = parserToInputStream ((testParser2 <?> "foo") <?> "bar") >=> toList
+
+
+------------------------------------------------------------------------------
+testPartialParse :: Test
+testPartialParse = testCase "attoparsec/partialParse" $ do
+    is <- fromList ["1,", "2,", "3"]
+    expectExceptionH $ parseFromStreamInternal parseFunc feedFunc testParser is
+
+  where
+    result    = Partial (const result)
+    parseFunc = const $ const $ result
+    feedFunc  = const $ const $ result
+
+------------------------------------------------------------------------------
+testTrivials :: Test
+testTrivials = testCase "attoparsec/trivials" $ do
+    coverTypeableInstance (undefined :: ParseException)
+    let (Right x) = eitherResult $ Done undefined 4 :: Either (ByteString, 
[String], String) Int
+    assertEqual "eitherResult" 4 x
+
+------------------------------------------------------------------------------
+testEmbeddedNull :: Test
+testEmbeddedNull = testCase "attoparsec/embeddedNull" $ do
+    is <- fromList ["", "1", "23", "", ", 4", ", 5, 6, 7"]
+    x0 <- parseFromStream testParser is
+
+    assertEqual "first parse" (Just 123) x0
+
+    l  <- parserToInputStream testParser is >>= toList
+
+    assertEqual "rest" [4, 5, 6, 7] l
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/io-streams-1.3.6.1/test/System/IO/Streams/Tests/Attoparsec/Text.hs 
new/io-streams-1.4.0.0/test/System/IO/Streams/Tests/Attoparsec/Text.hs
--- old/io-streams-1.3.6.1/test/System/IO/Streams/Tests/Attoparsec/Text.hs      
1970-01-01 01:00:00.000000000 +0100
+++ new/io-streams-1.4.0.0/test/System/IO/Streams/Tests/Attoparsec/Text.hs      
2017-05-09 20:33:10.000000000 +0200
@@ -0,0 +1,140 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module System.IO.Streams.Tests.Attoparsec.Text (tests, testParserU) where
+
+------------------------------------------------------------------------------
+import           Control.Monad
+import           Data.Attoparsec.Text                  hiding (eitherResult)
+import           Data.Char                             (isAlpha, isSpace)
+import           Data.Text                             (Text)
+import           Prelude                               hiding (takeWhile)
+import           System.IO.Streams
+import           System.IO.Streams.Attoparsec.Text
+import           System.IO.Streams.Internal.Attoparsec (eitherResult, 
parseFromStreamInternal)
+import           System.IO.Streams.Tests.Common
+import           Test.Framework
+import           Test.Framework.Providers.HUnit
+import           Test.HUnit                            hiding (Test)
+------------------------------------------------------------------------------
+
+tests :: [Test]
+tests = [ testParseFromStream
+        , testParseFromStreamError
+        , testParseFromStreamError2
+        , testPartialParse
+        , testEmbeddedNull
+        , testTrivials
+        , testParseFromStreamU
+        ]
+
+
+------------------------------------------------------------------------------
+testParser :: Parser (Maybe Int)
+testParser = do
+    end <- atEnd
+    if end
+      then return Nothing
+      else do
+          _ <- takeWhile (\c -> isSpace c || c == ',')
+          liftM Just decimal
+
+
+------------------------------------------------------------------------------
+testParser2 :: Parser (Maybe Text)
+testParser2 = do
+    end <- atEnd
+    if end
+      then return Nothing
+      else liftM Just $ string "bork"
+
+
+------------------------------------------------------------------------------
+testParserU :: Parser (Maybe Text)
+testParserU = do
+    end <- atEnd
+    if end
+      then return Nothing
+      else do
+          _ <- takeWhile (not . isAlpha)
+          liftM Just (takeWhile isAlpha)
+
+
+------------------------------------------------------------------------------
+testParseFromStream :: Test
+testParseFromStream = testCase "attoparsec/parseFromStream" $ do
+    is <- fromList ["1", "23", ", 4", ", 5, 6, 7"]
+    x0 <- parseFromStream testParser is
+
+    assertEqual "first parse" (Just 123) x0
+
+    l  <- parserToInputStream testParser is >>= toList
+
+    assertEqual "rest" [4, 5, 6, 7] l
+    toList is >>= assertEqual "double eof" []
+
+
+------------------------------------------------------------------------------
+testParseFromStreamError :: Test
+testParseFromStreamError = testCase "attoparsec/parseFromStreamError" $ do
+    is <- fromList ["1", "23", ", 4", ",xxxx 5, 6, 7"] >>=
+          parserToInputStream testParser
+
+    expectExceptionH $ toList is
+
+
+------------------------------------------------------------------------------
+testParseFromStreamError2 :: Test
+testParseFromStreamError2 = testCase "attoparsec/parseFromStreamError2" $ do
+    l <- fromList ["borkbork", "bork"] >>= p
+    assertEqual "ok" ["bork", "bork", "bork"] l
+
+    expectExceptionH $ fromList ["bork", "bo"] >>= p
+    expectExceptionH $ fromList ["xxxxx"] >>= p
+
+  where
+    p = parserToInputStream ((testParser2 <?> "foo") <?> "bar") >=> toList
+
+
+------------------------------------------------------------------------------
+testPartialParse :: Test
+testPartialParse = testCase "attoparsec/partialParse" $ do
+    is <- fromList ["1,", "2,", "3"]
+    expectExceptionH $ parseFromStreamInternal parseFunc feedFunc testParser is
+
+  where
+    result    = Partial (const result)
+    parseFunc = const $ const $ result
+    feedFunc  = const $ const $ result
+
+------------------------------------------------------------------------------
+testTrivials :: Test
+testTrivials = testCase "attoparsec/trivials" $ do
+    coverTypeableInstance (undefined :: ParseException)
+    let (Right x) = eitherResult $ Done undefined 4 :: Either (Text, [String], 
String) Int
+    assertEqual "eitherResult" 4 x
+
+------------------------------------------------------------------------------
+testEmbeddedNull :: Test
+testEmbeddedNull = testCase "attoparsec/embeddedNull" $ do
+    is <- fromList ["", "1", "23", "", ", 4", ", 5, 6, 7"]
+    x0 <- parseFromStream testParser is
+
+    assertEqual "first parse" (Just 123) x0
+
+    l  <- parserToInputStream testParser is >>= toList
+
+    assertEqual "rest" [4, 5, 6, 7] l
+
+------------------------------------------------------------------------------
+testParseFromStreamU :: Test
+testParseFromStreamU = testCase "attoparsec/parseFromStreamU" $ do
+    is <- fromList ["123æø", "å", "💻⛇⛄☃Š", "š5ŧđ6naå7"]
+    x0 <- parseFromStream testParserU is
+
+    assertEqual "first parse" (Just "æøå") x0
+
+    l  <- parserToInputStream testParserU is >>= toList
+
+    assertEqual "rest" ["Šš", "ŧđ", "naå", ""] l
+    toList is >>= assertEqual "double eof" []
+
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/io-streams-1.3.6.1/test/System/IO/Streams/Tests/Attoparsec.hs 
new/io-streams-1.4.0.0/test/System/IO/Streams/Tests/Attoparsec.hs
--- old/io-streams-1.3.6.1/test/System/IO/Streams/Tests/Attoparsec.hs   
2017-03-24 22:43:21.000000000 +0100
+++ new/io-streams-1.4.0.0/test/System/IO/Streams/Tests/Attoparsec.hs   
1970-01-01 01:00:00.000000000 +0100
@@ -1,112 +0,0 @@
-{-# LANGUAGE OverloadedStrings #-}
-
-module System.IO.Streams.Tests.Attoparsec (tests) where
-
-------------------------------------------------------------------------------
-import           Control.Monad
-import           Data.Attoparsec.ByteString.Char8      hiding (eitherResult)
-import           Data.ByteString.Char8                 (ByteString)
-import           Prelude                               hiding (takeWhile)
-import           System.IO.Streams
-import           System.IO.Streams.Internal.Attoparsec
-import           System.IO.Streams.Tests.Common
-import           Test.Framework
-import           Test.Framework.Providers.HUnit
-import           Test.HUnit                            hiding (Test)
-------------------------------------------------------------------------------
-
-tests :: [Test]
-tests = [ testParseFromStream
-        , testParseFromStreamError
-        , testParseFromStreamError2
-        , testPartialParse
-        , testEmbeddedNull
-        , testTrivials
-        ]
-
-
-------------------------------------------------------------------------------
-testParser :: Parser (Maybe Int)
-testParser = do
-    end <- atEnd
-    if end
-      then return Nothing
-      else do
-          _ <- takeWhile (\c -> isSpace c || c == ',')
-          liftM Just decimal
-
-
-------------------------------------------------------------------------------
-testParser2 :: Parser (Maybe ByteString)
-testParser2 = do
-    end <- atEnd
-    if end
-      then return Nothing
-      else liftM Just $ string "bork"
-
-
-------------------------------------------------------------------------------
-testParseFromStream :: Test
-testParseFromStream = testCase "attoparsec/parseFromStream" $ do
-    is <- fromList ["1", "23", ", 4", ", 5, 6, 7"]
-    x0 <- parseFromStream testParser is
-
-    assertEqual "first parse" (Just 123) x0
-
-    l  <- parserToInputStream testParser is >>= toList
-
-    assertEqual "rest" [4, 5, 6, 7] l
-    toList is >>= assertEqual "double eof" []
-
-
-------------------------------------------------------------------------------
-testParseFromStreamError :: Test
-testParseFromStreamError = testCase "attoparsec/parseFromStreamError" $ do
-    is <- fromList ["1", "23", ", 4", ",xxxx 5, 6, 7"] >>=
-          parserToInputStream testParser
-
-    expectExceptionH $ toList is
-
-
-------------------------------------------------------------------------------
-testParseFromStreamError2 :: Test
-testParseFromStreamError2 = testCase "attoparsec/parseFromStreamError2" $ do
-    l <- fromList ["borkbork", "bork"] >>= p
-    assertEqual "ok" ["bork", "bork", "bork"] l
-
-    expectExceptionH $ fromList ["bork", "bo"] >>= p
-    expectExceptionH $ fromList ["xxxxx"] >>= p
-
-  where
-    p = parserToInputStream ((testParser2 <?> "foo") <?> "bar") >=> toList
-
-
-------------------------------------------------------------------------------
-testPartialParse :: Test
-testPartialParse = testCase "attoparsec/partialParse" $ do
-    is <- fromList ["1,", "2,", "3"]
-    expectExceptionH $ parseFromStreamInternal parseFunc feedFunc testParser is
-
-  where
-    result    = Partial (const result)
-    parseFunc = const $ const $ result
-    feedFunc  = const $ const $ result
-
-------------------------------------------------------------------------------
-testTrivials :: Test
-testTrivials = testCase "attoparsec/trivials" $ do
-    coverTypeableInstance (undefined :: ParseException)
-    let (Right x) = eitherResult $ Done undefined (4 :: Int)
-    assertEqual "eitherResult" 4 x
-
-------------------------------------------------------------------------------
-testEmbeddedNull :: Test
-testEmbeddedNull = testCase "attoparsec/embeddedNull" $ do
-    is <- fromList ["", "1", "23", "", ", 4", ", 5, 6, 7"]
-    x0 <- parseFromStream testParser is
-
-    assertEqual "first parse" (Just 123) x0
-
-    l  <- parserToInputStream testParser is >>= toList
-
-    assertEqual "rest" [4, 5, 6, 7] l
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/io-streams-1.3.6.1/test/TestSuite.hs 
new/io-streams-1.4.0.0/test/TestSuite.hs
--- old/io-streams-1.3.6.1/test/TestSuite.hs    2017-03-24 22:43:21.000000000 
+0100
+++ new/io-streams-1.4.0.0/test/TestSuite.hs    2017-05-09 20:33:10.000000000 
+0200
@@ -1,28 +1,30 @@
 module Main where
 
-import qualified System.IO.Streams.Tests.Attoparsec  as Attoparsec
-import qualified System.IO.Streams.Tests.Builder     as Builder
-import qualified System.IO.Streams.Tests.ByteString  as ByteString
-import qualified System.IO.Streams.Tests.Combinators as Combinators
-import qualified System.IO.Streams.Tests.Concurrent  as Concurrent
-import qualified System.IO.Streams.Tests.Debug       as Debug
-import qualified System.IO.Streams.Tests.File        as File
-import qualified System.IO.Streams.Tests.Handle      as Handle
-import qualified System.IO.Streams.Tests.Internal    as Internal
-import qualified System.IO.Streams.Tests.List        as List
-import qualified System.IO.Streams.Tests.Network     as Network
-import qualified System.IO.Streams.Tests.Process     as Process
-import qualified System.IO.Streams.Tests.Text        as Text
-import qualified System.IO.Streams.Tests.Vector      as Vector
-import qualified System.IO.Streams.Tests.Zlib        as Zlib
-import           Test.Framework                      (defaultMain, testGroup)
+import qualified System.IO.Streams.Tests.Attoparsec.ByteString as 
AttoparsecByteString
+import qualified System.IO.Streams.Tests.Attoparsec.Text       as 
AttoparsecText
+import qualified System.IO.Streams.Tests.Builder               as Builder
+import qualified System.IO.Streams.Tests.ByteString            as ByteString
+import qualified System.IO.Streams.Tests.Combinators           as Combinators
+import qualified System.IO.Streams.Tests.Concurrent            as Concurrent
+import qualified System.IO.Streams.Tests.Debug                 as Debug
+import qualified System.IO.Streams.Tests.File                  as File
+import qualified System.IO.Streams.Tests.Handle                as Handle
+import qualified System.IO.Streams.Tests.Internal              as Internal
+import qualified System.IO.Streams.Tests.List                  as List
+import qualified System.IO.Streams.Tests.Network               as Network
+import qualified System.IO.Streams.Tests.Process               as Process
+import qualified System.IO.Streams.Tests.Text                  as Text
+import qualified System.IO.Streams.Tests.Vector                as Vector
+import qualified System.IO.Streams.Tests.Zlib                  as Zlib
+import           Test.Framework                                (defaultMain, 
testGroup)
 
 
 ------------------------------------------------------------------------------
 main :: IO ()
 main = defaultMain tests
   where
-    tests = [ testGroup "Tests.Attoparsec" Attoparsec.tests
+    tests = [ testGroup "Tests.Attoparsec.ByteString" 
AttoparsecByteString.tests
+            , testGroup "Tests.Attoparsec.Text" AttoparsecText.tests
             , testGroup "Tests.Builder" Builder.tests
             , testGroup "Tests.ByteString" ByteString.tests
             , testGroup "Tests.Debug" Debug.tests


Reply via email to