question about comprehension or array creation

Hi, I tried to create an array like the following. "array (1,3) [(1,1), (2,2), (3,3)]" through code in .hs e = [1,2,3] array (1,3) [(i,v) | i<-[1..3], v<-e] but I got "array (1,3) [(1,3), (2,3), (3,3)]" why v is always 3 in this case? Can anyone shed some light on this? Thanks,

On Saturday 15 January 2011 15:19:05, cchang wrote:
Hi,
I tried to create an array like the following.
"array (1,3) [(1,1), (2,2), (3,3)]"
through code in .hs e = [1,2,3] array (1,3) [(i,v) | i<-[1..3], v<-e]
but I got "array (1,3) [(1,3), (2,3), (3,3)]"
why v is always 3 in this case? Can anyone shed some light on this?
Because [(x,y) | x <- list1, y <- list2] gives you the cartesian product of the two lists [each element of the first paired with each of the second], thus [(i,v) | i <- [1 .. 3], v <- e] = [(1,1),(1,2),(1,3),(2,1),(2,2),(2,3),(3,1),(3,2),(3,3)] and (as a known deviation from the Haskell Report), GHC overwrites array elements with multiple definitions on creation (according to the report, it should throw an error, but checking for duplicates would be too inefficient). Thus, with the list above, in each slot the three values 1, 2 and 3 are written (in that order), the last is the one you see afterwards. What you want is one of array (1,3) $ zip [1 .. 3] e {-# LANGUAGE ParallelListComp #-} -- Note the two `|' array (1,3) [(i,v) | i <- [1 .. 3] | v <- e] or equivalent.

The docs say:
[(i, e)] a list of associations of the form (index, value). Typically, this
list will be expressed as a comprehension. An association '(i, x)' defines the
value of the array at index i to be x.
I think the important part is that the array is used as a lookup for the values
to associate with the array. The lookup returns a ?random? one of the three
values in the list of tuples that have 1 as the first index. In this case it
happens to be 3. And so on.
This may help:
Prelude Array> let e = [1,2,3]
Prelude Array> array (1,3) [(i,v) | i<-[1..3], v<-e]
array (1,3) [(1,3),(2,3),(3,3)]
Prelude Array> array (1,9) [(i,v) | i<-[1..3], v<-e]
array (1,9) [(1,3),(2,3),(3,3),(4,*** Exception: (Array.!): undefined array
element
Prelude Array>
It couldn't look up a value for 4 so it failed...
Does that help?
--Tim
----- Original Message ----
From: cchang
participants (3)
-
cchang
-
Daniel Fischer
-
Tim Perry