opt out of accursedUnutterablePerformIO
Bertram Felgenhauer
bertram.felgenhauer at googlemail.com
Tue Mar 6 21:28:12 UTC 2018
This has nothing to do with <insane>PerformIO.
> import Data.Char ( ord )
> import qualified Data.ByteString as B
> import qualified Data.ByteString.Char8 as BC
> import qualified Data.ByteString.Internal as BI
> import Test.QuickCheck
>
> -- | betweenLinesPS returns the B.ByteString between the two lines given,
> -- or Nothing if they do not appear.
> betweenLinesPS :: B.ByteString -> B.ByteString
> -> B.ByteString -> Maybe B.ByteString
> betweenLinesPS start end ps =
> case break (start ==) (linesPS1 ps) of
> -- replace this call here ^^^^^ with linesPS2
> -- and it crashes
> (_, _:rest@(bs1:_)) ->
> case BI.toForeignPtr bs1 of
> (ps1, s1, _) ->
> case break (end ==) rest of
> (_, bs2:_) ->
> case BI.toForeignPtr bs2 of
> (_, s2, _) -> Just $ BI.fromForeignPtr ps1 s1 (s2 - s1)
Ouch. What if the elements returned by linesPS1 are not based off the
same memory area? And indeed that happens. If add a bit of debug output,
(ps2, s2, _) -> traceShow ("oops", s1, s2, ps1, ps2) $
Just $ BI.fromForeignPtr ps1 s1 (s2 - s1)
then we get
("oops",2,4,0x0000004200107060,0x0000004200107060)
with linesPS1 but
("oops",0,4,0x0000000000000000,0x0000004200107060)
with linesPS2. The reason for the 0 pointer is that 'Data.ByteString.take'
has a special case when the empty string is produced:
take :: Int -> ByteString -> ByteString
take n ps@(PS x s l)
| n <= 0 = empty
| n >= l = ps
| otherwise = PS x s n
{-# INLINE take #-}
where
empty = PS nullForeignPtr 0 0
You are kind of lucky that linesPS1 works.
Cheers,
Bertram
More information about the Libraries
mailing list