Skip to content

Commit

Permalink
Merge #4
Browse files Browse the repository at this point in the history
4: fix support for text-2.0 r=nyghtly-derek a=jali-clarke

inspired by winterland1989#54 @ upstream (of which this is a fork), should fix segfaults for any builds using this library

Co-authored-by: Jinnah Ali-Clarke <[email protected]>
  • Loading branch information
nora-dingbot[bot] and jali-clarke authored Apr 10, 2024
2 parents 26f5b69 + 58b504d commit a8e5841
Showing 1 changed file with 39 additions and 0 deletions.
39 changes: 39 additions & 0 deletions Database/MySQL/Protocol/Escape.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}

{-|
Module : Database.MySQL.Protocol.Escape
Expand Down Expand Up @@ -32,6 +33,7 @@ The @\%@ and @\_@ sequences are used to search for literal instances of @%@ and

module Database.MySQL.Protocol.Escape where

import Control.Monad (forM_)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Internal as B
import Data.Text (Text)
Expand All @@ -44,6 +46,42 @@ import Foreign.Storable (peek, poke, pokeByteOff)
import GHC.IO (unsafeDupablePerformIO)

escapeText :: Text -> Text
#if MIN_VERSION_text(2,0,0)
escapeText (T.Text arr off len)
| len <= 0 = T.empty
| otherwise =
let (arr', len') = TA.run2 $ do
marr <- TA.new (len * 2)
loop arr (off + len) marr off 0
in T.Text arr' 0 len'
where
escape c marr ix = do
TA.unsafeWrite marr ix 92
TA.unsafeWrite marr (ix+1) c

loop oarr oend marr !ix !ix'
| ix == oend = return (marr, ix')
| otherwise = do
let c = TA.unsafeIndex oarr ix
cs = c : [ TA.unsafeIndex oarr (ix+1) | c >= 0xC0 ]
++ [ TA.unsafeIndex oarr (ix+2) | c >= 0xE0 ]
++ [ TA.unsafeIndex oarr (ix+3) | c >= 0xF0 ]
go2 = loop oarr oend marr (ix+1) (ix'+2)
goN = do
forM_ (zip [0..4] cs) $ \(di,c') -> TA.unsafeWrite marr (ix' + di) c'
loop oarr oend marr (ix + length cs) (ix' + length cs)
if | c == 0
|| c == 39
|| c == 34 -> escape c marr ix' >> go2 -- \0 \' \"
| c == 8 -> escape 98 marr ix' >> go2 -- \b
| c == 10 -> escape 110 marr ix' >> go2 -- \n
| c == 13 -> escape 114 marr ix' >> go2 -- \r
| c == 9 -> escape 116 marr ix' >> go2 -- \t
| c == 26 -> escape 90 marr ix' >> go2 -- \Z
| c == 92 -> escape 92 marr ix' >> go2 -- \\

| otherwise -> goN
#else
escapeText (T.Text arr off len)
| len <= 0 = T.empty
| otherwise =
Expand Down Expand Up @@ -77,6 +115,7 @@ escapeText (T.Text arr off len)
| c == 92 -> escape 92 marr ix' >> go2 -- \\

| otherwise -> TA.unsafeWrite marr ix' c >> go1
#endif

escapeBytes :: ByteString -> ByteString
escapeBytes (B.PS fp s len) = unsafeDupablePerformIO $ withForeignPtr fp $ \ a ->
Expand Down

0 comments on commit a8e5841

Please sign in to comment.