[Haskell-cafe] Question about STRef

Antoine Rimlet antoine.rimlet at gmail.com
Thu Jan 26 10:26:53 UTC 2017


Hi list,

I try to get the following little program (a slightly modified "Man or
boy", it prints -14254067) work "as expected", that is, without consuming
lots of memory:

 import Control.Monad.ST
 import Data.STRef
 a k x1 x2 x3 x4 x5 =
   do kk <- newSTRef k
      let b = do k <- modifySTRef kk pred >> readSTRef kk; a k b x1 x2 x3 x4
      if k <= 0 then do x3' <- x3; x4' <- x4; return (x3' + x4')
                else do x5' <- x5; b' <- b; return (x5' + b')
 main = print (runST (a 22 (return 1) (return (-1)) (return (-1)) (return
1) (return 0)))

I use GHC 7.8.4, and executing this program uses about 2.5 GB of memory (or
about 3.5 GB with runghc).  However, the "equivalent" program in OCaml only
needs 4 MB (or 9 MB with the interpreter):

let rec a k x1 x2 x3 x4 x5 =
  let kk = ref k in let rec b () = begin decr kk; a !kk b x1 x2 x3 x4 end
  in if k <= 0 then let v = x3 () in v + x4 () else let v = x5 () in v + b
();;
print_int (a 22 (fun () -> 1) (fun () -> -1) (fun () -> -1) (fun () -> 1)
(fun () -> 0));; print_newline ();;

Therefore I suspect I'm doing something wrong, but I can't see what.  I did
try to use the strict version modifySTRef' as indicated in the manual, but
with no visible improvement.

Thanks,

Antoine
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170126/1f97e2ed/attachment.html>


More information about the Haskell-Cafe mailing list