Skip to content

Commit

Permalink
added a bounds assert for writeCharBuff in hPutStr
Browse files Browse the repository at this point in the history
  • Loading branch information
BebeSparkelSparkel committed Apr 30, 2024
1 parent a9c5047 commit 69975fd
Showing 1 changed file with 27 additions and 21 deletions.
48 changes: 27 additions & 21 deletions src/Data/Text/IO.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE BangPatterns, CPP, RecordWildCards, ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NamedFieldPuns #-}
-- |
-- Module : Data.Text.IO
-- Copyright : (c) 2009, 2010 Bryan O'Sullivan,
Expand Down Expand Up @@ -55,8 +56,8 @@ import Data.Text.Internal.Fusion (stream)
import Data.Text.Internal.Fusion.Types (Step(..), Stream(..))
import Data.Text.Internal.IO (hGetLineWith, readChunk)
import GHC.IO.Buffer (Buffer(..), BufferState(..), CharBufElem, CharBuffer,
RawCharBuffer, emptyBuffer, isEmptyBuffer, newCharBuffer,
writeCharBuf)
emptyBuffer, isEmptyBuffer, newCharBuffer)
import qualified GHC.IO.Buffer
import GHC.IO.Exception (IOException(ioe_type), IOErrorType(InappropriateType))
import GHC.IO.Handle.Internals (augmentIOError, hClose_help, wantReadableHandle,
wantWritableHandle)
Expand Down Expand Up @@ -209,7 +210,7 @@ hPutChars h (Stream next0 s0 _len) = loop s0
writeLines :: Handle -> Newline -> Buffer CharBufElem -> Stream Char -> IO ()
writeLines h nl buf0 (Stream next0 s0 _len) = outer s0 buf0
where
outer s1 Buffer{bufRaw=raw, bufSize=len} = inner s1 (0::Int)
outer s1 buf@Buffer{bufSize=len} = inner s1 (0::Int)
where
inner !s !n =
case next0 s of
Expand All @@ -219,42 +220,47 @@ writeLines h nl buf0 (Stream next0 s0 _len) = outer s0 buf0
| n + 1 >= len -> commit n True{-needs flush-} False >>= outer s
| x == '\n' -> do
n' <- if nl == CRLF
then do n1 <- writeCharBuf raw n '\r'
writeCharBuf raw n1 '\n'
else writeCharBuf raw n x
then do n1 <- writeCharBuf buf n '\r'
writeCharBuf buf n1 '\n'
else writeCharBuf buf n x
commit n' True{-needs flush-} False >>= outer s'
| otherwise -> writeCharBuf raw n x >>= inner s'
commit = commitBuffer h raw len
| otherwise -> writeCharBuf buf n x >>= inner s'
commit = commitBuffer h buf

writeBlocksCRLF :: Handle -> Buffer CharBufElem -> Stream Char -> IO ()
writeBlocksCRLF h buf0 (Stream next0 s0 _len) = outer s0 buf0
where
outer s1 Buffer{bufRaw=raw, bufSize=len} = inner s1 (0::Int)
outer s1 buf@Buffer{bufSize=len} = inner s1 (0::Int)
where
inner !s !n =
case next0 s of
Done -> commit n False{-no flush-} True{-release-} >> return ()
Skip s' -> inner s' n
Yield x s'
| n + 1 >= len -> commit n True{-needs flush-} False >>= outer s
| x == '\n' -> do n1 <- writeCharBuf raw n '\r'
writeCharBuf raw n1 '\n' >>= inner s'
| otherwise -> writeCharBuf raw n x >>= inner s'
commit = commitBuffer h raw len
| x == '\n' -> do n1 <- writeCharBuf buf n '\r'
writeCharBuf buf n1 '\n' >>= inner s'
| otherwise -> writeCharBuf buf n x >>= inner s'
commit = commitBuffer h buf

writeBlocksRaw :: Handle -> Buffer CharBufElem -> Stream Char -> IO ()
writeBlocksRaw h buf0 (Stream next0 s0 _len) = outer s0 buf0
where
outer s1 Buffer{bufRaw=raw, bufSize=len} = inner s1 (0::Int)
outer s1 buf@Buffer{bufSize=len} = inner s1 (0::Int)
where
inner !s !n =
case next0 s of
Done -> commit n False{-no flush-} True{-release-} >> return ()
Skip s' -> inner s' n
Yield x s'
| n - 10 >= len -> commit n True{-needs flush-} False >>= outer s
| otherwise -> writeCharBuf raw n x >>= inner s'
commit = commitBuffer h raw len
| n >= len -> commit n True{-needs flush-} False >>= outer s
| otherwise -> writeCharBuf buf n x >>= inner s'
commit = commitBuffer h buf

-- | Only modifies the raw buffer and not the buffer attributes
writeCharBuf :: CharBuffer -> Int -> Char -> IO Int
writeCharBuf Buffer{bufRaw, bufSize} n c = E.assert (n >= 0 && n < bufSize) $
GHC.IO.Buffer.writeCharBuf bufRaw n c

-- This function is completely lifted from GHC.IO.Handle.Text.
getSpareBuffer :: Handle__ -> IO (BufferMode, CharBuffer)
Expand All @@ -276,12 +282,12 @@ getSpareBuffer Handle__{haCharBuffer=ref,
return (mode, new_buf)


-- This function is completely lifted from GHC.IO.Handle.Text.
commitBuffer :: Handle -> RawCharBuffer -> Int -> Int -> Bool -> Bool
-- This function is modified from GHC.Internal.IO.Handle.Text.
commitBuffer :: Handle -> CharBuffer -> Int -> Bool -> Bool
-> IO CharBuffer
commitBuffer hdl !raw !sz !count flush release =
commitBuffer hdl Buffer{bufRaw, bufSize} !count flush release =
wantWritableHandle "commitAndReleaseBuffer" hdl $
commitBuffer' raw sz count flush release
commitBuffer' bufRaw bufSize count flush release
{-# INLINE commitBuffer #-}

-- | Write a string to a handle, followed by a newline.
Expand Down

0 comments on commit 69975fd

Please sign in to comment.