Re: re. Arrays and Assoc

1993-10-06 Thread Thomas Johnsson



 
 Thomas Johnsson says:
 
 If I recall correctly, the := to be used in array comprehensions was a
 consession to the FORTRAN/Id/Sisal community, so that array comprehensions
 would look more like they were used to.
 
 Both Arvind and I think this is notation is awful, and I don't recall
 either of us ASKING for it, so this was probably someone else's idea
 of a ``concession'' to the Id community!
 
 Nikhil

Oh. My apologies to the Id community.
-- Thomas




Re: Arrays and Assoc

1993-10-06 Thread Thomas Johnsson



 Let me just remind people what the LML arrays does:
 
 example:
 lmlarray 1 3 f list = 
 array [ 1:= f [ x | (1,x) - list],
 2:= f [ x | (2,x) - list],
 3:= f [ x | (3,x) - list]
   ]
 where array is like the ordinary Haskell array constructor function.
  ...
 It seems to me that it is a bit more general to apply f to the entire
 list accumulated at each index, rather than as an operator for foldr.
 
 If you want the list you can supply (:) and []. If not, you supply the
 operations, .[ ] 
 
This is of course a matter of taste, but I think that in some cases it is a
bit clumsier:

lmlarray l u (take 2) list

does seem simpler than, say

amap (take 2) (lmlarray' l u (:) list).

(I don't know how to express  take 2  as an operator for foldr).
Also, in LML there is only one array constructor function, lmlarray
(simply called array in LML), so an 'ordinary' array is obtained by 

lmlarray l u (\[ x ].x) list

(LML has . instead of - ).  Note that the pattern [ x ] in the function
forces the evaluation of the entire list and its indices, because,
intuitively, it has to be checked that there is no more than one element for
each index.

  and the intermediate list never gets built.

Yes, there is that. 
-- Thomas





Re: Arrays and Assoc

1993-10-06 Thread Thomas Johnsson



 I agree, but I also agree with Lennart that both sorts of arrays are needed.

Yes, I agree on that; language design is, as always, a compromise
between the desirable semantics (in this case, as lazy as possible),
and desirable efficency, and we don't know yet how to make lazy arrays
a la LML arrays as (potentially) efficient as current Haskell accumArray.

So here is a concrete suggestion:

1) Keep accumarray as it is (but like foldr-like behaviour instead of 
   foldl).

2) Add one more function to the prelude (or a standard module,
   to be imported explicitly):

filterArray f z b list =
array b [ i := foldr f z [ x | j - indices b, i==j ] 
| i - indices b 
]

The only difference between assocArray and filterArray would be
that filterArray is lazy and ignores indices out of bound.


Another possibility would be to have only one, the lazy one,
and to use strictness annotations when the extra efficiency is desired;
but there seems to be a consensus against strictness annotations
(re the "newtype" discussion thread.)
But maybe the distaste is only for annotated *constructors* ?


-- Thomas






re. Arrays and Assoc

1993-10-05 Thread nikhil



Thomas Johnsson says:

If I recall correctly, the := to be used in array comprehensions was a
consession to the FORTRAN/Id/Sisal community, so that array comprehensions
would look more like they were used to.

Both Arvind and I think this is notation is awful, and I don't recall
either of us ASKING for it, so this was probably someone else's idea
of a ``concession'' to the Id community!

Nikhil




Re: Arrays and Assoc

1993-10-05 Thread Lennart Augustsson



 1. We should get rid of Assoc.
I agree wholeheartedly!  Do we have tp consider backwards
compat?

 2. Arrays should be lazier.
I agree again.  But I think both kinds should be provided.

 3. AccumArray should mimic foldr, not foldl.
Right!

-- Lennart





Re: re. Arrays and Assoc

1993-10-05 Thread Joe Fasel


Nikhil says,

| Thomas Johnsson says:
|
| If I recall correctly, the := to be used in array comprehensions was a
| consession to the FORTRAN/Id/Sisal community, so that array comprehensions
| would look more like they were used to.
|
| Both Arvind and I think this is notation is awful, and I don't recall
| either of us ASKING for it, so this was probably someone else's idea
| of a ``concession'' to the Id community!
|
| Nikhil

All right!  I'm sorry!  ;-)

As I recall, Nikhil is right that neither he nor Arvind asked for this.
Some scientific programmers of my acquaintance did, though.  Id uses
= for this purpose, together with square brackets around the index.
This, of course, was not possible for Haskell.  The motivation was not
so much a "concession" to the Id community, as a concern for the
readability of

[((i,j), (f i j, g i j)) |

versus

[(i,j) := (f i j, g i j) |

or Id's

{matrix (1,N),(1,N) | [i,j] = (f i j, g i j) ||

(if I have that somewhere close to right).  The use of := for pairing
(or if you like, binding, or single-assignment) rather that assignment
did have a precedent in Val and Sisal.

All this syntax may seem of little consequence now, but at the time,
there was a genuine concern about the unpalatability of some choices
of syntax to a large community of programmers.

--Joe




Re: Arrays and Assoc

1993-10-05 Thread Thomas Johnsson



John Launchbury says:
 1. We should get rid of Assoc.
 
 When explaining my programs to other people I find this is a point of
 confusion. Imagine exaplaining array construction, "When I define an array,
 the comprehension produces a list of index/value pairs, only they are not
 written as pairs--these's this special type called Assoc. Oh, and don't be
 confused by :=. That's not assignment. It is an infix pairing operator."
 All of this is entirely unnecessary. Pairs have been used in maths for
 decades to represent exactly this sort of thing. I simply do not believe
 that [Assoc a b] provides me with any better information than [(a,b)].
 Worse, I often find myself having to redefine standard pair functions on
 elements of Assoc.

I agree. 
If I recall correctly, the := to be used in array comprehensions was a
consession to the FORTRAN/Id/Sisal community, so that array comprehensions
would look more like they were used to.
But := is a bit unintuitive if you're thinking e.g. FORTRAN:
a = array[1 := 2, 2 := 4]
does *not* mean 1 is assigned to 2, etc!

But I think we can have the cake and eat it too, if we get rid of the
restriction (which I never liked) that operators beginning with : must be a
constructor: just define 
a := b = (a,b)

[ While I'm at it: we should also get rid of the lower/uppercase
restrictions on constructor/nonconstructor names.
]


 2. Arrays should be lazier.
 
 I'm expecting Lennart to agree with me here as LML has the Right Thing. I
 am convinced that there is no semantic problem with this, and I think that
 even Simon isn't horrified at the implementation implications. The ability
 to define arrays by self reference is just as important as it is for lists.

I'm not exactly sure what you mean here. It is allready possible to define 
arrays by self-reference in Haskell.

 I am assuming that the fact that lazy indexes provide a better match with
 laziness elsewhere is clear, but I am willing to expand on this point if
 someone wants.
 
 3. AccumArray should mimic foldr, not foldl.
 
 This is tied up with the last point. The only advantage I can see with the
 present scheme would be if the array element could be used as the
 accumulator while the array was under construction. However, as arrays are
 non-strict in their *elements* this seems to be of no benefit. It seems to
 me highly sensible that the structure of the computation at each point
 should reflect the structure of the input sequence (i.e. the elements are
 in the same order). Furthermore, if a lazy operation is used (such as (:))
 then the result becomes available early (assuming point 2. above).
 

Again I wholeheartedly agree. 
Let me just remind people what the LML arrays does:

example:
lmlarray 1 3 f list = 
array [ 1:= f [ x | (1,x) - list],
2:= f [ x | (2,x) - list],
3:= f [ x | (3,x) - list]
  ]
where array is like the ordinary Haskell array constructor function.
In the implementation, the filtering needs to be done only once
and not n times, where n is the size of the array.
[ If anyone wants to know how this is done, I could expand on this. ]

It seems to me that it is a bit more general to apply f to the entire
list accumulated at each index, rather than as an operator for foldr.

-- Thomas







Re: Arrays and Assoc

1993-10-05 Thread Joe Fasel


John Launchbury says,
| Here are three comments directed particularly at Haskell 1.3 people, but
| obviously open to general feedback.
|
| 1. We should get rid of Assoc.
|
| When explaining my programs to other people I find this is a point of
| confusion. Imagine exaplaining array construction, "When I define an array,
| the comprehension produces a list of index/value pairs, only they are not
| written as pairs--these's this special type called Assoc. Oh, and don't be
| confused by :=. That's not assignment. It is an infix pairing operator."
| All of this is entirely unnecessary. Pairs have been used in maths for
| decades to represent exactly this sort of thing. I simply do not believe
| that [Assoc a b] provides me with any better information than [(a,b)].
| Worse, I often find myself having to redefine standard pair functions on
| elements of Assoc.

Mea maxima culpa.  I must admit that the reason for introducing Assoc
was syntactic.  Making a semantic distinction between pairs and assocs
for a syntactic purpose should have set off alarms; somehow, I managed
to ignore them.

At the time this decision was made, arrays and array syntax were something
of a contentious issue.  Even the use of infix ! for indexing was a
source of anguish for potential users of arrays, and the fear was that
pair syntax in "array comprehensions" would be unwieldy, particularly
for multidimensional arrays.  Consider a matrix of pairs (a typical
construction in scientific mesh algorithms).

Lennart asks whether we should be concerned about an upward compatibility
problem.  Thomas suggests that we could drop the syntactic restrictions
on constructor and nonconstructor symbols and define (:=) as a pairing
function.  That almost does the job, but there are some programs that
pattern-match Assocs.  Also, I think there will be objection in some
quarters to dropping the separation of name spaces.  Here are two more
possibilities:

2.  Provide a way to declare synonyms for constructors, and
use it to equate := with (,).

3.  Don't provide such a general facility, but hack in :=
as a special case (rather like prefix minus).


| 2. Arrays should be lazier.
|
| I'm expecting Lennart to agree with me here as LML has the Right Thing. I
| am convinced that there is no semantic problem with this, and I think that
| even Simon isn't horrified at the implementation implications. The ability
| to define arrays by self reference is just as important as it is for lists.
| I am assuming that the fact that lazy indexes provide a better match with
| laziness elsewhere is clear, but I am willing to expand on this point if
| someone wants.

I agree, but I also agree with Lennart that both sorts of arrays are needed.
The historical context again:  Accumulators had been added to Id because
too many scientific programs couldn't live without them (or else effects).
Pragmatically, the accumulations in these programs were almost always
sums.  (histogramming, Monte Carlo tallying)  People needed to be convinced
that this could be done efficiently.


| 3. AccumArray should mimic foldr, not foldl.
|
| This is tied up with the last point. The only advantage I can see with the
| present scheme would be if the array element could be used as the
| accumulator while the array was under construction. However, as arrays are
| non-strict in their *elements* this seems to be of no benefit. It seems to
| me highly sensible that the structure of the computation at each point
| should reflect the structure of the input sequence (i.e. the elements are
| in the same order). Furthermore, if a lazy operation is used (such as (:))
| then the result becomes available early (assuming point 2. above).
|
| John.
|

Agreed again.  The historical reason for the choice of foldl should be
evident from the remarks above.

Since all of these decisions had to do with Id arrays, I'm pleased
to hear from Nikhil that pH people are thinking along the same lines
as John and Lennart.  Consensus!

--Joe




Re: Arrays and Assoc

1993-10-05 Thread John Launchbury



But I think we can have the cake and eat it too, if we get rid of the
restriction (which I never liked) that operators beginning with : must be a
constructor: just define 
a := b = (a,b)

Unfortunately that won't work if := had been used in patterns. I think
backward compatibility is an issue. The standard technique of supporting
Assoc but with compiler warnings will probably have to be used.

---

I'm not exactly sure what you mean here. It is allready possible to define 
arrays by self-reference in Haskell.

Haskell arrays are strict in the indices. That is, the whole of the
defining list is consumed and the indices examined before the array becomes
available. Thus, a recursive array definition in which the *index
calculation* depends on the earlier part of the array gives bottom. The
current definition allows for a recursive definition so long as it is only
the values of the array elements which depend on the array. This is not
always sufficient.

---

Let me just remind people what the LML arrays does:

example:
lmlarray 1 3 f list = 
array [ 1:= f [ x | (1,x) - list],
2:= f [ x | (2,x) - list],
3:= f [ x | (3,x) - list]
  ]
where array is like the ordinary Haskell array constructor function.
 ...
It seems to me that it is a bit more general to apply f to the entire
list accumulated at each index, rather than as an operator for foldr.

If you want the list you can supply (:) and []. If not, you supply the
operations, and the intermediate list never gets built.

John.





Arrays and Assoc

1993-10-05 Thread rabin


John Launchbury makes the suggestion, inter alia, that Haskell 1.3
`should get rid of Assoc.'

Reading some of the followup messages, I see that there is some
division on this point.  Those closer to the scientific applications
community, such as Nikhil and Joe Fasel's acquaintances, seem to be
warmed by the familiar sight of `:=', whereas the more
pure-mathematically motivated commentators seem to find the (assuredly
equivalent) pair constructor more congenial.

There have also been some noises about compatibility, since adopting
John's suggestion will definitely stop old code dead in its tracks
(namely, in the type-checker).

Clearly, what's needed to satisfy all parties and make Haskell 1.3 the
rousing success that it deserves to be is to introduce a class
`Associator' with methods `key', `image', `associate', `toPair',
`toAssoc'.  Then the array prelude functions could be redefined in
terms of the class by (1) pattern-matching on `toAssoc assoc' instead
of `assoc' for each variable assoc :: Assoc, and (2) replacing
explicit applications of the constructor `:=' by `associate'.  I don't
think user code would have to change, but users might wonder about the
new inferred type constraints on their array code.  

Of course, to recover efficiency, all Haskell implementors will have
to treat the class `Associator' specially so that no dictionary usage
is actually produced (as long as the users haven't perversely
introduced their own instances, which suggests some wondrous new
interpretations of the concept `array').

I intended this message to be humorous when I started, but I'm
beginning to think this is a reasonable approach to such matters.  So
let's generalize with wild abandon: what would be the consequences of
automatically deriving an class abstraction for _every_ Haskell data
type?  Even function types are eligible via the abstract operation
`apply'.  What new vistas now unfold?

-
Dan Rabin   I must Create a System 
Department of Computer Scienceor be enslav'd by another Man's. 
P.O. Box 208285 I will not Reason  Compare:   
New Haven, CT 06520-8285  my business is to Create.
   
[EMAIL PROTECTED] -- William Blake, `Jerusalem'
-