import Control.Exception (throwIO, try)
import Control.Monad (liftM, unless)
import Control.Monad.Trans.State.Strict (StateT(..))
+import Data.Monoid ((<>))
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Encoding as TE
-- into a Pipe of Text
decodeUtf8 :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r)
-decodeUtf8 = go PE.streamDecodeUtf8 where
- go dec0 p = do
- x <- lift (next p)
- case x of Left r -> return (return r)
- Right (chunk, p') ->
- case dec0 chunk of PE.Some text _ dec -> do yield text
- go dec p'
- PE.Other text bs -> do yield text
- return (do yield bs
- p')
+decodeUtf8 = go B.empty PE.streamDecodeUtf8 where
+ go carry dec0 p = do
+ x <- lift (next p)
+ case x of Left r -> return (do yield carry
+ return r)
+ Right (chunk, p') -> case dec0 chunk of
+ PE.Some text carry2 dec -> do yield text
+ go carry2 dec p'
+ PE.Other text bs -> do yield text
+ return (do yield bs
+ p')
-- | Splits a 'Producer' after the given number of characters
splitAt
import qualified Pipes.Text as TP
import qualified Pipes.ByteString as BP
import qualified Pipes as P
-
-
import Debug.Trace
+
main :: IO ()
main = defaultMain [tests]
-- >>> :main -a 10000
tests = testGroup "stream_decode" [
-- testProperty "t_utf8_incr_valid" t_utf8_incr_valid,
- testProperty "t_utf8_incr_mixed" t_utf8_incr_mixed,
- testProperty "t_utf8_incr_pipe" t_utf8_incr_pipe]
+-- testProperty "t_utf8_incr_mixed" t_utf8_incr_mixed ] -- ,
+ testProperty "t_utf8_incr_pipe" t_utf8_incr_pipe]
t_utf8_incr_valid = do
Positive n <- arbitrary
chunk n bs = let (a,b) = B.splitAt n bs in if B.null a then [] else a : chunk n b
appendBytes txt bts = E.encodeUtf8 txt <> B.pack bts ; (<>) = B.append
-
-
-
t_utf8_incr_pipe = do
Positive m <- arbitrary
Positive n <- arbitrary
txt <- genUnicode
let chunkSize = mod n 7 + 1
- bytesLength = mod 20 m
+ bytesLength = mod 3 m
forAll (vector bytesLength) $
(BL.toStrict . BP.toLazy . roundtrip . P.each . chunk chunkSize . appendBytes txt)
`eq`
appendBytes txt
where
roundtrip :: Monad m => P.Producer B.ByteString m r -> P.Producer B.ByteString m r
- roundtrip p = do pbs <- TP.decodeUtf8 p P.>-> TP.encodeUtf8
- pbs
+ roundtrip p = join (TP.decodeUtf8 p P.>-> TP.encodeUtf8)
chunk n bs = let (a,b) = B.splitAt n bs in if B.null a then [] else a : chunk n b
appendBytes txt bts = E.encodeUtf8 txt <> B.pack bts ; (<>) = B.append