Skip to content

Combining hPutBuilder + primMapByteStringBounded unsafe with reuse? #203

@vdukhovni

Description

@vdukhovni

The program below will hang if the iteration count (command-line argument) is sufficiently high, 253 loops or more (the default of 10 shows it working initially):

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TupleSections  #-}
module Main (main) where 

import Data.ByteString.Char8 as C8 (pack)
import Data.ByteString.Builder as B
import Data.ByteString.Builder.Prim as P
import Data.ByteString.Lazy as B
import Data.ByteString.Lazy.Char8 as L8
import Data.List as L
import System.IO as S
import System.Environment as S

main = do
    count >>= B.hPutBuilder S.stdout . loop
  where
    count :: IO Int
    count = maybe 10 read . fmap fst . L.uncons <$> S.getArgs

    loop n
        | n > 0 =
            B.string8 "iteration "
            <> B.intDec n
            <> B.char8 ' '
            <> B.word8 0x22
            <> P.primMapByteStringBounded enc
               do C8.pack "\\Escape me\192\"please\""
            <> B.word8 0x22
            <> B.char8 '\n'
            <> loop (n-1)
        | otherwise = mempty

    enc =
        P.condB
          do (\w -> w >= 0x20 && w < 0x7f)
          do P.condB
               do (\w -> w /= 0x22 && w /= 0x5c)
               do toB P.word8
               do fstUnit >$< esc >*< toB P.word8
          do P.condB
               do (> 99)
               do fstUnit >$< esc >*< P.word8Dec
               do P.condB
                    do (> 9)
                    do fstUnit . fstUnit
                           >$< esc >*< zero >*< P.word8Dec
                    do fstUnit . fstUnit . fstUnit
                           >$< esc >*< zero >*< zero >*< P.word8Dec
    toB = P.liftFixedToBounded
    esc = toB $ const 0x5c >$< P.word8
    fstUnit = ((), )
    zero = toB $ const 0x30 >$< P.word8

Metadata

Metadata

Assignees

No one assigned

    Labels

    No labels
    No labels

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions