[Haskell-cafe] castIOUArray and hPutArray redux

Ben midfield at gmail.com
Fri May 2 21:13:48 EDT 2008


hi haskellers,

have the issues with castIOUArray (and thus hGetArray, hPutArray) in
Data.Array.IO discussed below been resolved?

http://www.haskell.org/pipermail/libraries/2003-January/thread.html

here is a (trivial) program which has rather unexpected behavior.
(i'm switching to Data.Binary in the meantime.)

import Data.Array.IO
import System.IO (IOMode(..), openBinaryFile, hClose)

dumpArray arr name = do
  h <- openBinaryFile name WriteMode
  w <- castIOUArray arr
  (l,u) <- getBounds w
  let len = u-1+1
  hPutArray h w len
  hClose h
  return len

loadArray name num = do
  arr <- newArray_ (1, num)
  h <- openBinaryFile name ReadMode
  read <- hGetArray h arr num
  if not(read == num) then
      error "Incorrect number of bytes read in from array!" else
      return arr

len = 20

main = do
  arr <- newArray (1, len) 1::IO(IOUArray Int Int)
  size <- dumpArray arr "foo"
  arr2' <- loadArray "foo" size
  arr2 <- (castIOUArray arr2')::IO(IOUArray Int Int)
  e1 <- getElems arr
  e2 <- getElems arr2
  print e1
  print e2
  print size
  print $ show (arr == arr2)


best, b


More information about the Haskell-Cafe mailing list