[Git][ghc/ghc][master] tryFillBuffer: strictify

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Jan 27 01:08:08 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
b3ef5c89 by doyougnu at 2023-01-26T20:07:48-05:00
tryFillBuffer: strictify

more speculative bangs

- - - - -


1 changed file:

- libraries/base/GHC/Foreign.hs


Changes:

=====================================
libraries/base/GHC/Foreign.hs
=====================================
@@ -202,11 +202,11 @@ peekEncodedCString :: TextEncoding -- ^ Encoding of CString
 peekEncodedCString (TextEncoding { mkTextDecoder = mk_decoder }) (p, sz_bytes)
   = bracket mk_decoder close $ \decoder -> do
       let chunk_size = sz_bytes `max` 1 -- Decode buffer chunk size in characters: one iteration only for ASCII
-      from0 <- fmap (\fp -> bufferAdd sz_bytes (emptyBuffer fp sz_bytes ReadBuffer)) $ newForeignPtr_ (castPtr p)
-      to <- newCharBuffer chunk_size WriteBuffer
+      !from0 <- fmap (\fp -> bufferAdd sz_bytes (emptyBuffer fp sz_bytes ReadBuffer)) $ newForeignPtr_ (castPtr p)
+      !to    <- newCharBuffer chunk_size WriteBuffer
 
-      let go !iteration from = do
-            (why, from', to') <- encode decoder from to
+      let go !iteration !from = do
+            (why, from', !to') <- encode decoder from to
             if isEmptyBuffer from'
              then
               -- No input remaining: @why@ will be InputUnderflow, but we don't care
@@ -281,11 +281,11 @@ newEncodedCString (TextEncoding { mkTextEncoder = mk_encoder }) null_terminate s
 
 tryFillBuffer :: TextEncoder dstate -> Bool -> Buffer Char -> Ptr Word8 -> Int
                     ->  IO (Maybe (Buffer Word8))
-tryFillBuffer encoder null_terminate from0 to_p to_sz_bytes = do
-    to_fp <- newForeignPtr_ to_p
-    go (0 :: Int) (from0, emptyBuffer to_fp to_sz_bytes WriteBuffer)
+tryFillBuffer encoder null_terminate from0 to_p !to_sz_bytes = do
+    !to_fp <- newForeignPtr_ to_p
+    go (0 :: Int) from0 (emptyBuffer to_fp to_sz_bytes WriteBuffer)
   where
-    go !iteration (from, to) = do
+    go !iteration !from !to = do
       (why, from', to') <- encode encoder from to
       putDebugMsg ("tryFillBufferAndCall: " ++ show iteration ++ " " ++ show why ++ " " ++ summaryBuffer from ++ " " ++ summaryBuffer from')
       if isEmptyBuffer from'
@@ -293,8 +293,8 @@ tryFillBuffer encoder null_terminate from0 to_p to_sz_bytes = do
              then return Nothing -- We had enough for the string but not the terminator: ask the caller for more buffer
              else return (Just to')
        else case why of -- We didn't consume all of the input
-              InputUnderflow  -> recover encoder from' to' >>= go (iteration + 1) -- These conditions are equally bad
-              InvalidSequence -> recover encoder from' to' >>= go (iteration + 1) -- since the input was truncated/invalid
+              InputUnderflow  -> recover encoder from' to' >>= \(a,b) -> go (iteration + 1) a b -- These conditions are equally bad
+              InvalidSequence -> recover encoder from' to' >>= \(a,b) -> go (iteration + 1) a b -- since the input was truncated/invalid
               OutputUnderflow -> return Nothing -- Oops, out of buffer during decoding: ask the caller for more
 {-
 Note [Check *before* fill in withEncodedCString]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3ef5c89fd4ce8cbdbe2b6dd4070a8568d0eb70a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3ef5c89fd4ce8cbdbe2b6dd4070a8568d0eb70a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230126/614e5865/attachment-0001.html>


More information about the ghc-commits mailing list