comp.lang.ada
 help / color / mirror / Atom feed
* Copying rows in a two dimensional array.
@ 2010-02-01  2:11 Peter C. Chapin
  2010-02-01  4:42 ` Jeffrey R. Carter
                   ` (4 more replies)
  0 siblings, 5 replies; 48+ messages in thread
From: Peter C. Chapin @ 2010-02-01  2:11 UTC (permalink / raw)


This is something of a newbie question..

I'm working with a two dimensional array of floating point values. Lets call
it A. The array has type

type Matrix is array(Positive range <>, Positive range <>) of Floating_Type;

I need to exchange two rows in this array. What I'd like to do is something
along these lines:

   Temp_Array      := A(I, 1 .. Size);
   A(I, 1 .. Size) := A(K, 1 .. Size);
   A(K, 1 .. Size) := Temp_Array;

The compiler (GNAT GPL 2009) has a problem with this syntax and, after looking
into it some, I think that's because slicing only works for one dimensional
arrays. Fair enough.

So I thought, "Perhaps A needs to be an array of arrays."

type Matrix is array(Positive range <>) of WHAT_EXACTLY?

Apparently the component type of an array needs to be fully constrained (which
again makes sense) yet I don't know the size I'll want to use at the point
where this type is declared.

So now I'm thinking that I'll have to write a procedure to explicity swap each
row element one at a time. Of course this is not a terrible thing, but I'm
wondering if there is a more elegant way that I'm missing. I have some
confidence that the compiler can optimize slice operations reasonably well.
I'm less confident about its ability to optimize element by element
operations (maybe I'm overly pessimistic).

Peter




^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01  2:11 Copying rows in a two dimensional array Peter C. Chapin
@ 2010-02-01  4:42 ` Jeffrey R. Carter
  2010-02-01  6:55 ` Niklas Holsti
                   ` (3 subsequent siblings)
  4 siblings, 0 replies; 48+ messages in thread
From: Jeffrey R. Carter @ 2010-02-01  4:42 UTC (permalink / raw)


Peter C. Chapin wrote:
> 
> type Matrix is array(Positive range <>, Positive range <>) of Floating_Type;
> 
> I need to exchange two rows in this array. What I'd like to do is something
> along these lines:
> 
>    Temp_Array      := A(I, 1 .. Size);
>    A(I, 1 .. Size) := A(K, 1 .. Size);
>    A(K, 1 .. Size) := Temp_Array;
> 
> The compiler (GNAT GPL 2009) has a problem with this syntax and, after looking
> into it some, I think that's because slicing only works for one dimensional
> arrays. Fair enough.

That's correct: slicing is only defined for one-D arrays.

> So I thought, "Perhaps A needs to be an array of arrays."
> 
> type Matrix is array(Positive range <>) of WHAT_EXACTLY?

Row_Vector?

> Apparently the component type of an array needs to be fully constrained (which
> again makes sense) yet I don't know the size I'll want to use at the point
> where this type is declared.

Correct again: array components must be definite.

I'm not aware of a solution other than the brute force approach.

-- 
Jeff Carter
"Gentlemen, you can't fight in here. This is the War Room!"
Dr. Strangelove
30



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01  2:11 Copying rows in a two dimensional array Peter C. Chapin
  2010-02-01  4:42 ` Jeffrey R. Carter
@ 2010-02-01  6:55 ` Niklas Holsti
  2010-02-01 23:36   ` Peter C. Chapin
  2010-02-04  4:27   ` Hibou57 (Yannick Duchêne)
  2010-02-01  8:37 ` Dmitry A. Kazakov
                   ` (2 subsequent siblings)
  4 siblings, 2 replies; 48+ messages in thread
From: Niklas Holsti @ 2010-02-01  6:55 UTC (permalink / raw)


Peter C. Chapin wrote:
> This is something of a newbie question..
> 
> I'm working with a two dimensional array of floating point values. Lets call
> it A. The array has type
> 
> type Matrix is array(Positive range <>, Positive range <>) of Floating_Type;
> 
> I need to exchange two rows in this array. What I'd like to do is something
> along these lines:
> 
>    Temp_Array      := A(I, 1 .. Size);
>    A(I, 1 .. Size) := A(K, 1 .. Size);
>    A(K, 1 .. Size) := Temp_Array;
> 
> The compiler (GNAT GPL 2009) has a problem with this syntax and, after looking
> into it some, I think that's because slicing only works for one dimensional
> arrays. Fair enough.
> 
> So I thought, "Perhaps A needs to be an array of arrays."
> 
> type Matrix is array(Positive range <>) of WHAT_EXACTLY?
> 
> Apparently the component type of an array needs to be fully constrained (which
> again makes sense) yet I don't know the size I'll want to use at the point
> where this type is declared.

One solution -- which may not match your design in other respects -- is 
to make the Matrix an array of accesses to rows:

    type Row is array (Positive range <>) of Float;
    type Row_Ref is access Row;
    type Matrix is array (Positive range <>) of Row_Ref;

Exchanging two rows is then very quick:

    Temp_Ref := A(I);
    A(I)     := A(K);
    A(K)     := Temp_Ref;

However, you now have to allocate the rows using "new Row (1 .. Size)" 
and perhaps later deallocate them using Unchecked_Deallocation.

Another solution -- which perhaps you have considered -- is to use a 
generic package to define row and matrix types:

    generic Size : Positive;
    package Matrices
    is
       type Row is array (1 .. Size) of Float;
       type Matrix is array (1 .. Size) of Row;
    end Matrices;

However, this will probably force some other parts of your code to 
become generic, too, parametrized either by a Size, or by an instance of 
Matrices.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01  2:11 Copying rows in a two dimensional array Peter C. Chapin
  2010-02-01  4:42 ` Jeffrey R. Carter
  2010-02-01  6:55 ` Niklas Holsti
@ 2010-02-01  8:37 ` Dmitry A. Kazakov
  2010-02-02  0:11   ` Randy Brukardt
  2010-02-01 22:10 ` Jerry
  2010-02-04  4:13 ` Hibou57 (Yannick Duchêne)
  4 siblings, 1 reply; 48+ messages in thread
From: Dmitry A. Kazakov @ 2010-02-01  8:37 UTC (permalink / raw)


On Sun, 31 Jan 2010 21:11:12 -0500, Peter C. Chapin wrote:

> So I thought, "Perhaps A needs to be an array of arrays."
> 
> type Matrix is array(Positive range <>) of WHAT_EXACTLY?
> 
> Apparently the component type of an array needs to be fully constrained (which
> again makes sense)

Not really. Arrays should have been allowed to have discriminants. That was
missed in the language design. If they had discriminants you could write:

type Row is array (Positive range <>) of Float;
type Matrix (Width : Positive) is
   array (Positive range <>) of Row (1..Width);

(Of course  the array bounds should have been discriminants rather than
attributes)

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01  2:11 Copying rows in a two dimensional array Peter C. Chapin
                   ` (2 preceding siblings ...)
  2010-02-01  8:37 ` Dmitry A. Kazakov
@ 2010-02-01 22:10 ` Jerry
  2010-02-02  0:07   ` Randy Brukardt
  2010-02-02  8:52   ` Jean-Pierre Rosen
  2010-02-04  4:13 ` Hibou57 (Yannick Duchêne)
  4 siblings, 2 replies; 48+ messages in thread
From: Jerry @ 2010-02-01 22:10 UTC (permalink / raw)


I've never understood why Ada does not allow slicing in
multidimensional arrays. What are the safety issues involved? And how
is it safe to force the programmer into ad hoc methods?

Jerry



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01  6:55 ` Niklas Holsti
@ 2010-02-01 23:36   ` Peter C. Chapin
  2010-02-04  4:27   ` Hibou57 (Yannick Duchêne)
  1 sibling, 0 replies; 48+ messages in thread
From: Peter C. Chapin @ 2010-02-01 23:36 UTC (permalink / raw)


Niklas Holsti wrote:

> Another solution -- which perhaps you have considered -- is to use a 
> generic package to define row and matrix types:
> 
>     generic Size : Positive;
>     package Matrices
>     is
>        type Row is array (1 .. Size) of Float;
>        type Matrix is array (1 .. Size) of Row;
>     end Matrices;
> 
> However, this will probably force some other parts of your code to 
> become generic, too, parametrized either by a Size, or by an instance of 
> Matrices.
> 

Actually I hadn't considered this, but such an approach might work well for
me. I'll have to consider it more.

Thanks!

Peter




^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01 22:10 ` Jerry
@ 2010-02-02  0:07   ` Randy Brukardt
  2010-02-02  8:52   ` Jean-Pierre Rosen
  1 sibling, 0 replies; 48+ messages in thread
From: Randy Brukardt @ 2010-02-02  0:07 UTC (permalink / raw)


I presume this was because the elements in question are not necessarily 
adjacent. As such the code ends up being exactly the same (or sometimes 
worse) than an explicitly coded loop.

And honestly, I don't see any real advantage to slices in terms of safety 
(given that indexes are checked for in-range, as they are in Ada). I make 
just as many mistakes with slices as I do with loops -- I find it hard to 
figure out the ends of the two slices for assignment (which have to be the 
same length - mine only are about 1/2 of the time); it's about the same 
difficulty as figuring out the offset amount when writing a loop to copy 
items. So I see it as a wash, other than that a one-dimensional slice can 
generate much better code (using a direct memory-memory move the for entire 
amount). The safety win comes for whole object assignments, not parts.

                           Randy.

"Jerry" <lanceboyle@qwest.net> wrote in message 
news:ed36036c-8318-4f27-aaae-5329a8bfc83d@t31g2000prh.googlegroups.com...
> I've never understood why Ada does not allow slicing in
> multidimensional arrays. What are the safety issues involved? And how
> is it safe to force the programmer into ad hoc methods?
>
> Jerry 





^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01  8:37 ` Dmitry A. Kazakov
@ 2010-02-02  0:11   ` Randy Brukardt
  2010-02-07 16:13     ` Robert A Duff
  0 siblings, 1 reply; 48+ messages in thread
From: Randy Brukardt @ 2010-02-02  0:11 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote in message 
news:178rg3rch8qdu$.13cgkywb09x3p.dlg@40tude.net...
> On Sun, 31 Jan 2010 21:11:12 -0500, Peter C. Chapin wrote:
>
>> So I thought, "Perhaps A needs to be an array of arrays."
>>
>> type Matrix is array(Positive range <>) of WHAT_EXACTLY?
>>
>> Apparently the component type of an array needs to be fully constrained 
>> (which
>> again makes sense)
>
> Not really. Arrays should have been allowed to have discriminants. That 
> was
> missed in the language design.

Early Ada 9x had discriminants for arrays. The capability got dropped when 
lots of "nice-to-have" features got dropped from Ada 95. Such "array" types 
have to be implemented as discriminant dependent records anyway; there is no 
real hope of performance improvement from them, but a lot of implementation 
complication. (I recall I was one of the stronger opponents of this feature, 
mostly for implementation cost/benefit reasons.)

So it is completely wrong to say that "this was missed in the language 
design". The correct statement is that "this was explicitly rejected in the 
language design".

                                 Randy.





^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01 22:10 ` Jerry
  2010-02-02  0:07   ` Randy Brukardt
@ 2010-02-02  8:52   ` Jean-Pierre Rosen
  2010-02-02 22:23     ` Jerry
                       ` (3 more replies)
  1 sibling, 4 replies; 48+ messages in thread
From: Jean-Pierre Rosen @ 2010-02-02  8:52 UTC (permalink / raw)


Jerry a �crit :
> I've never understood why Ada does not allow slicing in
> multidimensional arrays. What are the safety issues involved? And how
> is it safe to force the programmer into ad hoc methods?
> 
One-dimensional slices are simple and efficient. Multidimensional slices
are a can of worms.

I guess you are thinking about rectangular slices. But why stop there? A
slice comprising the main diagonal and the diagonal above and below can
be very useful for some calculations. Or a slice which is the triangular
part of the upper half...

AFAICT, Fortran-99 does provide this - and the syntax is so complicated
that nobody uses it. And implementation is also a nightmare.

When designing a programming language, you have to stop at some point.
The ratio (cost of implementation) / usefulness is a good measure for
this. I think the ratio was simply to high for this feature.

-- 
---------------------------------------------------------
           J-P. Rosen (rosen@adalog.fr)
Visit Adalog's web site at http://www.adalog.fr



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-02  8:52   ` Jean-Pierre Rosen
@ 2010-02-02 22:23     ` Jerry
  2010-02-03  1:24       ` Adam Beneschan
  2010-02-04  4:42     ` Hibou57 (Yannick Duchêne)
                       ` (2 subsequent siblings)
  3 siblings, 1 reply; 48+ messages in thread
From: Jerry @ 2010-02-02 22:23 UTC (permalink / raw)


On Feb 2, 1:52 am, Jean-Pierre Rosen <ro...@adalog.fr> wrote:
> Jerry a écrit :> I've never understood why Ada does not allow slicing in
> > multidimensional arrays. What are the safety issues involved? And how
> > is it safe to force the programmer into ad hoc methods?
>
> One-dimensional slices are simple and efficient. Multidimensional slices
> are a can of worms.
>
> I guess you are thinking about rectangular slices. But why stop there? A
> slice comprising the main diagonal and the diagonal above and below can
> be very useful for some calculations. Or a slice which is the triangular
> part of the upper half...
>
> AFAICT, Fortran-99 does provide this - and the syntax is so complicated
> that nobody uses it. And implementation is also a nightmare.
>
> When designing a programming language, you have to stop at some point.
> The ratio (cost of implementation) / usefulness is a good measure for
> this. I think the ratio was simply to high for this feature.
>
> --
> ---------------------------------------------------------
>            J-P. Rosen (ro...@adalog.fr)
> Visit Adalog's web site athttp://www.adalog.fr

Well, yes, I was thinking of rectangular slices. No doubt the (cost of
implementation) / usefulness is high (and usage difficult) for non-
rectangular parts, but that is far less common than rectangular parts.
Python, Matlab/Octave, Igor Pro... all pull it off without too much
hassle (although Python asks you to imagine addressing the array by
the "cracks" between elements, as I recall--probably a disease of C-
style counting).

Jerry



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-02 22:23     ` Jerry
@ 2010-02-03  1:24       ` Adam Beneschan
  0 siblings, 0 replies; 48+ messages in thread
From: Adam Beneschan @ 2010-02-03  1:24 UTC (permalink / raw)


On Feb 2, 2:23 pm, Jerry <lancebo...@qwest.net> wrote:
> On Feb 2, 1:52 am, Jean-Pierre Rosen <ro...@adalog.fr> wrote:
>
>
>
>
>
> > Jerry a écrit :> I've never understood why Ada does not allow slicing in
> > > multidimensional arrays. What are the safety issues involved? And how
> > > is it safe to force the programmer into ad hoc methods?
>
> > One-dimensional slices are simple and efficient. Multidimensional slices
> > are a can of worms.

> Well, yes, I was thinking of rectangular slices. No doubt the (cost of
> implementation) / usefulness is high (and usage difficult) for non-
> rectangular parts, but that is far less common than rectangular parts.
> Python, Matlab/Octave, Igor Pro... all pull it off without too much
> hassle (although Python asks you to imagine addressing the array by
> the "cracks" between elements, as I recall--probably a disease of C-
> style counting).

I don't know anything about any of those languages.  What I know about
Ada is that when multi-dimensional arrays are passed as parameters to
procedures, they're normally passed by reference (if they're large
enough).  Some arrays are required to be passed by reference; in other
cases, it's unspecified, but I'd expect any array to be passed by
reference unless it's a packed array of 32 Booleans or something.  So
say you have a procedure:

   type Matrix is array (Natural range <>, Natural range <>) of
Float;
   procedure Operation_On_Matrix (M : in out Matrix) is ...

You later declare a matrix:

   X : Matrix (1..10, 1..10);

and want to call the operation on a rectangular slice.  If the "slice"
consists of an entire row, or one or more consecutive rows:

   Operation_On_Matrix (X (3..4, 1..10));

this could be done as efficiently as if all of X were passed, since
the procedure would see it as an array of 20 consecutive floats (in a
typical implementation).  However, a slice consisting of one or more
columns:

   Operation_On_Matrix (X (1..10, 5..6));

or some smaller rectangle:

   Operation_On_Matrix (X (4..6, 4..6));

would be tricky, since the procedure now has to be told that there are
gaps between the "rows" of the array that it's seeing as a parameter.
This means making Operation_On_Matrix less efficient, since it has to
be given more information about each Matrix that comes in; and the
inefficiency has to be put there even if no caller ever used a 2-D
rectangular slice, ever.  Maybe the efficiency hit isn't all that
large---I don't know.

It wouldn't really work to fix the language to say that rectangular
slices are allowed only if they include the entire index range in all
dimensions but the first, since that would fail for array types
declared with the Fortran convention.

I realize that the original question was about using assignment to
copy slices.  I suppose that, theoretically, the language could be
changed to allow multi-dimensional slices in assignments but not as
subprogram parameters.  Yuck.  I wouldn't want to add that kind of
inconsistency to the language.

Anyway, I don't know how serious these issues are, but this seems to
me to be a possible reason why adding this feature isn't as simple as
it sounds.

                                  -- Adam



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01  2:11 Copying rows in a two dimensional array Peter C. Chapin
                   ` (3 preceding siblings ...)
  2010-02-01 22:10 ` Jerry
@ 2010-02-04  4:13 ` Hibou57 (Yannick Duchêne)
  2010-02-04  9:10   ` Dmitry A. Kazakov
  4 siblings, 1 reply; 48+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-04  4:13 UTC (permalink / raw)


On 1 fév, 03:11, "Peter C. Chapin" <pcc482...@gmail.com> wrote:
> Apparently the component type of an array needs to be fully constrained (which
> again makes sense) yet I don't know the size
That's what generics are made for.
But you will have a single matrix type of a fixed size.

I you don't want a fixed size type, the best I will think about, would
be to create an abstract matrix type which will be implemented on a
one dimensional array. You could use slice in the implementation.

Ex. for a 2x2 matrix, you will use a 1 .. 4 array of Float. You may
define a swap row method which will move items from 1 .. 2 to 3 .. 4
and vice-versa.

You will be able to use slice optimized operations.

Tell me if you need a more concrete example (I confess I'm a bit terse
here).



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-01  6:55 ` Niklas Holsti
  2010-02-01 23:36   ` Peter C. Chapin
@ 2010-02-04  4:27   ` Hibou57 (Yannick Duchêne)
  1 sibling, 0 replies; 48+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-04  4:27 UTC (permalink / raw)


On 1 fév, 07:55, Niklas Holsti <niklas.hol...@tidorum.invalid> wrote:
> Another solution -- which perhaps you have considered -- is to use a
> generic package to define row and matrix types:
>
>     generic Size : Positive;
>     package Matrices
>     is
>        type Row is array (1 .. Size) of Float;
>        type Matrix is array (1 .. Size) of Row;
>     end Matrices;
>
> However, this will probably force some other parts of your code to
> become generic, too, parametrized either by a Size, or by an instance of
> Matrices.
I was just thinking while I was reading you : if he use generics, then
the generic package should define two matrix types, one for source
matrix and one for result matrix of some matrix functions (which
returns matrix with reversed dimensions). One Matrix(X,Y) and one
Matrix(Y,X)



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-02  8:52   ` Jean-Pierre Rosen
  2010-02-02 22:23     ` Jerry
@ 2010-02-04  4:42     ` Hibou57 (Yannick Duchêne)
  2010-02-14  0:42     ` jonathan
  2010-02-16  6:51     ` David Thompson
  3 siblings, 0 replies; 48+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-04  4:42 UTC (permalink / raw)


On 2 fév, 09:52, Jean-Pierre Rosen <ro...@adalog.fr> wrote:
> When designing a programming language, you have to stop at some point.
You have to stop to primitives (like rendezvous for tasking), things
which are a pain to simulate if not supported by the language (like
post/pre condition which will come with the next revision),
consistency (like my suggestion to make object declared with Constant
overloadable) and constructs with overall properties (like the loop
construct and its immutable variant instead of the goto-made-loop).

For every thing else (starting with personal-need-of-the-day), there
are generics and generic instantiations

(and a language is not a library, it's a paradigm)



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-04  4:13 ` Hibou57 (Yannick Duchêne)
@ 2010-02-04  9:10   ` Dmitry A. Kazakov
  2010-02-04  9:23     ` Hibou57 (Yannick Duchêne)
  0 siblings, 1 reply; 48+ messages in thread
From: Dmitry A. Kazakov @ 2010-02-04  9:10 UTC (permalink / raw)


On Wed, 3 Feb 2010 20:13:20 -0800 (PST), Hibou57 (Yannick Duch�ne) wrote:

> On 1 f�v, 03:11, "Peter C. Chapin" <pcc482...@gmail.com> wrote:
>> Apparently the component type of an array needs to be fully constrained (which
>> again makes sense) yet I don't know the size
> That's what generics are made for.
> But you will have a single matrix type of a fixed size.

Generics per design are incapable to express that the thing is variable.
You cannot make a generic variable-dimension matrix, a generic string, or
for that matter even a generic number:

generic
   Value : WHAT?
package Integer is
   ...
end Integer;

That does not work.

> I you don't want a fixed size type, the best I will think about, would
> be to create an abstract matrix type which will be implemented on a
> one dimensional array. You could use slice in the implementation.

This does not work either, I mean at the user interface level, because
slice does not have a type. In Ada types system you cannot express "the
subtype S is a vector of the type M". Therefore making it abstract types
you will loose most of the comfort built-in arrays offer.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-04  9:10   ` Dmitry A. Kazakov
@ 2010-02-04  9:23     ` Hibou57 (Yannick Duchêne)
  0 siblings, 0 replies; 48+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-04  9:23 UTC (permalink / raw)


On 4 fév, 10:10, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:
> This does not work either, I mean at the user interface level, because
> slice does not have a type. In Ada types system you cannot express "the
> subtype S is a vector of the type M". Therefore making it abstract types
> you will loose most of the comfort built-in arrays offer.
I've was to post him some seed of a package (not tested, I sincerely
apologize for that) :

package Matrix is
   -- Provides a matrix type with an efficient implementation
   -- of a row swapping method. A similar method as the one
   -- provided here, may be used to get a matrix type with an
   -- efficient implementation of column swapping method.
   -- This package most likely need to be extended in order
   -- to be fully useful to something in real life.

   subtype Float_Type is Float;

   subtype One_Dimensional_Size_Type is Natural range 1 .. 2 ** 15;
   -- Either a number of rows or a number of columns.
   -- The maximum size is so that One_Dimensional_Size_Type ** 2 is
   -- most unlikely to commit an overflow and will mostly be a valid
   -- value on most of target machines.

   First_Index : constant := 1;
   -- This may be changed to zero if needed, whenever the
   -- C indexing convention is preferred. This may not be
   -- changed to a value greater than one, otherwise
   -- Index_Type may potentially go out of Natural range.

   subtype Index_Type is Natural
      range
        (First_Index) ..
        (First_Index + (One_Dimensional_Size_Type'Last - 1));

   type Instance_Type (<>) is private;
   -- The type must be initialized at declaration :
   -- use New_Instance in that purpose (see below).

   -- The methods First_Row, Last_Row, First_Column,
   -- Last_Column and Item, are at least required to
   -- define pre- and post- condition of the New_Instance
   -- and Swap_Rows method.

   function First_Row
     (Instance : Instance_Type)
      return Index_Type;
   --|Ensures: Result = First_Index

   function Last_Row
     (Instance : Instance_Type)
      return Index_Type;

   function First_Column
     (Instance : Instance_Type)
      return Index_Type;
   --|Ensures: Result = First_Index

   function Last_Column
     (Instance : Instance_Type)
      return Index_Type;

   function Item
     (Instance : Instance_Type;
      Row      : Index_Type;
      Column   : Index_Type)
      return Float_Type;
   --|Requires: Row in First_Row (Instance) .. Last_Row (Instance);
   --|Requires:
   --|   Column in First_Column (Instance) ..
   --|   Last_Column (Instance);

   function New_Instance
      (Number_Of_Rows    : One_Dimensional_Size_Type;
       Number_Of_Columns : One_Dimensional_Size_Type)
       return Instance_Type;
   --|Ensures:
   --|   Last_Row (Instance) =
   --|   First_Index + Number_Of_Rows - 1;
   --|Ensures:
   --|   Last_Column (Instance) =
   --|   First_Index + Number_Of_Column - 1;
   --|Ensures:
   --|   for each Row in First_Row (Instance) .. Last_Row (Instance)
   --|   => for each Column in First_Column (Instance) ..
   --|   Last_Column (Instance) => Item (Row, Column) = 0.0;
   -- Note : all items are zero initialized.

   procedure Swap_Rows
      (Instance : in out Instance_Type;
       Row_1    : in Index_Type;
       Row_2    : in Index_Type);
   --|Requires: Row_1 in First_Row (Instance) .. Last_Row (Instance);
   --|Requires: Row_2 in First_Row (Instance) .. Last_Row (Instance);
   --|Ensures:
   --|   for each Column in First_Column (Instance) ..
   --|   Last_Column (Instance) => (Item (Instance, Row_1, Column) =
   --|   old Item (Instance, Row_2, Column));
   --|Ensures:
   --|   for each Column in First_Column (Instance) ..
   --|   Last_Column (Instance) => (Item (Instance, Row_2, Column) =
   --|   old Item (Instance, Row_1, Column));
   -- Note: Row_1 and Row_2 may be equal.

   --
===================================================================
   -- *** DO NOT CROSS *** DO NOT CROSS *** DO NOT CROSS *** DO NOT
CROSS
   --
-------------------------------------------------------------------

private

   pragma Assert
     ((First_Index + (One_Dimensional_Size_Type'Last ** 2)) <=
      (Natural'Last));
   -- Ensure computation on indexes will never go out of range.

   pragma Inline (First_Row);
   pragma Inline (Last_Row);
   pragma Inline (First_Column);
   pragma Inline (Last_Column);

   type Storage_Type is array (Natural range <>) of Float_Type;
   -- Flatenned array rows first columns next.
   -- Ex. (Row-1,Col-1),(Row-2,Col-1),(Row-1,Col-2),(Row-2,Col-2)
   --
   -- This way of flatening the matrix is the one which gives
   -- better performance to swap rows, as all items of a row
   -- appears to be consecutive, allowing slice access.
   --
   -- If good performance at swaping columns is targeting instead,
   -- then use the reverse representation (that is, like the
   -- Fortran convention), and update implementation of methods
   -- accordingly.
   --
   -- Note: the index type musn't be Index_Type,
   -- which is an index in one dimension, not in the overall storage.

   type Instance_Type
      (Number_Of_Rows    : One_Dimensional_Size_Type;
       Number_Of_Columns : One_Dimensional_Size_Type;
       Last_Data_Index   : Natural)
   is record
      Data : Storage_Type (First_Index .. Last_Data_Index);
   end record;

end Matrix;

package body Matrix is

   function First_Row
     (Instance : Instance_Type)
      return Index_Type
   is
   begin
      return First_Index;
   end First_Row;

   function Last_Row
     (Instance : Instance_Type)
      return Index_Type
   is
   begin
      return First_Index + (Instance.Number_Of_Rows - 1);
   end Last_Row;

   function First_Column
     (Instance : Instance_Type)
      return Index_Type
   is
   begin
      return First_Index;
   end First_Column;

   function Last_Column
     (Instance : Instance_Type)
      return Index_Type
   is
   begin
      return First_Index + (Instance.Number_Of_Columns - 1);
   end Last_Column;

   function Start_Of_Row
      (Instance : Instance_Type;
       Row     : Index_Type)
       return Natural
   -- Index in Data for the first item of the row
   -- whose index is Row. Used for accessing a matrix items
   -- and for row slice accesses.
   is
      Rows_Size : constant Natural := Instance.Number_Of_Columns;
   begin
      return First_Index +  (Rows_Size * (Row - First_Index));
   end Start_Of_Row;

   pragma Inline (Start_Of_Row);

   function End_Of_Row
      (Instance : Instance_Type;
       Row     : Index_Type)
       return Natural
   -- Index in Data for the last item of the row
   -- whose index is Row. Used for row slice accesses.
   is
      Rows_Size : constant Natural := Instance.Number_Of_Columns;
   begin
      return Start_Of_Row (Instance, Row) +  (Rows_Size - 1);
      -- This is an upper bound, not a limit, so
      -- Rows_Size - 1 is used. We add an offset starting
      -- the fist index of the row.
   end End_Of_Row;

   pragma Inline (End_Of_Row);

   function Item
     (Instance : Instance_Type;
      Row      : Index_Type;
      Column   : Index_Type)
      return Float_Type
   is
   begin
      Validity_Constraints :
      begin
         if Row not in First_Index .. Last_Row (Instance) then
            raise Program_Error;
         end if;
         if Column not in First_Index .. Last_Column (Instance) then
            raise Program_Error;
         end if;
      end Validity_Constraints;

      Method:
      declare
         Row_Start : constant Natural := Start_Of_Row (Instance, Row);
         Column_Offset : constant Natural := Column - First_Index;
         Data_Index : constant Natural := Row_Start + Column_Offset;
      begin
         return Instance.Data (Data_Index);
      end Method;
   end Item; -- Procedure

   function New_Instance
      (Number_Of_Rows    : One_Dimensional_Size_Type;
       Number_Of_Columns : One_Dimensional_Size_Type)
       return Instance_Type
   is
      Data_Size : constant Natural :=
        (Number_Of_Rows * Number_Of_Columns);

      Last_Data_Index : constant Natural :=
        (First_Index + (Data_Size - 1));
   begin
      return
        (Number_Of_Rows    => Number_Of_Rows,
         Number_Of_Columns => Number_Of_Columns,
         Last_Data_Index   => Last_Data_Index,
         Data              => (others => 0.0));
   end New_Instance; -- Function

   procedure Swap_Rows
      (Instance : in out Instance_Type;
       Row_1    : in Index_Type;
       Row_2    : in Index_Type)
   is
   begin
      Validity_Constraints :
      begin
         if Row_1 not in First_Index .. Last_Row (Instance) then
            raise Program_Error;
         end if;
         if Row_2 not in First_Index .. Last_Row (Instance) then
            raise Program_Error;
         end if;
      end Validity_Constraints;

      Special_Cases :
      begin
         if Row_1 = Row_2 then
            return;
         end if;
      end Special_Cases;

      Method :
      declare
         -- See comments in the package's private part.

         Rows_Size : constant Natural :=
           (Instance.Number_Of_Columns);

         Slice_Start_Of_Row_1 : constant Natural :=
            Start_Of_Row (Instance, Row_1);

         Slice_End_Of_Row_1 : constant Natural :=
            End_Of_Row (Instance, Row_1);

         Slice_Start_Of_Row_2 : constant Natural :=
            Start_Of_Row (Instance, Row_1);

         Slice_End_Of_Row_2 : constant Natural :=
            End_Of_Row (Instance, Row_2);

         Row_1_Slice : constant Storage_Type
         -- Backup of Row-1
           (Slice_Start_Of_Row_1 .. Slice_End_Of_Row_1) :=
               Instance.Data
                 (Slice_Start_Of_Row_1 ..
                  Slice_End_Of_Row_1);
      begin
         -- Copy Row-2 at the place of Row-1 (Row-1 was
         -- backed up).
         Instance.Data
           (Slice_Start_Of_Row_1 ..
            Slice_End_Of_Row_1)
            :=
               Instance.Data
                 (Slice_Start_Of_Row_2 ..
                  Slice_End_Of_Row_2);

         -- Copy backup of Row-1 at the place of
         -- Row-2.
         Instance.Data
           (Slice_Start_Of_Row_2 ..
            Slice_End_Of_Row_2)
            :=
               Row_1_Slice;
      end Method;

   end Swap_Rows; -- Procedure

end Matrix; -- Package



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-02  0:11   ` Randy Brukardt
@ 2010-02-07 16:13     ` Robert A Duff
  2010-02-08  6:30       ` tmoran
  0 siblings, 1 reply; 48+ messages in thread
From: Robert A Duff @ 2010-02-07 16:13 UTC (permalink / raw)


"Randy Brukardt" <randy@rrsoftware.com> writes:

> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote in message 
> news:178rg3rch8qdu$.13cgkywb09x3p.dlg@40tude.net...
>> On Sun, 31 Jan 2010 21:11:12 -0500, Peter C. Chapin wrote:
>>
>>> So I thought, "Perhaps A needs to be an array of arrays."
>>>
>>> type Matrix is array(Positive range <>) of WHAT_EXACTLY?
>>>
>>> Apparently the component type of an array needs to be fully constrained 
>>> (which
>>> again makes sense)
>>
>> Not really. Arrays should have been allowed to have discriminants. That 
>> was
>> missed in the language design.
>
> Early Ada 9x had discriminants for arrays. The capability got dropped when 
> lots of "nice-to-have" features got dropped from Ada 95. Such "array" types 
> have to be implemented as discriminant dependent records anyway; there is no 
> real hope of performance improvement from them, but a lot of implementation 
> complication. (I recall I was one of the stronger opponents of this feature, 
> mostly for implementation cost/benefit reasons.)
>
> So it is completely wrong to say that "this was missed in the language 
> design". The correct statement is that "this was explicitly rejected in the 
> language design".

It was missed in the design of Ada 83.  By the time of Ada 9X,
it was too late.  Sad.

If Ada 83 had had discriminated arrays, it would have been a
(slightly) simpler language.  And they're not hard to implement,
if you know about them ahead of time.  They may be hard to add
to an existing Ada 83 compiler that was designed based on
the rules of Ada 83.

That's true in general -- it's a lot easier to build an Ada 95 compiler,
than it is to build an Ada 83 compiler and then modify it to support
Ada 95.

Discriminated arrays would be more efficient than Ada's arrays.
We would have:

    type String (Length : Natural) is
        array (Positive range 1..Length) of Character;

This typically shrinks all unknown-length strings by 32 bits,
which is significant.  (Think about all the memory currently being
wasted to store zillions of copies of the number 1.)
And it makes bounds checking cheaper because the lower
bound is known at compile time.

And it would reduce the number of bugs -- all strings would
start at 1 (as opposed to the current sitation, where 99.99%
of all strings start at 1, and remaining 0.01% are bugs
waiting to happen).

And it would simplify the language (no need for the "range <>" syntax,
no need for the 'First and 'Last attributes of arrays, no need for
separate rules about array bounds and discriminants (which are
almost, but not quite, the same), etc).  Adding it to Ada 95 would NOT
simplify, because we'd have to keep all those now-useless features
for compatibility.

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-07 16:13     ` Robert A Duff
@ 2010-02-08  6:30       ` tmoran
  2010-02-08 13:15         ` Robert A Duff
  0 siblings, 1 reply; 48+ messages in thread
From: tmoran @ 2010-02-08  6:30 UTC (permalink / raw)


> Discriminated arrays would be more efficient than Ada's arrays.
> We would have:
>
>     type String (Length : Natural) is
>         array (Positive range 1..Length) of Character;

  How would you handle slices, either in assignments or as parameters?



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08  6:30       ` tmoran
@ 2010-02-08 13:15         ` Robert A Duff
  2010-02-08 13:45           ` Dmitry A. Kazakov
  2010-02-08 18:53           ` tmoran
  0 siblings, 2 replies; 48+ messages in thread
From: Robert A Duff @ 2010-02-08 13:15 UTC (permalink / raw)


tmoran@acm.org writes:

>> Discriminated arrays would be more efficient than Ada's arrays.
>> We would have:
>>
>>     type String (Length : Natural) is
>>         array (Positive range 1..Length) of Character;
>
>   How would you handle slices, either in assignments or as parameters?

Sliding.  All strings should start at 1, including slices.

In Ada, if you do "P(X(5..10));" procedure P can see that the
lower bound is 5.  That's a break in the abstraction -- P shouldn't
know or care where the string came from.

If both bounds are constrained, then slices should be illegal.
That is, "is array(1..10) of ..." should mean that ALL objects
of that type have bounds exactly 1..10.

Actually, slices are one of the least useful features of Ada.
I wouldn't mind (much) if they didn't exist in the first place.

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 13:15         ` Robert A Duff
@ 2010-02-08 13:45           ` Dmitry A. Kazakov
  2010-02-08 21:20             ` Robert A Duff
  2010-02-08 18:53           ` tmoran
  1 sibling, 1 reply; 48+ messages in thread
From: Dmitry A. Kazakov @ 2010-02-08 13:45 UTC (permalink / raw)


On Mon, 08 Feb 2010 08:15:50 -0500, Robert A Duff wrote:

> Actually, slices are one of the least useful features of Ada.
> I wouldn't mind (much) if they didn't exist in the first place.

But only if the language provided means to have user-defined ones. Which is
far from trivial. You need a lot of related types to describe slices
themselves and indicator sets (ranges). Plus you have to provide means to
determine if subarrays overlap in order to implement assignment in a safe
way. And user-defined assignment itself need to be properly done (syntax,
referential semantics of function results etc.)

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 13:15         ` Robert A Duff
  2010-02-08 13:45           ` Dmitry A. Kazakov
@ 2010-02-08 18:53           ` tmoran
  2010-02-08 21:14             ` Robert A Duff
  1 sibling, 1 reply; 48+ messages in thread
From: tmoran @ 2010-02-08 18:53 UTC (permalink / raw)


> In Ada, if you do "P(X(5..10));" procedure P can see that the
> lower bound is 5.  That's a break in the abstraction -- P shouldn't
> know or care where the string came from.
    For many, but not all, P.

> Actually, slices are one of the least useful features of Ada.
> I wouldn't mind (much) if they didn't exist in the first place.
   Wow, I beg to strongly differ.



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 18:53           ` tmoran
@ 2010-02-08 21:14             ` Robert A Duff
  2010-02-08 21:29               ` Pascal Obry
  2010-02-09  6:34               ` tmoran
  0 siblings, 2 replies; 48+ messages in thread
From: Robert A Duff @ 2010-02-08 21:14 UTC (permalink / raw)


tmoran@acm.org writes:

>> In Ada, if you do "P(X(5..10));" procedure P can see that the
>> lower bound is 5.  That's a break in the abstraction -- P shouldn't
>> know or care where the string came from.
>     For many, but not all, P.

Can you give an example where P should know that its String
parameter came from a slice, and should know the lower bound
of that slice?  I can't think of any off the top of my head
-- it just seems like a fundamentally broken abstraction if
you care about the lower bound of a string.

Just to be clear: I'm talking about Strings here, and other
array types that have a natural lower bound (usually 1,
sometimes 0).  I'm not necessarily talking about all
array types -- the discriminated arrays feature I am
imagining would allow the programmer to choose whether
to fix the lower bound at a particular value.  Or the upper
bound, or both, or neither.

>> Actually, slices are one of the least useful features of Ada.
>> I wouldn't mind (much) if they didn't exist in the first place.
>    Wow, I beg to strongly differ.

OK, I guess I shouldn't have said "least useful".  I should have
said that it's easy enough to work around the lack of this
feature.  In my experience, almost all slices are of
type String.  And almost all are R-values.  So a function:

    function Slice (S: String; First: Positive; Last: Natural) return String;

would do the trick, at some small efficiency cost.  (Note that we
tolerate this interface in the case of unbounded strings.)

Think about it this way:  Name some features of Ada that you
would rather do without than slices.  I can think of a few,
but not many.  It would be much more painful to do without,
say, case statements than slices.

Or think about it this way:  Name some features that Ada does
not have that you'd be willing to trade slices for.  For example,
I'd love to be able to fix the lower bound of an array type, and I'd
happily do without slices for that.  ;-)

And if you want a really useful/powerful slice facility, look to
Fortran!

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 13:45           ` Dmitry A. Kazakov
@ 2010-02-08 21:20             ` Robert A Duff
  2010-02-08 23:26               ` (see below)
  2010-02-09  1:05               ` Adam Beneschan
  0 siblings, 2 replies; 48+ messages in thread
From: Robert A Duff @ 2010-02-08 21:20 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

> On Mon, 08 Feb 2010 08:15:50 -0500, Robert A Duff wrote:
>
>> Actually, slices are one of the least useful features of Ada.
>> I wouldn't mind (much) if they didn't exist in the first place.
>
> But only if the language provided means to have user-defined ones.

I'm all in favor of allowing users to define their own abstractions,
rather than trying to build-in lots of stuff into the language.

.... Which is
> far from trivial.

It's trivial if you only want slices as R-values.
And anyway, slices as L-values don't really work:

    X : String := "abc";

    X (2..2) := "xxx";

One might expect X = "axxxc", but of course it raises
an exception instead.  You can do that sort of thing in Ada
with unbounded strings -- but then you don't get slice
syntax!

>...You need a lot of related types to describe slices
> themselves and indicator sets (ranges). Plus you have to provide means to
> determine if subarrays overlap in order to implement assignment in a safe
> way. And user-defined assignment itself need to be properly done (syntax,
> referential semantics of function results etc.)

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 21:14             ` Robert A Duff
@ 2010-02-08 21:29               ` Pascal Obry
  2010-02-09  8:56                 ` Jean-Pierre Rosen
  2010-02-09 14:26                 ` Robert A Duff
  2010-02-09  6:34               ` tmoran
  1 sibling, 2 replies; 48+ messages in thread
From: Pascal Obry @ 2010-02-08 21:29 UTC (permalink / raw)


Bob,

> OK, I guess I shouldn't have said "least useful".  I should have
> said that it's easy enough to work around the lack of this
> feature.  In my experience, almost all slices are of
> type String.  And almost all are R-values.  So a function:
> 
>     function Slice (S: String; First: Positive; Last: Natural) return String;

I beg to disagree strongly to that too :)

I have lot of code like this one:

   S (A .. B) := R (C .. D);

or

   S (A .. B) := V;

I would say that slices are really what make life easier in Ada compared
to other languages in many ways.

Pascal.

-- 

--|------------------------------------------------------
--| Pascal Obry                           Team-Ada Member
--| 45, rue Gabriel Peri - 78114 Magny Les Hameaux FRANCE
--|------------------------------------------------------
--|    http://www.obry.net  -  http://v2p.fr.eu.org
--| "The best way to travel is by means of imagination"
--|
--| gpg --keyserver keys.gnupg.net --recv-key F949BD3B




^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 21:20             ` Robert A Duff
@ 2010-02-08 23:26               ` (see below)
  2010-02-09  0:36                 ` Randy Brukardt
  2010-02-09 14:33                 ` Robert A Duff
  2010-02-09  1:05               ` Adam Beneschan
  1 sibling, 2 replies; 48+ messages in thread
From: (see below) @ 2010-02-08 23:26 UTC (permalink / raw)


On 08/02/2010 21:20, in article wccd40fpgpu.fsf@shell01.TheWorld.com,
"Robert A Duff" <bobduff@shell01.TheWorld.com> wrote:

> It's trivial if you only want slices as R-values.
> And anyway, slices as L-values don't really work:

I can't agree. I have this code:

procedure FFT_to_HWT (FFTCs    : in  complex_array; ...
                      HWT_tree : out complex_array; ...) is
...
   iFFTCs : complex_array (1..f(FFTCs'length));
begin
...
   iFFTCs(1..nr_bins) := FFTCs(first_bin..last_bin);
   iFFTCs(nr_bins+1..iFFT_size) := (others => (0.0,0.0));
   inverse_FFT(iFFTCs(1..iFFT_size));
...
   HWT_tree(next_HWTC..next_HWTC+iFFT_size-1) := iFFTCs(1..iFFT_size);
...
end FFT_to_HWT;

I think that using slices as L-values as well as R-values helps to make this
a lot clearer than it otherwise would be, and probably faster as well.

-- 
Bill Findlay
<surname><forename> chez blueyonder.co.uk





^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 23:26               ` (see below)
@ 2010-02-09  0:36                 ` Randy Brukardt
  2010-02-09  1:03                   ` (see below)
  2010-02-09  7:11                   ` Pascal Obry
  2010-02-09 14:33                 ` Robert A Duff
  1 sibling, 2 replies; 48+ messages in thread
From: Randy Brukardt @ 2010-02-09  0:36 UTC (permalink / raw)



"(see below)" <yaldnif.w@blueyonder.co.uk> wrote in message 
news:C7964E2E.135979%yaldnif.w@blueyonder.co.uk...
> On 08/02/2010 21:20, in article wccd40fpgpu.fsf@shell01.TheWorld.com,
> "Robert A Duff" <bobduff@shell01.TheWorld.com> wrote:
>
>> It's trivial if you only want slices as R-values.
>> And anyway, slices as L-values don't really work:
>
> I can't agree. I have this code:
>
> procedure FFT_to_HWT (FFTCs    : in  complex_array; ...
>                      HWT_tree : out complex_array; ...) is
> ...
>   iFFTCs : complex_array (1..f(FFTCs'length));
> begin
> ...
>   iFFTCs(1..nr_bins) := FFTCs(first_bin..last_bin);
>   iFFTCs(nr_bins+1..iFFT_size) := (others => (0.0,0.0));
>   inverse_FFT(iFFTCs(1..iFFT_size));
> ...
>   HWT_tree(next_HWTC..next_HWTC+iFFT_size-1) := iFFTCs(1..iFFT_size);
> ...
> end FFT_to_HWT;
>
> I think that using slices as L-values as well as R-values helps to make 
> this
> a lot clearer than it otherwise would be, and probably faster as well.

It's cases like this that make both the pro and con for slices. Expressions 
like these are probably easier to read and probably faster than the 
equivalent non-slice code.

But on the flip side, it's very hard to get the bounds right (I think I get 
these sorts of slices wrong 25% of the time). So you end up spending a lot 
of time debugging (at least Ada detects this). Moreover, it's hard to figure 
out from the code whether or not the bounds are right -- I'll often end 
drawing a picture and plug in various values to see if it makes sense. Case 
in point is the first statement; it fails unless last_bin - first_bin + 1 = 
nr_bins. So it's not clear how that is saving anything.

                                              Randy.





^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09  0:36                 ` Randy Brukardt
@ 2010-02-09  1:03                   ` (see below)
  2010-02-09  7:11                   ` Pascal Obry
  1 sibling, 0 replies; 48+ messages in thread
From: (see below) @ 2010-02-09  1:03 UTC (permalink / raw)


On 09/02/2010 00:36, in article hkqamr$8mq$1@munin.nbi.dk, "Randy Brukardt"
<randy@rrsoftware.com> wrote:

> 
> "(see below)" <yaldnif.w@blueyonder.co.uk> wrote in message
> news:C7964E2E.135979%yaldnif.w@blueyonder.co.uk...
>> On 08/02/2010 21:20, in article wccd40fpgpu.fsf@shell01.TheWorld.com,
>> "Robert A Duff" <bobduff@shell01.TheWorld.com> wrote:
>> 
>>> It's trivial if you only want slices as R-values.
>>> And anyway, slices as L-values don't really work:
>> 
>> I can't agree. I have this code:
>> 
>> procedure FFT_to_HWT (FFTCs    : in  complex_array; ...
>>                      HWT_tree : out complex_array; ...) is
>> ...
>>   iFFTCs : complex_array (1..f(FFTCs'length));
>> begin
>> ...
>>   iFFTCs(1..nr_bins) := FFTCs(first_bin..last_bin);
>>   iFFTCs(nr_bins+1..iFFT_size) := (others => (0.0,0.0));
>>   inverse_FFT(iFFTCs(1..iFFT_size));
>> ...
>>   HWT_tree(next_HWTC..next_HWTC+iFFT_size-1) := iFFTCs(1..iFFT_size);
>> ...
>> end FFT_to_HWT;
>> 
>> I think that using slices as L-values as well as R-values helps to make
>> this
>> a lot clearer than it otherwise would be, and probably faster as well.
> 
> It's cases like this that make both the pro and con for slices. Expressions
> like these are probably easier to read and probably faster than the
> equivalent non-slice code.
> 
> But on the flip side, it's very hard to get the bounds right (I think I get
> these sorts of slices wrong 25% of the time). So you end up spending a lot
> of time debugging (at least Ada detects this). Moreover, it's hard to figure
> out from the code whether or not the bounds are right -- I'll often end
> drawing a picture and plug in various values to see if it makes sense. Case

But you rraly have to do that reasoning in any case.

> in point is the first statement; it fails unless last_bin - first_bin + 1 =
> nr_bins. So it's not clear how that is saving anything.

The elided statements include:

if ... then
   nr_bins  := ...;
   last_bin := nr_bins + first_bin - 1;
else
   last_bin := ...;
   nr_bins := last_bin - first_bin + 1;
end if;

I was hoping the compiler would be able to propagate the bounds down to the
slices, and then note that:

  iFFTCs(1..nr_bins)'Length == FFTCs(first_bin..last_bin)'Length

Perhaps that is asking too much.

Recoding thus:

   iFFTCs(1..last_bin-first_bin+1) := FFTCs(first_bin..last_bin);
   iFFTCs(last_bin-first_bin+2..iFFT_size) := (others => (0.0,0.0));

 might even be an improvement in clarity, and I'd be disappointed if the
compiler did not then notice the identity of lengths.

-- 
Bill Findlay
<surname><forename> chez blueyonder.co.uk





^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 21:20             ` Robert A Duff
  2010-02-08 23:26               ` (see below)
@ 2010-02-09  1:05               ` Adam Beneschan
  2010-02-09 14:45                 ` Robert A Duff
  1 sibling, 1 reply; 48+ messages in thread
From: Adam Beneschan @ 2010-02-09  1:05 UTC (permalink / raw)


On Feb 8, 1:20 pm, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
> And anyway, slices as L-values don't really work:
>
>     X : String := "abc";
>
>     X (2..2) := "xxx";
>
> One might expect X = "axxxc",

One *what*??  One Perl programmer???

Really, I don't expect that anyone who understands Ada is going to get
this wrong.  Programmers who haven't yet learned the language may not
understand it, but that's probably true of *any* feature of the
language, except perhaps for this:

procedure Main_Program is
begin
   null;
end Main_Program;

Like most of the other posters here, I find slices very useful.  Also,
I don't have a particular problem using them, on both sides of ":=".
I don't think I get them wrong any more than I get anything else
wrong.

                                    -- Adam






^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 21:14             ` Robert A Duff
  2010-02-08 21:29               ` Pascal Obry
@ 2010-02-09  6:34               ` tmoran
  2010-02-09 14:29                 ` Robert A Duff
  1 sibling, 1 reply; 48+ messages in thread
From: tmoran @ 2010-02-09  6:34 UTC (permalink / raw)


>>> In Ada, if you do "P(X(5..10));" procedure P can see that the
>>> lower bound is 5.  That's a break in the abstraction -- P shouldn't
>>> know or care where the string came from.
>>     For many, but not all, P.
>
>Can you give an example where P should know that its String
>parameter came from a slice, and should know the lower bound
>of that slice?  I can't think of any off the top of my head
>-- it just seems like a fundamentally broken abstraction if
>you care about the lower bound of a string.

  package Int_IO is new Ada.Text_IO.Integer_IO(Integer);
  ...
  Last := Line'first-1;
  for i in V'range loop
    Integer_IO.Get(Line(Last+1 .. Line'last), V(i), Last);
  end loop;



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09  0:36                 ` Randy Brukardt
  2010-02-09  1:03                   ` (see below)
@ 2010-02-09  7:11                   ` Pascal Obry
  2010-02-09  8:14                     ` AdaMagica
  1 sibling, 1 reply; 48+ messages in thread
From: Pascal Obry @ 2010-02-09  7:11 UTC (permalink / raw)



A pattern that I have used in some applications. I have an application
that output structured strings, so I use something like that:

   type Index is range 1 .. 100;
   type Output is new String (Index);

   subtype Label    is Index range 1 .. 10;
   subtype Code     is Index range 12 .. 18;
   subtype Category is Index range 35 .. 50;
   ...

You get the idea... Then the code is simply:

   Line : Output;

   Line (Code) := "...";
or
   Put_Line (Line (Category));
or
   if Line (Code) = "..." then

An equivalent code using routines (a la C, using strcpy, strcmp) will
never be as readable as the use of slices in Ada. I would even say that
such code become obfuscated beyond anything acceptable to my taste.

Pascal.


-- 

--|------------------------------------------------------
--| Pascal Obry                           Team-Ada Member
--| 45, rue Gabriel Peri - 78114 Magny Les Hameaux FRANCE
--|------------------------------------------------------
--|    http://www.obry.net  -  http://v2p.fr.eu.org
--| "The best way to travel is by means of imagination"
--|
--| gpg --keyserver keys.gnupg.net --recv-key F949BD3B




^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09  7:11                   ` Pascal Obry
@ 2010-02-09  8:14                     ` AdaMagica
  0 siblings, 0 replies; 48+ messages in thread
From: AdaMagica @ 2010-02-09  8:14 UTC (permalink / raw)


> A pattern that I have used in some applications. I have an application
> that output structured strings, so I use something like that:
>
>    type Index is range 1 .. 100;
>    type Output is new String (Index);
>
>    subtype Label    is Index range 1 .. 10;
>    subtype Code     is Index range 12 .. 18;
>    subtype Category is Index range 35 .. 50;
>    ...
>
> You get the idea... Then the code is simply:
>
>    Put_Line (Line (Category));

This is a pattern I have used myself. So there's a strong opposition
to "useless slices" among Ada's aficionados.



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 21:29               ` Pascal Obry
@ 2010-02-09  8:56                 ` Jean-Pierre Rosen
  2010-02-09  9:14                   ` AdaMagica
  2010-02-09 14:26                 ` Robert A Duff
  1 sibling, 1 reply; 48+ messages in thread
From: Jean-Pierre Rosen @ 2010-02-09  8:56 UTC (permalink / raw)


Pascal Obry a �crit :

> or
> 
>    S (A .. B) := V;
> 
> I would say that slices are really what make life easier in Ada compared
> to other languages in many ways.
> 
And don't forget:
   S (A .. B) := (others => 0);

Enough with loop and loops at the lowest level! Thanks to slices, you
can really manipulate arrays as high level objects, without always going
down inside!

Now, I am sure someone will tell: "but that doesn't go as far as
multidimensional arrays...". True. Look at the syntax for Fortran
slices, and you'll see that the cure would be worth than the disease.
-- 
---------------------------------------------------------
           J-P. Rosen (rosen@adalog.fr)
Visit Adalog's web site at http://www.adalog.fr



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09  8:56                 ` Jean-Pierre Rosen
@ 2010-02-09  9:14                   ` AdaMagica
  2010-02-09 11:19                     ` Jean-Pierre Rosen
  0 siblings, 1 reply; 48+ messages in thread
From: AdaMagica @ 2010-02-09  9:14 UTC (permalink / raw)


> Now, I am sure someone will tell: "but that doesn't go as far as
> multidimensional arrays...". True. Look at the syntax for Fortran
> slices, and you'll see that the cure would be
> worth than the disease.
 ~~~~~~
I think you mean the opposite: worse



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09  9:14                   ` AdaMagica
@ 2010-02-09 11:19                     ` Jean-Pierre Rosen
  0 siblings, 0 replies; 48+ messages in thread
From: Jean-Pierre Rosen @ 2010-02-09 11:19 UTC (permalink / raw)


AdaMagica a �crit :
>> Now, I am sure someone will tell: "but that doesn't go as far as
>> multidimensional arrays...". True. Look at the syntax for Fortran
>> slices, and you'll see that the cure would be
>> worth than the disease.
>  ~~~~~~
> I think you mean the opposite: worse
Sure. Certainly no Freudian slip here!

-- 
---------------------------------------------------------
           J-P. Rosen (rosen@adalog.fr)
Visit Adalog's web site at http://www.adalog.fr



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 21:29               ` Pascal Obry
  2010-02-09  8:56                 ` Jean-Pierre Rosen
@ 2010-02-09 14:26                 ` Robert A Duff
  1 sibling, 0 replies; 48+ messages in thread
From: Robert A Duff @ 2010-02-09 14:26 UTC (permalink / raw)


Pascal Obry <pascal@obry.net> writes:

> I beg to disagree strongly to that too :)
>
> I have lot of code like this one:
>
>    S (A .. B) := R (C .. D);
>
> or
>
>    S (A .. B) := V;

I just did some searching in the GNAT sources.  About a million lines
of code.  About 7000 slices.  About 1500 slices on the left of ":=".

Warning: this is a crude search -- I probably have both false
positives and false negatives.

I must admit, these are higher numbers than I expected.

Almost all of them look like strings, at a quick glance.

> I would say that slices are really what make life easier in Ada compared
> to other languages in many ways.

OK, but I'm not comparing them to other languages.  I'm comparing them to
other features of Ada (or other features that I'd like to see
in Ada).

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09  6:34               ` tmoran
@ 2010-02-09 14:29                 ` Robert A Duff
  2010-02-09 18:49                   ` tmoran
  0 siblings, 1 reply; 48+ messages in thread
From: Robert A Duff @ 2010-02-09 14:29 UTC (permalink / raw)


tmoran@acm.org writes:

>>Can you give an example where P should know that its String
>>parameter came from a slice, and should know the lower bound
>>of that slice?  I can't think of any off the top of my head
>>-- it just seems like a fundamentally broken abstraction if
>>you care about the lower bound of a string.
>
>   package Int_IO is new Ada.Text_IO.Integer_IO(Integer);
>   ...
>   Last := Line'first-1;
>   for i in V'range loop
>     Integer_IO.Get(Line(Last+1 .. Line'last), V(i), Last);
>   end loop;

Interesting example.  Thanks!

I'd still prefer all strings start at 1, and I'd do parsing of
a text stream of integers in a different way (keep track
of current position without using slices at all).

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-08 23:26               ` (see below)
  2010-02-09  0:36                 ` Randy Brukardt
@ 2010-02-09 14:33                 ` Robert A Duff
  1 sibling, 0 replies; 48+ messages in thread
From: Robert A Duff @ 2010-02-09 14:33 UTC (permalink / raw)


"(see below)" <yaldnif.w@blueyonder.co.uk> writes:

> On 08/02/2010 21:20, in article wccd40fpgpu.fsf@shell01.TheWorld.com,
> "Robert A Duff" <bobduff@shell01.TheWorld.com> wrote:
>
>> It's trivial if you only want slices as R-values.
>> And anyway, slices as L-values don't really work:
>
> I can't agree. I have this code:
>
> procedure FFT_to_HWT (FFTCs    : in  complex_array; ...
>                       HWT_tree : out complex_array; ...) is
> ...
>    iFFTCs : complex_array (1..f(FFTCs'length));
> begin
> ...
>    iFFTCs(1..nr_bins) := FFTCs(first_bin..last_bin);
>    iFFTCs(nr_bins+1..iFFT_size) := (others => (0.0,0.0));
>    inverse_FFT(iFFTCs(1..iFFT_size));
> ...
>    HWT_tree(next_HWTC..next_HWTC+iFFT_size-1) := iFFTCs(1..iFFT_size);
> ...
> end FFT_to_HWT;
>
> I think that using slices as L-values as well as R-values helps to make this
> a lot clearer than it otherwise would be, and probably faster as well.

"Clearer"?  Yes, I agree.  "A lot clearer"?  I don't know -- something
like:

    Copy_Slice(iFFTCs, ...);

doesn't seem so horrible.

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09  1:05               ` Adam Beneschan
@ 2010-02-09 14:45                 ` Robert A Duff
  2010-02-09 18:50                   ` tmoran
  2010-02-09 19:51                   ` Pascal Obry
  0 siblings, 2 replies; 48+ messages in thread
From: Robert A Duff @ 2010-02-09 14:45 UTC (permalink / raw)


Adam Beneschan <adam@irvine.com> writes:

> On Feb 8, 1:20�pm, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
>> And anyway, slices as L-values don't really work:
>>
>> � � X : String := "abc";
>>
>> � � X (2..2) := "xxx";
>>
>> One might expect X = "axxxc",
>
> One *what*??  One Perl programmer???
>
> Really, I don't expect that anyone who understands Ada is going to get
> this wrong.

Yes, of course.  My point is just that if you want to replace
a slice of a string with another string, you can't do it,
unless they happen to be the same size.  I agree most Ada
programmers understand that -- and if they don't, they'll
find out pretty quickly.

Or you can do a lot of horsing around with unbounded strings.
And there, you don't get any special slice syntax, just
subprograms.  I really hate the fact that you don't get
normal string syntax for unbounded strings, but if I had
to choose which such syntax I want the most, I'd choose
string literals and indexing long before I'd choose slices.

>...Programmers who haven't yet learned the language may not
> understand it, but that's probably true of *any* feature of the
> language, except perhaps for this:
>
> procedure Main_Program is
> begin
>    null;
> end Main_Program;
>
> Like most of the other posters here, I find slices very useful.

Yeah, everybody in this thread is singing the praises of slices.
But nobody's taken my challenge: write down several features
of Ada that you'd rather do without than slices.  In other
words, fill in the blank:

    I'd rather do without ________ than do without slices.

I can think of some:  Entry families.  Line/column counting in Text_IO.

But you won't find me putting "packages" or "case statements"
or "parameter passing" in that blank!

My point is: the benefit of slices (over plain old procedure calls)
has to be relative to other features.  Just saying "slices are
useful" doesn't contradict anything I said -- I agree they're
useful.

>...Also,
> I don't have a particular problem using them, on both sides of ":=".
> I don't think I get them wrong any more than I get anything else
> wrong.

Well, what started this was my claim that all strings, including slices,
ought to start at 1.  I've seen huge numbers of bugs where this was
incorrectly assumed.  And it's nasty, because the vast majority of strings
DO start at one, so you don't notice the bug right away.  You notice it
a year later when somebody passes a slice to a procedure that always
worked before.

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09 14:29                 ` Robert A Duff
@ 2010-02-09 18:49                   ` tmoran
  2010-02-09 22:58                     ` Robert A Duff
  0 siblings, 1 reply; 48+ messages in thread
From: tmoran @ 2010-02-09 18:49 UTC (permalink / raw)


>>     Integer_IO.Get(Line(Last+1 .. Line'last), V(i), Last);
>...
>I'd still prefer all strings start at 1, and I'd do parsing of
>a text stream of integers in a different way (keep track
>of current position without using slices at all).
  I wouldn't usually parse a text stream of integers like that
either, but it's a very short example, using a routine in the
standard library.

  In general, the index of a found item in an array search is more
helpful than the offset.  For instance,
  function Find_Biggest(X : in Array_Type) return Index_Type;
leads to a cleaner recursive (or multitasking) divide-and-conquer
routine than returning an offset into the array.  The offset is
a means to the end, while the index is the end itself, and you can't
return the index if you don't know the X'first.



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09 14:45                 ` Robert A Duff
@ 2010-02-09 18:50                   ` tmoran
  2010-02-09 19:51                   ` Pascal Obry
  1 sibling, 0 replies; 48+ messages in thread
From: tmoran @ 2010-02-09 18:50 UTC (permalink / raw)


>But nobody's taken my challenge: write down several features
>of Ada that you'd rather do without than slices.
  It's hard to think, off the top of my head, of things I rarely use.
(Perhaps there's a cause-effect here :)
Aha! Goto statements!



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09 14:45                 ` Robert A Duff
  2010-02-09 18:50                   ` tmoran
@ 2010-02-09 19:51                   ` Pascal Obry
  2010-02-09 23:03                     ` Robert A Duff
  1 sibling, 1 reply; 48+ messages in thread
From: Pascal Obry @ 2010-02-09 19:51 UTC (permalink / raw)


Bob,

> Yeah, everybody in this thread is singing the praises of slices.
> But nobody's taken my challenge: write down several features
> of Ada that you'd rather do without than slices.  In other
> words, fill in the blank:
> 
>     I'd rather do without ________ than do without slices.

I won't respond to that. Everybody has it's own completion most probably
because of the domain of application. I suppose that in some embedded
device strings are not used at all. Should we remove them? Many people
have never use tasking, should we remove tasks?

Or maybe my response is I do not want to remove any feature from Ada.
Even entries families (that you have cited) are useful, I had use of
them in one application.

Pascal.

-- 

--|------------------------------------------------------
--| Pascal Obry                           Team-Ada Member
--| 45, rue Gabriel Peri - 78114 Magny Les Hameaux FRANCE
--|------------------------------------------------------
--|    http://www.obry.net  -  http://v2p.fr.eu.org
--| "The best way to travel is by means of imagination"
--|
--| gpg --keyserver keys.gnupg.net --recv-key F949BD3B




^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09 18:49                   ` tmoran
@ 2010-02-09 22:58                     ` Robert A Duff
  0 siblings, 0 replies; 48+ messages in thread
From: Robert A Duff @ 2010-02-09 22:58 UTC (permalink / raw)


tmoran@acm.org writes:

>   In general, the index of a found item in an array search is more
> helpful than the offset.  For instance,
>   function Find_Biggest(X : in Array_Type) return Index_Type;
> leads to a cleaner recursive (or multitasking) divide-and-conquer
> routine than returning an offset into the array.  The offset is
> a means to the end, while the index is the end itself, and you can't
> return the index if you don't know the X'first.

Right, although it might be better to return a cursor.

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-09 19:51                   ` Pascal Obry
@ 2010-02-09 23:03                     ` Robert A Duff
  0 siblings, 0 replies; 48+ messages in thread
From: Robert A Duff @ 2010-02-09 23:03 UTC (permalink / raw)


Pascal Obry <pascal@obry.net> writes:

> Or maybe my response is I do not want to remove any feature from Ada.

Fair enough, but that's not quite the same as saying that all
Ada features are equally useful.  For ex., if you got rid of the
full coverage rules for case statements, I would kick and scream!

> Even entries families (that you have cited) are useful, I had use of
> them in one application.

Sure, I've used entry families.  But you can use requeue instead,
so I judge entry families less useful than slices.

- Bob



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-02  8:52   ` Jean-Pierre Rosen
  2010-02-02 22:23     ` Jerry
  2010-02-04  4:42     ` Hibou57 (Yannick Duchêne)
@ 2010-02-14  0:42     ` jonathan
  2010-02-14  1:54       ` Hibou57 (Yannick Duchêne)
  2010-02-16  6:51     ` David Thompson
  3 siblings, 1 reply; 48+ messages in thread
From: jonathan @ 2010-02-14  0:42 UTC (permalink / raw)


On Feb 2, 8:52 am, Jean-Pierre Rosen <ro...@adalog.fr> wrote:
> Jerry a écrit :> I've never understood why Ada does not allow slicing in
> > multidimensional arrays. What are the safety issues involved? And how
> > is it safe to force the programmer into ad hoc methods?
>
> One-dimensional slices are simple and efficient. Multidimensional slices
> are a can of worms.
>
> I guess you are thinking about rectangular slices. But why stop there? A
> slice comprising the main diagonal and the diagonal above and below can
> be very useful for some calculations. Or a slice which is the triangular
> part of the upper half...
>
> AFAICT, Fortran-99 does provide this - and the syntax is so complicated
> that nobody uses it. And implementation is also a nightmare.
>
> When designing a programming language, you have to stop at some point.
> The ratio (cost of implementation) / usefulness is a good measure for
> this. I think the ratio was simply to high for this feature.
>
> --
> ---------------------------------------------------------
>            J-P. Rosen (ro...@adalog.fr)
> Visit Adalog's web site athttp://www.adalog.fr


I've never felt the need for two dimensional (or higher
dimensional) slicing. It's partly a performance issue: if
you make the data storage matrix as small as possible (ie
make it exactly the same size as the matrix-transformation
you are doing) then you sometimes get a disastrous loss of
efficiency. If on the other hand you always make the data storage
matrix larger than necessary (so that your transformation will
always be performed on a sub-matrix of the data storage matrix),
then you always have the option of avoiding these efficiency
losses. Once you write the transformation routine so that it
operates on sub-matrices of the data storage matrix, then
you usually don't have to slice or copy a sub-matrix from
the data storage matrix in order to transform it.

Here are some Ada and Fortran examples of the
problem on various sized data storage arrays.
I used some bits and pieces of routines from
http://web.am.qub.ac.uk/users/j.parker/miscellany/

First example: we eigen-decompose an N x N = 2048 x 2048 matrix.
The data storage matrix is M x M = (1024+Padding) x (1024+Padding)
Here is the running time in seconds of an iterative jacobi
eigen-decomposition:

   2048x2048:  322 sec, gnat      (Padding=24)
   2048x2048: 1646 sec, gnat      (Padding=0)
   2048x2048: 1632 sec, gfortran  (Padding=0)
   2048x2048: 1492 sec, ifort     (Padding=0)

The observed 500% slowdown in the absence of padded arrays is
unacceptable, even if it is a rare event (occurring only on 2**p sized
data arrays). In fact it's not all that rare ... more comments on
that below.  (BTW, ifort is the INTEL fortran compiler, all
optimizations at Max. gfortran is the gcc variant.)

By the way, I never bothered to write a paddable Fortran routine,
but here are some more timings near a power-of-2 array bounds:

   1023x1023: 33.5 sec, gnat     (Padding=9)
   1023x1023: 42.4 sec, gfortran (Padding=0)
   1023x1023: 37.3 sec, ifort    (Padding=0)

   1022x1022: 33.5 sec, gnat     (Padding=10)
   1022x1022: 30.2 sec, gfortran (Padding=0)
   1022x1022: 28.3 sec, ifort    (Padding=0)

   1024x1024: 33.2 sec, gnat     (Padding=8)
   1024x1024: 96.0 sec, gnat     (Padding=0)
   1024x1024: 116  sec, gfortran (Padding=0)
   1024x1024: 43   sec, ifort    (Padding=0)

There is one puzzle here I don't have time solve.  Normally, a good
fortran will automatically pad the array for you ... I recall that
happening in the past. This time it seems to have slipped its fortran
mind. The ifort man pages:

   -O3 enables "Padding the size of certain power-of-two
   arrays to allow more  efficient cache use."

But I used -O3 and also -O3 -fast ... maybe did something wrong,
but important lesson: compiler optimization policies change
with time, and of course vary from compiler to compiler.
You can't rely on them or even, amazingly, man pages. It's much
better to write the program in a way that is insensitive to changing
optimization policies.

A web search of "cache thrashing" will reveal much depressing
detail on the subject. The efficiency problems discussed above
occur as our arrays become large and spill out of the L3 cache
(6 Meg in the present case).

Just to demonstrate that these problems show up on all sorts
of arrays, I did some runs in the 2000 to 3000 range, this time
using a householder decomposition scavenged from the Golub
singular value decomposition. Can still find plenty of 500%'s:

   2102x2102, 3.93 sec, gnat  (Padding = 0)
   2102x2102, 3.19 sec, gnat  (Padding = 8)

   2176x2176, 5.03 sec, gnat  (Padding = 0)
   2176x2176, 3.42 sec, gnat  (Padding = 8)

   2304x2304, 8.47 sec, gnat  (Padding = 0)
   2304x2304, 4.52 sec, gnat  (Padding = 8)

   2560x2560, 24.1 sec, gnat  (Padding = 0)
   2560x2560, 5.42 sec, gnat  (Padding = 8)

   3072x3072, 38.9 sec, gnat  (Padding = 0)
   3072x3072, 7.76 sec, gnat  (Padding = 8)

   3584x3584, 53.2 sec, gnat  (Padding = 0)
   3584x3584, 11.5 sec, gnat  (Padding = 8)

Finally, an example on 1-dim arrays, using fast fourier
transforms, FFT. The standard, and the most common FFT is
computed on a power-of-2 length data set: 0 .. 2**p-1. I
timed computation of these FFT's on arrays of length  2**p, and
I compared this with computation on arrays of
length  2**p + Padding, where Padding = 24.  The computation
on the padded arrays was faster. The ratio of running times is:

   p = 10  ratio = .93
   p = 11  ratio = .88
   p = 12  ratio = .76
   p = 13  ratio = .79
   p = 14  ratio = .76
   p = 15  ratio = .75
   p = 16  ratio = .77
   p = 17  ratio = .84
   p = 18  ratio = .75
   p = 19  ratio = .45
   p = 20  ratio = .63
   p = 21  ratio = .69
   p = 22  ratio = .69
   p = 22  ratio = .67
   p = 24  ratio = .62
   p = 25  ratio = .62

So the problem is more common here, and smaller. (These
efficiency losses I still consider unacceptable, especially
in a routine whose reason for existence is efficiency.)
The problem is still worse when you take FFTs of two
dimensional arrays.

There is another (and entirely independent) reason
I prefer routines that perform their transformations on
arbitrary sub-matrices (or on arbitrary diagonal blocks)
of the data storage matrix. After writing my 1st linear
algebra routine, I was very pleased with myself, but it
didn't really do what I wanted.  I realized I needed to
transform the diagonal sub-blocks of a large matrix,
and do it iteratively on arbitrarily sized diagonal
sub-blocks. It was a very simple matter to modify the code to
do this, and the result was so convenient that I've never
considered doing it otherwise.

Jonathan



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-14  0:42     ` jonathan
@ 2010-02-14  1:54       ` Hibou57 (Yannick Duchêne)
  2010-02-14 16:16         ` jonathan
  0 siblings, 1 reply; 48+ messages in thread
From: Hibou57 (Yannick Duchêne) @ 2010-02-14  1:54 UTC (permalink / raw)


Le Sun, 14 Feb 2010 01:42:13 +0100, jonathan <johnscpg@googlemail.com> a  
écrit:
> First example: we eigen-decompose an N x N = 2048 x 2048 matrix.
> The data storage matrix is M x M = (1024+Padding) x (1024+Padding)
> Here is the running time in seconds of an iterative jacobi
> eigen-decomposition:
>
>    2048x2048:  322 sec, gnat      (Padding=24)
>    2048x2048: 1646 sec, gnat      (Padding=0)
>    2048x2048: 1632 sec, gfortran  (Padding=0)
>    2048x2048: 1492 sec, ifort     (Padding=0)
>
> The observed 500% slowdown in the absence of padded arrays is
> unacceptable, even if it is a rare event (occurring only on 2**p sized
> data arrays). In fact it's not all that rare ... more comments on
> that below.  (BTW, ifort is the INTEL fortran compiler, all
> optimizations at Max. gfortran is the gcc variant.)
So this is mostly about representation clauses finally. Is that it ?

Do not know if you already know this document (as I remember I picked it  
up from some one thread at comp.lang.ada), I've talked about on the other  
fr.c.l.a :
http://research.scee.net/files/presentations/gcapaustralia09/Pitfalls_of_Object_Oriented_Programming_GCAP_09.pdf
I had pointed about frames  #17, #18, #19 et #20, which contains good  
source of inspiration. Hope this could help you to figure a path.

You've posted a long list of tests-bench and observations. I did not  
looked at every thing, but hope I will have a more closer look at it later.

-- 
No-no, this isn't an oops ...or I hope (TM) - Don't blame me... I'm just  
not lucky



^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-14  1:54       ` Hibou57 (Yannick Duchêne)
@ 2010-02-14 16:16         ` jonathan
  2010-03-22  8:56           ` Ole-Hjalmar Kristensen
  0 siblings, 1 reply; 48+ messages in thread
From: jonathan @ 2010-02-14 16:16 UTC (permalink / raw)


On Feb 14, 1:54 am, Hibou57 (Yannick Duchêne)
<yannick_duch...@yahoo.fr> wrote:
> Le Sun, 14 Feb 2010 01:42:13 +0100, jonathan <johns...@googlemail.com> a  
> écrit:

  First example: we eigen-decompose an N x N = 2048 x 2048 matrix.
  The data storage matrix is M x M = (1024+Padding) x (1024+Padding)

should be of course:

  First example: we eigen-decompose an N x N = 2048 x 2048 matrix.
  The data storage matrix is M x M = (2048+Padding) x (2048+Padding)

> Do not know if you already know this document (as I remember I picked it  
> up from some one thread at comp.lang.ada), I've talked about on the other  
> fr.c.l.a :http://research.scee.net/files/presentations/gcapaustralia09/Pitfalls...
> I had pointed about frames  #17, #18, #19 et #20, which contains good  
> source of inspiration. Hope this could help you to figure a path.

Yes, I remembered this, probably from an old post of yours.  I wanted
to cite it when
when I posted earlier, but I could not find the site.  This is not
something you
forget quickly (frames 17 and 18):

   1980: RAM latency ~ 1 cycle
   2009: RAM latency ~ 400+ cycles

It's the heart of the matter, and it is just getting worse.  Helps
convince me
anyway that I did not waste time on an unimportant matter! In
numerical linear
algebra the usual solution is to restructure matrices as a collection
of
blocks.  That has a few of its own problems though. Minor footnote: I
did
some tests on Intel's new nehalem CPU's.  Vastly improved performance
on these
multi-megabyte arrays.  Problem not cured though. Don't know enough to
say more about it.
Thanks for the reminder.

Jonathan




^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-02  8:52   ` Jean-Pierre Rosen
                       ` (2 preceding siblings ...)
  2010-02-14  0:42     ` jonathan
@ 2010-02-16  6:51     ` David Thompson
  3 siblings, 0 replies; 48+ messages in thread
From: David Thompson @ 2010-02-16  6:51 UTC (permalink / raw)


On Tue, 02 Feb 2010 09:52:31 +0100, Jean-Pierre Rosen
<rosen@adalog.fr> wrote:

> Jerry a �crit :
> > I've never understood why Ada does not allow slicing in
> > multidimensional arrays. What are the safety issues involved? And how
> > is it safe to force the programmer into ad hoc methods?
> > 
> One-dimensional slices are simple and efficient. Multidimensional slices
> are a can of worms.
> 
> I guess you are thinking about rectangular slices. But why stop there? A
> slice comprising the main diagonal and the diagonal above and below can
> be very useful for some calculations. Or a slice which is the triangular
> part of the upper half...
> 
> AFAICT, Fortran-99 does provide this - and the syntax is so complicated
> that nobody uses it. And implementation is also a nightmare.
> 
Fortran 90 (and later) has rectangular but optionally non-unit-stride
slices; X(1:5:4,2:6:2) is X(1,2) X(1,4) X(1,6) X(5,2) X(5,4) X(5,6).
(Fortran arrays are column-major). (And although it treats string --
fixed length only -- as a different type than array of character, you
can use corresponding substrings of elements of an array of strings in
a way that is effectively also rectangular.)

It also has 'vector subscripting;: X(Y) accesses X(Y(1)) X(Y(2)) ...
X(Y(N)) -- but this cannot be used as modifiable actual argument or
POINTER target, making it not really a firstclass object/variable.

A major new 'coarray' feature, which essentially allows distribution
across parallel processing systems, vaguely like an in-language OpenMP
(although I hear the standardese must be rather contorted to avoid
impermissibly specifying implementation) was proposed for what was
scheduled to be F 08, but proved contentious enough that AFAIK it
still hasn't been finalized.

*PL/I* has the X DEFINED Y (iSUB) syntax which allows things like a
diagonal (but AFAICS not more than one at a time).

> When designing a programming language, you have to stop at some point.
> The ratio (cost of implementation) / usefulness is a good measure for
> this. I think the ratio was simply to high for this feature.

The features in F90 at least in this area weren't too much of a
problem, at least judging from the reports of visibly intelligent and
apparently informed people in c.l.f. Although those implementors had
the advantage that F90 was originally scheduled for I believe 87, and
even before that there had been experience with nonstandard but fairly
widespread HPF "High Performance Fortran" extensions.

In contrast F03, with adds features mostly in the areas of OO and
'parameterized' types somewhat like Ada discriminated ones, has taken
longer although most vendors are now reportedly getting close.




^ permalink raw reply	[flat|nested] 48+ messages in thread

* Re: Copying rows in a two dimensional array.
  2010-02-14 16:16         ` jonathan
@ 2010-03-22  8:56           ` Ole-Hjalmar Kristensen
  0 siblings, 0 replies; 48+ messages in thread
From: Ole-Hjalmar Kristensen @ 2010-03-22  8:56 UTC (permalink / raw)


jonathan <johnscpg@googlemail.com> writes:

<snip>
> It's the heart of the matter, and it is just getting worse.  Helps
> convince me
> anyway that I did not waste time on an unimportant matter! In
> numerical linear
> algebra the usual solution is to restructure matrices as a collection
> of
> blocks.  That has a few of its own problems though. Minor footnote: I
> did

Another approach is to keep the matrix as a single big matrix, but
reformulate your loops as recursive procedure which divides the matrix
a number of times and then loops at the lowest level. The increased
efficiency from tha cache will typically more than outweigh the
overhead from the recursion.

The following is a java version of the idea applied to transposing a
lagre matrix. (I have Ada and C versions as well) The recursive
version is typically about ten times faster than the pure nested loop
version. It is also interesting to see the speed of tha java version
relative to a C or Ada version. Try it and see...


import java.util.*;

class transpose
{
    private static final int u1 = 6000;
    private static final int u2 = 6000;
    private static int[][] a = new int[u1][u2];
    private static int[][] b = new int[u1][u2];

    private static void init(int[][]x)
    {
        int i = 0;
        int j = 0;
        for (i = 0; i < x.length; i++) {
            for (j = 0; j < x[i].length; j++) {
                x[i][j] = i; 
            }
        }
    }

    private static void loop_transpose(int[][]a, int[][]b, int ll1, int ul1, int ll2, int ul2)
    {
        int i = 0;
        int j = 0;
        for (i = ll1; i <= ul1; i++) {
            for (j = ll2; j <= ul2; j++) {
                b[j][i] = a[i][j]; 
            }
        }
    }

    private static void recursive_transpose(int[][]a, int[][]b, int ll1, int ul1, int ll2, int ul2, int cutoff) 
    {
        int split = 0;
        if (ul1 - ll1 > cutoff || ul2 - ll2 > cutoff) {
            if (ul1 - ll1 > ul2 - ll2 ) {
                split = (ul1 - ll1)/2;
                recursive_transpose(a,b,ll1,ll1+split,ll2,ul2,cutoff);
                recursive_transpose(a,b,ll1+1+split,ul1,ll2,ul2,cutoff);
            }else{
                split = (ul2 - ll2)/2;
                recursive_transpose(a,b,ll1,ul1,ll2,ll2+split,cutoff);
                recursive_transpose(a,b,ll1,ul1,ll2+1+split,ul2,cutoff);
            }
        }else {
            loop_transpose(a,b,ll1,ul1,ll2,ul2);
        }
    }

    public static void main(String[] args)
    {
        init(a); init(b);

        long start = (new Date()).getTime();
        loop_transpose(a,b,0,u1-1,0,u2-1);

        long stop = (new Date()).getTime();
        System.out.println( "loop " + (stop-start)); 

        start = (new Date()).getTime();
        recursive_transpose(a,b,0,u1-1,0,u2-1,16);

        stop = (new Date()).getTime();
        System.out.println( "recursive " + (stop-start)); 
    }
}
 
-- 
   C++: The power, elegance and simplicity of a hand grenade.



^ permalink raw reply	[flat|nested] 48+ messages in thread

end of thread, other threads:[~2010-03-22  8:56 UTC | newest]

Thread overview: 48+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2010-02-01  2:11 Copying rows in a two dimensional array Peter C. Chapin
2010-02-01  4:42 ` Jeffrey R. Carter
2010-02-01  6:55 ` Niklas Holsti
2010-02-01 23:36   ` Peter C. Chapin
2010-02-04  4:27   ` Hibou57 (Yannick Duchêne)
2010-02-01  8:37 ` Dmitry A. Kazakov
2010-02-02  0:11   ` Randy Brukardt
2010-02-07 16:13     ` Robert A Duff
2010-02-08  6:30       ` tmoran
2010-02-08 13:15         ` Robert A Duff
2010-02-08 13:45           ` Dmitry A. Kazakov
2010-02-08 21:20             ` Robert A Duff
2010-02-08 23:26               ` (see below)
2010-02-09  0:36                 ` Randy Brukardt
2010-02-09  1:03                   ` (see below)
2010-02-09  7:11                   ` Pascal Obry
2010-02-09  8:14                     ` AdaMagica
2010-02-09 14:33                 ` Robert A Duff
2010-02-09  1:05               ` Adam Beneschan
2010-02-09 14:45                 ` Robert A Duff
2010-02-09 18:50                   ` tmoran
2010-02-09 19:51                   ` Pascal Obry
2010-02-09 23:03                     ` Robert A Duff
2010-02-08 18:53           ` tmoran
2010-02-08 21:14             ` Robert A Duff
2010-02-08 21:29               ` Pascal Obry
2010-02-09  8:56                 ` Jean-Pierre Rosen
2010-02-09  9:14                   ` AdaMagica
2010-02-09 11:19                     ` Jean-Pierre Rosen
2010-02-09 14:26                 ` Robert A Duff
2010-02-09  6:34               ` tmoran
2010-02-09 14:29                 ` Robert A Duff
2010-02-09 18:49                   ` tmoran
2010-02-09 22:58                     ` Robert A Duff
2010-02-01 22:10 ` Jerry
2010-02-02  0:07   ` Randy Brukardt
2010-02-02  8:52   ` Jean-Pierre Rosen
2010-02-02 22:23     ` Jerry
2010-02-03  1:24       ` Adam Beneschan
2010-02-04  4:42     ` Hibou57 (Yannick Duchêne)
2010-02-14  0:42     ` jonathan
2010-02-14  1:54       ` Hibou57 (Yannick Duchêne)
2010-02-14 16:16         ` jonathan
2010-03-22  8:56           ` Ole-Hjalmar Kristensen
2010-02-16  6:51     ` David Thompson
2010-02-04  4:13 ` Hibou57 (Yannick Duchêne)
2010-02-04  9:10   ` Dmitry A. Kazakov
2010-02-04  9:23     ` Hibou57 (Yannick Duchêne)

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox