Re: [Haskell-cafe] Error in array index.

2009-06-25 Thread Claus Reinke

 It's too bad that indexes are `Int` instead of `Word` under
 the hood. Why is `Int` used in so many places where it is
 semantically wrong? Not just here but also in list indexing...
 Indices/offsets can only be positive and I can't see any good
 reason to waste half the address space -- yet we encounter
 this problem over and over again.


Readers who disliked the above also disliked the following:

   index out of range error message regression
   http://hackage.haskell.org/trac/ghc/ticket/2669

   Int / Word / IntN / WordN are unequally optimized
   http://hackage.haskell.org/trac/ghc/ticket/3055

   Arrays allow out-of-bounds indexes
   http://hackage.haskell.org/trac/ghc/ticket/2120
   ..

Not to mention that many serious array programmers use their
own array libraries (yes, plural:-(, bypassing the standard, so 
their valuable experience/expertise doesn't result in improvements 
in the standard array libraries (nor have they agreed on a new API). 

If any of this is affecting your use of GHC or libraries, you might 
want to add yourself to relevant tickets, or add new tickets. Small
bug fixes, alternative designs and grand array library reunification 
initiatives might also be welcome.


Claus

PS. You could, of course, rebase your array indices to make
   use of the negatives, so the address space isn't wasted, just
   made difficult to use.


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


Re[2]: [Haskell-cafe] Error in array index.

2009-06-25 Thread Bulat Ziganshin
Hello Claus,

Thursday, June 25, 2009, 11:50:12 AM, you wrote:

 PS. You could, of course, rebase your array indices to make
 use of the negatives, so the address space isn't wasted, just
 made difficult to use.

no, he can't - internally indexes are always counted from 0, so array
cannot have more than 2g-1 elements

i think the best he can do is to write his own ArraOfBool
implementation with Word indices


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

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


[Haskell-cafe] Error in array index.

2009-06-24 Thread Jason Dusek
  I'm using tuples to index into a `UArray` created like this:

fromList :: [(Word16, Word16)] - UArray (Word16, Word16) Bool
fromList list=  runSTUArray $ do
  arr   -  empty
  return arr

empty   ::  ST s (STUArray s (Word16, Word16) Bool)
empty=  newArray ((0,0), (0x,0x)) False

  You'll notice this example doesn't do much; I'm not able to
  get much mileage so far. For example:

 Array16Bit.fromList [(1,2), (2,3)]
array ((0,0),(65535,65535)) [((0,0),*** Exception: Error in array index

  What do I need to do to debug this?

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


Re: [Haskell-cafe] Error in array index.

2009-06-24 Thread Bulat Ziganshin
Hello Jason,

Wednesday, June 24, 2009, 1:55:24 PM, you wrote:

 array ((0,0),(65535,65535)) [((0,0),*** Exception: Error in array index

   What do I need to do to debug this?

i think that it may be a bit too large for internal Int indicies:

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



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

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


Re: [Haskell-cafe] Error in array index.

2009-06-24 Thread Ketil Malde
Bulat Ziganshin bulat.zigans...@gmail.com writes:

 array ((0,0),(65535,65535)) [((0,0),*** Exception: Error in array index

 i think that it may be a bit too large for internal Int indicies:

Aren't you asking for a 4G element array here, so with a 32bit
wraparound the array will be some multiple of 4GB, and be truncated
(silently, of course) down to zero, as per Int(32) behavior.  So in
effect, you have a zero-length underlying array, but the array
implementation still keeps track of the real indices and tries to
print some contents.  (Correct?)

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

Since array dereferencing are now checked against the underlying array
instead of the real indices, you get this kind of inconsistency.  It
is greatly surprising to me that this has not been fixed.

As long as 'unsafeAt' gives you the speed without the safety, I don't
think the default dereferencing shouldn't sacrifice helpful error
messages and predicability.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error in array index.

2009-06-24 Thread Jason Dusek
2009/06/24 Ketil Malde ke...@malde.org:
 Bulat Ziganshin bulat.zigans...@gmail.com writes:

     array ((0,0),(65535,65535)) [((0,0),*** Exception: Error in array index

 i think that it may be a bit too large for internal Int indicies:

 Aren't you asking for a 4G element array here, so with a 32bit
 wraparound the array will be some multiple of 4GB

  It's a bit array. It'd be 512MiB.

 So in effect, you have a zero-length underlying array, but the
 array implementation still keeps track of the real indices and
 tries to print some contents.  (Correct?)

  I don't quite understand your reasoning here.

 Since array dereferencing are now checked against the
 underlying array instead of the real indices, you get this
 kind of inconsistency.  It is greatly surprising to me that
 this has not been fixed.

 As long as 'unsafeAt' gives you the speed without the safety,
 I don't think the default dereferencing shouldn't sacrifice
 helpful error messages and predicability.

  This arrangement would make me LOL if it weren't my own
  project...

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


Re: [Haskell-cafe] Error in array index.

2009-06-24 Thread Daniel Fischer
Am Mittwoch 24 Juni 2009 18:50:49 schrieb Jason Dusek:
 2009/06/24 Ketil Malde ke...@malde.org:
  Bulat Ziganshin bulat.zigans...@gmail.com writes:
      array ((0,0),(65535,65535)) [((0,0),*** Exception: Error in array
  index
 
  i think that it may be a bit too large for internal Int indicies:
 
  Aren't you asking for a 4G element array here, so with a 32bit
  wraparound the array will be some multiple of 4GB

   It's a bit array. It'd be 512MiB.

  So in effect, you have a zero-length underlying array, but the
  array implementation still keeps track of the real indices and
  tries to print some contents.  (Correct?)

   I don't quite understand your reasoning here.

The 'length' of the array, as in 'number of elements' is calculated by 
multiplying the 
lengths in each dimension

sz = rangeSize d1 * rangeSize d2

rangeSize (0,65535) = 2^16
(2^16)^2 = 2^32
2^32 :: Int = 0 on 32-bit systems

I don't know if that's how it's implemented, but that's the reasoning leading 
to an array 
of size 0.


  Since array dereferencing are now checked against the
  underlying array instead of the real indices, you get this
  kind of inconsistency.  It is greatly surprising to me that
  this has not been fixed.
 
  As long as 'unsafeAt' gives you the speed without the safety,
  I don't think the default dereferencing shouldn't sacrifice
  helpful error messages and predicability.

   This arrangement would make me LOL if it weren't my own
   project...

 --
 Jason Dusek

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


Re[2]: [Haskell-cafe] Error in array index.

2009-06-24 Thread Bulat Ziganshin
Hello Jason,

Wednesday, June 24, 2009, 8:50:49 PM, you wrote:

 Aren't you asking for a 4G element array here, so with a 32bit
 wraparound the array will be some multiple of 4GB

   It's a bit array. It'd be 512MiB.

internally it's indexed by plain Int :)

when library checks index boundary, it finds out that your array
contains 0 elements, so any index should be illegal :)

try to work via unsafe indexing operations... although anyway you will
be unable to specify 4G elements array in 32-bit environment

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

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


Re: [Haskell-cafe] Error in array index.

2009-06-24 Thread Jason Dusek
2009/06/24 Daniel Fischer daniel.is.fisc...@web.de:
 Am Mittwoch 24 Juni 2009 18:50:49 schrieb Jason Dusek:
  2009/06/24 Ketil Malde ke...@malde.org:
   So in effect, you have a zero-length underlying array, but
   the array implementation still keeps track of the real
   indices and tries to print some contents.  (Correct?)
 
  I don't quite understand your reasoning here.

 The 'length' of the array, as in 'number of elements' is
 calculated by multiplying the lengths in each dimension

 [...]

 I don't know if that's how it's implemented, but that's the
 reasoning leading to an array of size 0.

  That seems reasonable, actually. My system is nominally 64bit
  (it's MacIntel) but the kernel claims `i386` so there we are.

  It's too bad that indexes are `Int` instead of `Word` under
  the hood. Why is `Int` used in so many places where it is
  semantically wrong? Not just here but also in list indexing...
  Indices/offsets can only be positive and I can't see any good
  reason to waste half the address space -- yet we encounter
  this problem over and over again.

  This problem probably runs pretty deep. Just having a flexible
  backing index type is only part of the issue, since pointer
  indexing operations work with `Int` as well. If you wanted to
  hide all this stuff, you'd need to segment particularly large
  unboxed arrays...

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


Re[2]: [Haskell-cafe] Error in array index.

2009-06-24 Thread Bulat Ziganshin
Hello Jason,

Wednesday, June 24, 2009, 9:51:59 PM, you wrote:

   It's too bad that indexes are `Int` instead of `Word` under

actually, it doesn't matter too much except for Bools. 2gb array is a
way too much for most 32-bit systems, in particular, in windows 32-bit
program cannot alloc memory block larger than 2gb

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

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


Re: Re[2]: [Haskell-cafe] Error in array index.

2009-06-24 Thread Jason Dusek
2009/06/24 Bulat Ziganshin bulat.zigans...@gmail.com:
 Wednesday, June 24, 2009, 9:51:59 PM, you wrote:
  It's too bad that indexes are `Int` instead of `Word` under

 actually, it doesn't matter too much except for Bools. 2gb
 array is a way too much for most 32-bit systems, in
 particular, in windows 32-bit program cannot alloc memory
 block larger than 2gb

  But on everything but Windows...

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


Re: Re[2]: [Haskell-cafe] Error in array index.

2009-06-24 Thread Jason Dusek
  So now I get to write a blog post called Compact Bit Arrays
  in Haskell or some such.

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


Re[4]: [Haskell-cafe] Error in array index.

2009-06-24 Thread Bulat Ziganshin
Hello Jason,

Wednesday, June 24, 2009, 10:15:14 PM, you wrote:

 particular, in windows 32-bit program cannot alloc memory
 block larger than 2gb

   But on everything but Windows...

well, people never thought about such things until they really get
into using 4gb RAM with 32-bit systems :)


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

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


Re: [Haskell-cafe] Error in array index.

2009-06-24 Thread wren ng thornton

Jason Dusek wrote:

  Why is `Int` used in so many places where it is
  semantically wrong? Not just here but also in list indexing...
  Indices/offsets can only be positive and I can't see any good
  reason to waste half the address space -- yet we encounter
  this problem over and over again.


I think history is the biggest culprit. Haskell98 doesn't ship with Nat 
and Natural types, so Int and Integer are used instead. And then the 
Word* types come around for bit bashing.


Another big culprit is that this is one of the places where Haskell 
gives a nod to performance. Many Prelude functions like take, drop, and 
(!!) should accept any Natural. Failing that, they should accept Integer 
and do the right thing for negatives. But most of the time an Int is 
sufficient, and that's what they take; this increases CPU performance, 
but more importantly it increases programmer performance since they 
don't need to write All Those Conversion Functions(tm). Though 
programmer performance suffers when an unbounded type is actually 
required, or when negatives aren't handled correctly.


The haskell' committee is considering adding a Nat or Natural type, so 
history may eventually be corrected. However, in order to deal with them 
in an, er, natural way the numeric typeclass hierarchy needs fixing. At 
the very least we'd want to separate (+) and (*) from (-), negate, abs, 
and signum so that we have a class for Nat and Natural that doesn't have 
partial functions. A safe version of (-) would be nice, though it's an 
open question whether x-(x+y) should be 0 or Nothing[1]. It's also 
unclear what should happen to fromInteger: do we have fromNatural be a 
subfunction of it, or do we desugar negative literals with negate and 
fromNatural and drop fromInteger entirely?



[1] My vote would be for Nothing so that we don't loose the information 
about whether the two operands are equal. Though this has the 
unfortunate side effect of requiring more plumbing. We could always 
offer both variants, so that clients who use subtraction and equality 
comparisons together frequently can use the Maybe version and those who 
want the other mathematical function can use it instead.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe