public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/31009]  New: derived type components: use memcpy when assigning arrays
@ 2007-03-01 14:39 dfranke at gcc dot gnu dot org
  2007-03-01 16:33 ` [Bug fortran/31009] Use memcpy when assigning whole arrays burnus at gcc dot gnu dot org
                   ` (5 more replies)
  0 siblings, 6 replies; 7+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2007-03-01 14:39 UTC (permalink / raw)
  To: gcc-bugs

In January, there were two patches from Roger Sayle [1,2] which were quite an
improvement for me. I'd like to suggest to do the same for derived type
components. Example:

TYPE :: summed_amplitude
  COMPLEX, DIMENSION(:,:), POINTER :: alm
END TYPE

SUBROUTINE summed_amplitude_init_copy(this, other)
  TYPE(summed_amplitude), INTENT(out) :: this
  TYPE(summed_amplitude), INTENT(in)  :: other
  ALLOCATE(this%alm(size(other%alm,1), size(other%alm,2)))
  this%alm = other%alm
END SUBROUTINE

Here, gfortran copies the arrays element-wise. In my code, this accounts for
about 20% of the runtime (as shown by gprof).

[1] http://gcc.gnu.org/ml/fortran/2007-01/msg00113.html (implement a(:) = b(:)
using memcpy when possible)
[2] http://gcc.gnu.org/ml/fortran/2007-01/msg00419.html (Use memcpy for array
constructor assignments)


-- 
           Summary: derived type components: use memcpy when assigning
                    arrays
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Keywords: missed-optimization
          Severity: enhancement
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dfranke at gcc dot gnu dot org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=31009


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

* [Bug fortran/31009] Use memcpy when assigning whole arrays
  2007-03-01 14:39 [Bug fortran/31009] New: derived type components: use memcpy when assigning arrays dfranke at gcc dot gnu dot org
@ 2007-03-01 16:33 ` burnus at gcc dot gnu dot org
  2007-03-01 16:58 ` dfranke at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-03-01 16:33 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2007-03-01 16:33 -------
> I'd like to suggest to do the same for derived type components.

The point is not components or not, the point is: Known size at compile time or
not. (A different thing are arrays of derived types.)
The same tree without memcopy is produced for e.g.

SUBROUTINE summed_amplitude_init_copy(this, other)
  COMPLEX, DIMENSION(:,:), INTENT(out) :: this
  COMPLEX, DIMENSION(:,:), INTENT(in)  :: other
  this = other
END SUBROUTINE

And if one replaces (:,:) by e.g. (5,5), __builtin_memcpy is used.

As the bounds are not constant, __builtin_memcpy cannot be used for (:,:) and
__memcpy has to be used.

The complication is that the memory might be not contiguous, example:

 real :: r(5,5)
 interface
  subroutine foo(a)
    real :: a(:,:)
  end subroutine foo
 end interface
 call foo(r(1:3,1:3))
 call foo(r(1:5:2,1:5:3))
end

(If no interface for "foo" is given, gfortran creates via
_gfortran_internal_pack a temporary array which is then contiguous.)

Thus you want to generate (schematically):
  if(contiguous)
     __memcopy
  else
     for(i = ...) {this[i] = that[i]}

For small arrays and for noncontiguous arrays, the contiguous check even slows
down the assignment, whereas I would expect a gain for big, contiguous arrays.

An implementation of the contiguous test can be found in
libgfortran/*/in_pack*, which is quite complicated and not necessarily fast for
small, noncontiguous arrays.
Maybe implementing it for one dimensional arrays is worthwhile as one has only
two simple extra if statments if the array is non contiguos.

  if (stride * (ubound-lbound) <= 0)
    return;
  if(stride == 1)
     memcpy(this[lbound],that[lbound], ubound-lbound);
  else
    for(i = lbound; i <= ubound; i++) that[i] = this[i]

For two-dimensional arrays, it is already more complicated, but it might still
be worthwhile.


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu dot
                   |                            |org
            Summary|derived type components: use|Use memcpy when assigning
                   |memcpy when assigning arrays|whole arrays


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=31009


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

* [Bug fortran/31009] Use memcpy when assigning whole arrays
  2007-03-01 14:39 [Bug fortran/31009] New: derived type components: use memcpy when assigning arrays dfranke at gcc dot gnu dot org
  2007-03-01 16:33 ` [Bug fortran/31009] Use memcpy when assigning whole arrays burnus at gcc dot gnu dot org
@ 2007-03-01 16:58 ` dfranke at gcc dot gnu dot org
  2007-03-01 19:42 ` tkoenig at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2007-03-01 16:58 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from dfranke at gcc dot gnu dot org  2007-03-01 16:58 -------
Tobias, I wouldn't expect gfortran to use memcpy if the array is not
continuous, as in your example. 

OTOH, my naive assumption is, that given "this = other", "this(:) = other(:)"
or even "this(a:b) = other(c:d)", it should, in general, be possible to handle
with memcopy, or memmove if this==other and a:b, c:d intersect, as long as the
array shapes are compatible. 

Since the finer details of fortran still elude me, is it possible at all that
in a statement as "this = other" were both shall be arrays of compatible shape,
either stride may not equal '1'?

> if(stride == 1)
> else
>   for(i = lbound; i <= ubound; i++) that[i] = this[i]
for(i = lbound; i <= ubound; i += stride) that[i] = this[i], probably?


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=31009


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

* [Bug fortran/31009] Use memcpy when assigning whole arrays
  2007-03-01 14:39 [Bug fortran/31009] New: derived type components: use memcpy when assigning arrays dfranke at gcc dot gnu dot org
  2007-03-01 16:33 ` [Bug fortran/31009] Use memcpy when assigning whole arrays burnus at gcc dot gnu dot org
  2007-03-01 16:58 ` dfranke at gcc dot gnu dot org
@ 2007-03-01 19:42 ` tkoenig at gcc dot gnu dot org
  2007-03-02  9:57 ` dfranke at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2007-03-01 19:42 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from tkoenig at gcc dot gnu dot org  2007-03-01 19:41 -------
(In reply to comment #2)

> Since the finer details of fortran still elude me, is it possible at all that
> in a statement as "this = other" were both shall be arrays of compatible shape,
> either stride may not equal '1'?

Yes.

The following is legal:

program main
  real, dimension(4) :: a
  a = (/ 1., 2., 3., 4. /)
  call foo(a(1:3:2), a(2:4:2))
  print *,a
contains
  subroutine foo(x,y)
    real, dimension(:), intent(in) :: x
    real, dimension(:), intent(out) :: y
    y = x
  end subroutine foo
end program main


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=31009


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

* [Bug fortran/31009] Use memcpy when assigning whole arrays
  2007-03-01 14:39 [Bug fortran/31009] New: derived type components: use memcpy when assigning arrays dfranke at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2007-03-01 19:42 ` tkoenig at gcc dot gnu dot org
@ 2007-03-02  9:57 ` dfranke at gcc dot gnu dot org
  2007-03-02 10:43 ` burnus at gcc dot gnu dot org
  2007-08-12 10:23 ` [Bug fortran/31009] Generate conditional code to assign arrays, depending on their stride fxcoudert at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2007-03-02  9:57 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from dfranke at gcc dot gnu dot org  2007-03-02 09:57 -------
Tobias, do the cases given in PR31016 include the one above? 
If yes, this PR could be closed as dupe?!


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=31009


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

* [Bug fortran/31009] Use memcpy when assigning whole arrays
  2007-03-01 14:39 [Bug fortran/31009] New: derived type components: use memcpy when assigning arrays dfranke at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2007-03-02  9:57 ` dfranke at gcc dot gnu dot org
@ 2007-03-02 10:43 ` burnus at gcc dot gnu dot org
  2007-08-12 10:23 ` [Bug fortran/31009] Generate conditional code to assign arrays, depending on their stride fxcoudert at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-03-02 10:43 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from burnus at gcc dot gnu dot org  2007-03-02 10:43 -------
> Tobias, do the cases given in PR31016 include the one above? 
> If yes, this PR could be closed as dupe?!

Actually not. PR 31016 (and related PR 31014) are about cases where one
actually knows that the memory is contiguous (with the size known either at
compile time or only at run time). There using memcpy or memset should always
be a win (except, maybe, for a one-element array).

This PR is about cases were the memory might not be contiguous; thus one needs
create code for both the contiguous and non-contiguous case and a check whether
either case is present. I believe this needs some thinking (and testing) to
make sure that the size of the generated code does not increase too much (at
least not for -Os) and that it is an overall gain without loosing to much speed
for real-world code with on non-contiguous arrays (strides).


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=31009


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

* [Bug fortran/31009] Generate conditional code to assign arrays, depending on their stride
  2007-03-01 14:39 [Bug fortran/31009] New: derived type components: use memcpy when assigning arrays dfranke at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2007-03-02 10:43 ` burnus at gcc dot gnu dot org
@ 2007-08-12 10:23 ` fxcoudert at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2007-08-12 10:23 UTC (permalink / raw)
  To: gcc-bugs



-- 

fxcoudert at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2007-08-12 10:23:00
               date|                            |
            Summary|Use memcpy when assigning   |Generate conditional code to
                   |whole arrays                |assign arrays, depending on
                   |                            |their stride


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=31009


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

end of thread, other threads:[~2007-08-12 10:23 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-03-01 14:39 [Bug fortran/31009] New: derived type components: use memcpy when assigning arrays dfranke at gcc dot gnu dot org
2007-03-01 16:33 ` [Bug fortran/31009] Use memcpy when assigning whole arrays burnus at gcc dot gnu dot org
2007-03-01 16:58 ` dfranke at gcc dot gnu dot org
2007-03-01 19:42 ` tkoenig at gcc dot gnu dot org
2007-03-02  9:57 ` dfranke at gcc dot gnu dot org
2007-03-02 10:43 ` burnus at gcc dot gnu dot org
2007-08-12 10:23 ` [Bug fortran/31009] Generate conditional code to assign arrays, depending on their stride fxcoudert at gcc dot gnu dot org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).