From 3cd9ed3c1d16ba18986bccbafbb34a4c0b89c564 Mon Sep 17 00:00:00 2001 From: William Rusnack Date: Tue, 25 Jun 2024 16:36:59 -0400 Subject: [PATCH] use hPutStream for lazy hPutStr (#603) MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit * use hPutStream for lazy hPutStr * added lazy streamLn * less points * set since version Co-authored-by: ˌbodʲɪˈɡrʲim --------- Co-authored-by: ˌbodʲɪˈɡrʲim --- src/Data/Text/Internal/Fusion.hs | 8 ++++---- src/Data/Text/Internal/Lazy/Fusion.hs | 28 ++++++++++++++++++++++++--- src/Data/Text/Lazy/IO.hs | 14 ++++++-------- 3 files changed, 35 insertions(+), 15 deletions(-) diff --git a/src/Data/Text/Internal/Fusion.hs b/src/Data/Text/Internal/Fusion.hs index 866222c74..389557088 100644 --- a/src/Data/Text/Internal/Fusion.hs +++ b/src/Data/Text/Internal/Fusion.hs @@ -79,7 +79,7 @@ stream :: HasCallStack => #endif Text -> Stream Char -stream t = stream' t False +stream = stream' False {-# INLINE [0] stream #-} -- | /O(n)/ @'streamLn' t = 'stream' (t <> \'\\n\')@ @@ -90,15 +90,15 @@ streamLn :: HasCallStack => #endif Text -> Stream Char -streamLn t = stream' t True +streamLn = stream' True -- | Shared implementation of 'stream' and 'streamLn'. stream' :: #if defined(ASSERTS) HasCallStack => #endif - Text -> Bool -> Stream Char -stream' (Text arr off len) addNl = Stream next off (betweenSize (len `shiftR` 2) maxLen) + Bool -> Text -> Stream Char +stream' addNl (Text arr off len) = Stream next off (betweenSize (len `shiftR` 2) maxLen) where maxLen = if addNl then len + 1 else len !end = off+len diff --git a/src/Data/Text/Internal/Lazy/Fusion.hs b/src/Data/Text/Internal/Lazy/Fusion.hs index 3297c00ff..aec3009a1 100644 --- a/src/Data/Text/Internal/Lazy/Fusion.hs +++ b/src/Data/Text/Internal/Lazy/Fusion.hs @@ -17,6 +17,7 @@ module Data.Text.Internal.Lazy.Fusion ( stream + , streamLn , unstream , unstreamChunks , length @@ -47,14 +48,35 @@ stream :: HasCallStack => #endif Text -> Stream Char -stream text = Stream next (text :*: 0) unknownSize +stream = stream' False +{-# INLINE [0] stream #-} + +-- | /O(n)/ @'streamLn' t = 'stream' (t <> \'\\n\')@ +-- +-- @since 2.1.2 +streamLn :: +#if defined(ASSERTS) + HasCallStack => +#endif + Text -> Stream Char +streamLn = stream' True + +-- | Shared implementation of 'stream' and 'streamLn'. +stream' :: +#if defined(ASSERTS) + HasCallStack => +#endif + Bool -> Text -> Stream Char +stream' addNl text = Stream next (text :*: 0) unknownSize where - next (Empty :*: _) = Done + next (Empty :*: i) + | addNl && i <= 0 = Yield '\n' (Empty :*: 1) + | otherwise = Done next (txt@(Chunk t@(I.Text _ _ len) ts) :*: i) | i >= len = next (ts :*: 0) | otherwise = Yield c (txt :*: i+d) where Iter c d = iter t i -{-# INLINE [0] stream #-} +{-# INLINE [0] stream' #-} -- | /O(n)/ Convert a 'Stream Char' into a 'Text', using the given -- chunk size. diff --git a/src/Data/Text/Lazy/IO.hs b/src/Data/Text/Lazy/IO.hs index 1a24bd23c..48b2bcec2 100644 --- a/src/Data/Text/Lazy/IO.hs +++ b/src/Data/Text/Lazy/IO.hs @@ -41,15 +41,15 @@ module Data.Text.Lazy.IO import Data.Text.Lazy (Text) import Prelude hiding (appendFile, getContents, getLine, interact, putStr, putStrLn, readFile, writeFile) -import System.IO (Handle, IOMode(..), hPutChar, openFile, stdin, stdout, +import System.IO (Handle, IOMode(..), openFile, stdin, stdout, withFile) -import qualified Data.Text.IO as T import qualified Data.Text.Lazy as L import qualified Control.Exception as E import Control.Monad (when) import Data.IORef (readIORef) -import Data.Text.Internal.IO (hGetLineWith, readChunk) -import Data.Text.Internal.Lazy (Text(..), chunk, empty) +import Data.Text.Internal.IO (hGetLineWith, readChunk, hPutStream) +import Data.Text.Internal.Lazy (chunk, empty) +import Data.Text.Internal.Lazy.Fusion (stream, streamLn) import GHC.IO.Buffer (isEmptyBuffer) import GHC.IO.Exception (IOException(..), IOErrorType(..), ioException) import GHC.IO.Handle.Internals (augmentIOError, hClose_help, @@ -129,13 +129,11 @@ hGetLine = hGetLineWith L.fromChunks -- | Write a string to a handle. hPutStr :: Handle -> Text -> IO () -hPutStr h = mapM_ (T.hPutStr h) . L.toChunks +hPutStr h = hPutStream h . stream -- | Write a string to a handle, followed by a newline. hPutStrLn :: Handle -> Text -> IO () -hPutStrLn h Empty = hPutChar h '\n' -hPutStrLn h (Chunk t Empty) = T.hPutStrLn h t -- print the newline after the last chunk atomically -hPutStrLn h (Chunk t ts) = T.hPutStr h t >> hPutStrLn h ts +hPutStrLn h = hPutStream h . streamLn -- | The 'interact' function takes a function of type @Text -> Text@ -- as its argument. The entire input from the standard input device is