Re: [Haskell-cafe] Bug in writeArray?

2009-09-24 Thread Grzegorz Chrupała
2009/9/23 Bulat Ziganshin bulat.zigans...@gmail.com:
 Hello Grzegorz,

 Wednesday, September 23, 2009, 7:19:59 PM, you wrote:

 This seems like a bug in the implementation of writeArray: when passed
   let (l,u) = ((0,10),(20,20))

 writeArray computes raw index (from 0 to total number of array
 elements) and check that this index is correct. with multi-dimensional
 arrays this approach may lead to wrong results, as you mentioned. it's
 known problem that isn't fixed for a long time probably due to
 efficiency cautions.

Hmm, I understand that efficiency is an issue, but in that case
shouldn't unsafe writing be provided by and unsafeWriteArray function,
while writeArray does proper range checking?

Or at least this problem with writeArray should be clearly indicated
in the documentation. I for one spent several hours debugging before
finding out about this lack of proper range checks so it's not an
imaginary problem.

--
Grzegorz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bug in writeArray?

2009-09-24 Thread Iavor Diatchki
I agree with Grzegorz.  Perhaps we should file a bug-report, if there
isn't one already?
-Iavor

2009/9/24 Grzegorz Chrupała pite...@gmail.com:
 2009/9/23 Bulat Ziganshin bulat.zigans...@gmail.com:
 Hello Grzegorz,

 Wednesday, September 23, 2009, 7:19:59 PM, you wrote:

 This seems like a bug in the implementation of writeArray: when passed
   let (l,u) = ((0,10),(20,20))

 writeArray computes raw index (from 0 to total number of array
 elements) and check that this index is correct. with multi-dimensional
 arrays this approach may lead to wrong results, as you mentioned. it's
 known problem that isn't fixed for a long time probably due to
 efficiency cautions.

 Hmm, I understand that efficiency is an issue, but in that case
 shouldn't unsafe writing be provided by and unsafeWriteArray function,
 while writeArray does proper range checking?

 Or at least this problem with writeArray should be clearly indicated
 in the documentation. I for one spent several hours debugging before
 finding out about this lack of proper range checks so it's not an
 imaginary problem.

 --
 Grzegorz
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bug in writeArray?

2009-09-24 Thread David Menendez
2009/9/24 Iavor Diatchki iavor.diatc...@gmail.com:
 I agree with Grzegorz.  Perhaps we should file a bug-report, if there
 isn't one already?

http://hackage.haskell.org/trac/ghc/ticket/2120

Apparently, it's fixed in GHC 6.12.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bug in writeArray?

2009-09-24 Thread Duncan Coutts
On Thu, 2009-09-24 at 13:53 +0200, Grzegorz Chrupała wrote:
 2009/9/23 Bulat Ziganshin bulat.zigans...@gmail.com:
  Hello Grzegorz,
 
  Wednesday, September 23, 2009, 7:19:59 PM, you wrote:
 
  This seems like a bug in the implementation of writeArray: when passed
let (l,u) = ((0,10),(20,20))
 
  writeArray computes raw index (from 0 to total number of array
  elements) and check that this index is correct. with multi-dimensional
  arrays this approach may lead to wrong results, as you mentioned. it's
  known problem that isn't fixed for a long time probably due to
  efficiency cautions.
 
 Hmm, I understand that efficiency is an issue, but in that case
 shouldn't unsafe writing be provided by and unsafeWriteArray function,
 while writeArray does proper range checking?
 
 Or at least this problem with writeArray should be clearly indicated
 in the documentation. I for one spent several hours debugging before
 finding out about this lack of proper range checks so it's not an
 imaginary problem.

It's now fixed:

http://hackage.haskell.org/trac/ghc/ticket/2120#comment:13

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Bug in writeArray?

2009-09-23 Thread Grzegorz Chrupała
Hi all,
This seems like a bug in the implementation of writeArray: when passed
an out-of-range index it silently writes to an incorrect index in the
array.
--

import Data.Array.IO
import Data.Array.Unboxed

main = do
  let (l,u) = ((0,10),(20,20))
  marr - newArray (l,u) 0 :: IO (IOUArray (Int,Int) Int)
  let badi = (10,9)
  print (inRange (l,u) badi)
  writeArray marr badi 1
  arr - freeze marr :: IO (UArray (Int,Int) Int)
  print . filter ((/=0) . snd) . assocs  $ arr

--
Grzegorz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bug in writeArray?

2009-09-23 Thread Bulat Ziganshin
Hello Grzegorz,

Wednesday, September 23, 2009, 7:19:59 PM, you wrote:

 This seems like a bug in the implementation of writeArray: when passed
   let (l,u) = ((0,10),(20,20))

writeArray computes raw index (from 0 to total number of array
elements) and check that this index is correct. with multi-dimensional
arrays this approach may lead to wrong results, as you mentioned. it's
known problem that isn't fixed for a long time probably due to
efficiency cautions. the error is here:

data Ix i = Array i e
 = Array !i -- the lower bound, l
 !i -- the upper bound, u
 !Int   -- a cache of (rangeSize (l,u))
-- used to make sure an index is
-- really in range
 (Array# e) -- The actual elements

(!) :: Ix i = Array i e - i - e
arr@(Array l u n _) ! i = unsafeAt arr $ safeIndex (l,u) n i

safeIndex :: Ix i = (i, i) - Int - i - Int
safeIndex (l,u) n i = let i' = unsafeIndex (l,u) i
  in if (0 = i')  (i'  n)
 then i'
 else error Error in array index


obviously, safeIndex should use inRange call instead


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe