comp.lang.ada
 help / color / mirror / Atom feed
* Re: loop indices
@ 1992-04-17 20:00 Mark A Biggar
  0 siblings, 0 replies; 5+ messages in thread
From: Mark A Biggar @ 1992-04-17 20:00 UTC (permalink / raw)


In article <70482@ut-emx.uucp> hasan@emx.utexas.edu (David A. Hasan) writes:
>Suppose I have a matrix manipulation routine which must
>loop over the elements of several different ARRAYs.
>My question stems from the observation that unless the
>ARRAYs have the same bounds on their indices, I won't
>be able to index into all of them using a single FOR-LOOP
>index. Consider this example: 
>   DECLARE
>      TYPE Vector IS ARRAY( Positive RANGE <> ) OF Integer;
>      p1 : CONSTANT Positive := 21;
>      p2 : CONSTANT Positive := 51;
>      size : Natural := 5;
>
>      v1 : Vector( p1 .. (p1+size-1) );
>      v2 : Vector( p2 .. (p2+size-1) );
>   BEGIN
>      FOR i IN 1..size LOOP
>         v2(i) := v1(i);      -------------------(!)
>      END LOOP;
>   END;
>Obviously, I'll have constraint error problems here.
>The problem is not solve, either, if I replace the FOR
>LOOP by 
>   FOR i IN v2'RANGE LOOP
>since the index *still* won't work in <v1>.

What's wrong with using:

	FOR i IN 1..size LOOP
	    v2(p1+i-1) := v2(p2+i-1);
	END LOOP;

or

	FOR i IN v2'RANGE LOOP
	    v2(i) := v1(i-p2+p1);
	END LOOP;


--
Mark Biggar
mab@wdl1.wdl.loral.com

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

* Re: loop indices
@ 1992-04-20 14:00 Robert Firth
  0 siblings, 0 replies; 5+ messages in thread
From: Robert Firth @ 1992-04-20 14:00 UTC (permalink / raw)


In article <70482@ut-emx.uucp> hasan@emx.utexas.edu (David A. Hasan) writes:

>      v1 : Vector( p1 .. (p1+size-1) );
>      v2 : Vector( p2 .. (p2+size-1) );
>   BEGIN
>      FOR i IN 1..size LOOP
>         v2(i) := v1(i);      -------------------(!)
>      END LOOP;
>   END;

Well, I tend to be guided by style rather than efficiency, but in this
case I think one can have both.  The loop I'd write is

	for I in 0 .. SIZE-1 loop
	  V2(I+V2'FIRST) := V1(I+V1'FIRST);
	end loop;

I might alos revise the declarations, but that's a minor point.

Now, any reasonably good compiler should be able to work out that the
address expressions in the loop contain invariant subexpressions, and
essentially hoist the addition of V'FIRST out of the loop.  Even better,
many compilers generate an array root address that already designates
the first true element (rather than the mythical element zero), so the
addition isn't needed at all.  Finally, if the compiler can do simple
algebra, it can also see that no range check is needed on the array
accesses.

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

* Re: loop indices
@ 1992-04-20 16:39 David A. Hasan
  0 siblings, 0 replies; 5+ messages in thread
From: David A. Hasan @ 1992-04-20 16:39 UTC (permalink / raw)


In a previous article, I asked for suggestions on how to
deal with loop indices and gave the following example.
>
>   DECLARE
>      TYPE Vector IS ARRAY( Positive RANGE <> ) OF Integer;
>      p1 : CONSTANT Positive := 21;
>      p2 : CONSTANT Positive := 51;
>      size : Natural := 5;
>
>      v1 : Vector( p1 .. (p1+size-1) );
>      v2 : Vector( p2 .. (p2+size-1) );
>   BEGIN
>      FOR i IN 1..size LOOP
>         v2(i) := v1(i);      -------------------(!)
>      END LOOP;
>   END;
>
This was an unfortunate example, for as numerous people 
suggested, slicing is the obvious solution.  Short of that,
there is some POSITIVE arithmetic which can be used to
"play" with the indices of one array while the loop index
is used to index into the other array.  Variations on this
approach were also suggested by several people.

Thank you all for your comments.

I guess in my zeal to simplify my problem, I posted an overly
simple example.  My real interest is in situations like the
following.  The important differences in this new example are
    1) the two array variables of interest are of different
       types,
    2) the type of the associated index are also different.

  DECLARE 
    TYPE Index_1 IS (a,b,c,d,e,f,g);
    TYPE Array_1 IS ARRAY(Index_Type1 RANGE <>) OF Integer;

    TYPE Index_2 IS (aa,bb,cc,dd,ee,ff,gg);
    TYPE Array_2 IS ARRAY(Index_Type2 RANGE <>) OF Integer;

    v1 : Array_1( a..e );
    v2 : Array_2( bb..ff );
    i1 : Index_1;
    i2 : Index_2;
  BEGIN
    i1 := v1'FIRST;
    i2 := v2'FIRST;
    FOR i IN 1..5 LOOP
      v1(i1) := v2(i2);
      IF i<5 THEN
        i1 := Index_1'SUCC( i1 );
        i2 := Index_2'SUCC( i2 );
      END IF;
    END LOOP;
  END;

In this case, slicing is not an option.  Neither is it
possible to perform arithmetic *directly* on the indices
of either <v1> or <v2> (or both).

Of course, using 'POS and 'VAL it is possible to come up
with a solution which does not require the IF...END IF;
in my example above.

I prefer the code above for the following reasons:
  1) the explicit use of 'SUCC makes it clear what's going
     on (there is no index arithmetic hiding my intent),
  2) the two array objects, <v1> and <v2>, are dealt with
     "symmetrically" (i.e., neither is given the distinguished
     position of defining the LOOP index type),
  3) the method applies equally to all ARRAY types with any
     sort of index type.

I have no inherent opposition to using 'POS and 'VAL.  I just
"prefer" the appearance of the code in this example.  So...

My first question is this:  does this code carry a performance
hit with it (relative to analogous code which works with
'POS and 'VAL)?

My second question is this:  is there some other approach to
solving this problem in a "readable" way?
-- 
 |   David A. Hasan
 |   hasan@emx.utexas.edu 

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

* Re: loop indices
@ 1992-04-20 21:11 David A. Hasan
  0 siblings, 0 replies; 5+ messages in thread
From: David A. Hasan @ 1992-04-20 21:11 UTC (permalink / raw)


In article <70628@ut-emx.uucp> hasan@ut-emx.uucp (David A. Hasan) writes:
>
>  DECLARE 
>    TYPE Index_1 IS (a,b,c,d,e,f,g);
>    TYPE Array_1 IS ARRAY(Index_Type1 RANGE <>) OF Integer;
>
>    TYPE Index_2 IS (aa,bb,cc,dd,ee,ff,gg);
>    TYPE Array_2 IS ARRAY(Index_Type2 RANGE <>) OF Integer;
>
>    v1 : Array_1( a..e );
>    v2 : Array_2( bb..ff );
>    i1 : Index_1;
>    i2 : Index_2;
>  BEGIN
>    i1 := v1'FIRST;
>    i2 := v2'FIRST;
>    FOR i IN 1..5 LOOP
>      v1(i1) := v2(i2);
>      IF i<5 THEN
>        i1 := Index_1'SUCC( i1 );
>        i2 := Index_2'SUCC( i2 );
>      END IF;
>    END LOOP;
>  END;
>
>My first question is this:  does this code carry a performance
>hit with it (relative to analogous code which works with
>'POS and 'VAL)?
>
At the expense of making a simple quesiont drag out
too long, I've got one data point here which might answer
my own question.  I see three general approaches to this
problem.  The are  

  i1 := first_element_in_v1;
  i2 := first_element_inv2;
  FOR i IN 1..number_of_elements LOOP
    v1(i1) := v2(i2);  
  EXIT WHEN i=number_of_elements;
    i1 := ...'SUCC( i1 );
    i2 := ...'SUCC( i2 );
  END LOOP;

or

  i1 := ...;
  i2 := ...;
  FOR ... LOOP 
    ...
    IF i<number_of_elements THEN
      --increment i1 & i2
    END IF;
  END LOOP;

or

  FOR i IN 1..number_of_elements LOOP
    v1( Index_1'VAL( Index_1'POS(v1'FIRST)+i-1 ) )
      :=
        v2( Index_2'VAL( Index_2'POS(v2'FIRST)+i-1 ) );
  END LOOP;

After looking at the VAX machine code (optimized for time),
I see that all three approaches involve four potential
branches inside the loop.  Based on this (admittedly crude)
analysis, I am tempted to conclude that I should not be
reluctant to use one of the first two (which I feel are 
easier to read), since the performance is roughly equivalent.

Any objections?

-- 
 |   David A. Hasan
 |   hasan@emx.utexas.edu 

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

* Re: loop indices
@ 1992-04-22 21:02 Robert I. Eachus
  0 siblings, 0 replies; 5+ messages in thread
From: Robert I. Eachus @ 1992-04-22 21:02 UTC (permalink / raw)


In article <1992Apr21.211509.1911@software.org> smithd@software.org (Doug Smith
) writes:

   Then during an investigation encountered an interesting problem.
   Guess where the following code encounters a constraint error:

   <example deleted...>

   No, this is not a solution--but look carefully at the variable
   v3:
       It is of subtype Vec which is a constrained array
	  with range 21..25
       v3'range is   51..55.

   Have I missed something?  (This compiles using Verdix and Dec
   Ada compilers).  Any comments from the Language Lawyers?

   RFTM 8.5(4) :-) ...The renamed entity must be an object of the base
type of the type mark.  The properties of the renamed object are not
affected by the renaming declaration.  In particular, its value and
whether or not it is a constant are unaffected; similarly, the
constraints that apply to an object are not affected by a renaming
(any constraint implied by the renaming declaration is ignored....

    Surprising, true.  But you really have to work at it to get bitten
by this rule.  (In the more frequent case where both type marks are
the same--and unconstrained--you don't want implicit sliding of the
bounds.  Having the bounds slide in some cases and not in others would
really be perverse.)


					Robert I. Eachus

with STANDARD_DISCLAIMER;
use  STANDARD_DISCLAIMER;
function MESSAGE (TEXT: in CLEVER_IDEAS) return BETTER_IDEAS is...
--

					Robert I. Eachus

with STANDARD_DISCLAIMER;
use  STANDARD_DISCLAIMER;
function MESSAGE (TEXT: in CLEVER_IDEAS) return BETTER_IDEAS is...

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

end of thread, other threads:[~1992-04-22 21:02 UTC | newest]

Thread overview: 5+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1992-04-22 21:02 loop indices Robert I. Eachus
  -- strict thread matches above, loose matches on Subject: below --
1992-04-20 21:11 David A. Hasan
1992-04-20 16:39 David A. Hasan
1992-04-20 14:00 Robert Firth
1992-04-17 20:00 Mark A Biggar

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