Attached is a program with a space leak that I do not understand. I have
coded a simple 'map' function, once using unsafePerformIO and once
without. UnsafePerformIO has a space leak in some circumstances. In the
main program I demonstrate cases with and without space leak. Without
space leak the program writes a file to the disk until it is full. Any idea?

The original problem is a function that is compiled by LLVM and shall be
applied to a list in a mapAccumL manner.
{-
$ ghc --make -Wall -O -prof -auto-all InterleaveIO.hs
$ InterleaveIO +RTS -M1m -prof-all -RTS
-}
import System.IO.Unsafe (unsafePerformIO, unsafeInterleaveIO, )

makeSuccUnsafe1 :: IO ([Char] -> [Char])
makeSuccUnsafe1 =
   return $
      \ sig -> unsafePerformIO $ do
         let go xt =
               unsafeInterleaveIO $
               case xt of
                  [] -> return []
                  x:xs -> fmap (succ x :) $ go xs
         go sig

makeSuccUnsafe :: IO ([Char] -> [Char])
makeSuccUnsafe =
   return $
      \ sig ->
         let go xt =
               unsafePerformIO $
               case xt of
                  [] -> return []
                  x:xs -> return (succ x : go xs)
         in  go sig

makeSuccPlain :: IO ([Char] -> [Char])
makeSuccPlain =
   return $
      \ sig ->
         let go xt =
               case xt of
                  [] -> []
                  x:xs -> succ x : go xs
         in  go sig

splitAtLazy :: [b] -> [a] -> ([a],[a])
splitAtLazy nt xt =
   (\ ~(ys,zs) -> (ys,zs)) $
   case (nt,xt) of
      (_:ns, x:xs) ->
         let (ys,zs) = splitAtLazy ns xs
         in  (x:ys,zs)
      (_, xs) -> ([],xs)


makeTwoLists :: Char -> ([Char], [Char])
makeTwoLists c =
   splitAtLazy (repeat ()) $ repeat c

main :: IO ()
main = do
   succUnsafe <- makeSuccUnsafe
   succPlain  <- makeSuccPlain
   writeFile "test.txt" $
      let (prefix, suffix) = makeTwoLists 'a'
      in  case 3::Int of
             -- no leak
             0 -> succUnsafe $ prefix ++ suffix
             -- no leak
             1 -> succPlain  $ prefix ++ suffix
             -- no leak
             2 -> succPlain  prefix ++ succPlain  suffix
             -- leak
             3 -> succUnsafe prefix ++ succPlain  suffix
             -- no leak
             4 -> succPlain  prefix ++ succUnsafe suffix
             -- leak
             5 -> succUnsafe prefix ++ succUnsafe suffix
             _ -> error "not implemented"
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to