public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/18022] New: problem with structure and calling a function
@ 2004-10-15 19:01 gruel at astro dot ufl dot edu
  2004-10-21 19:27 ` [Bug fortran/18022] " tobi at gcc dot gnu dot org
                   ` (20 more replies)
  0 siblings, 21 replies; 22+ messages in thread
From: gruel at astro dot ufl dot edu @ 2004-10-15 19:01 UTC (permalink / raw)
  To: gcc-bugs

there are a bug when you mix structure and function. Only the first part of the
structure seems to act correctly. The best thing is to try this sample:

The tab and the pts must be equal in their components and it's not the case.

I saw another things I don't like (even if I think that the norm required
nothing), it's the initial value of a tab: the majorities of the value are 0 but
sometimes it's random, I'll prefer to have all the value random (you have no
choice to initialize all you're variable) or (better I think) to have all the
value equal at 0.

Thanks,

 
Nicolas

program test_bug

  implicit none

  character(len=20), dimension(4,2) :: tab_c
  real,dimension(4,2) :: tab
  integer :: i,j
  
  type :: point
     real :: x,y
  end type point
  type(point), dimension(4) :: pts
  
  tab_c(:,1)(:) = (/'1','2','3','4'/)
  tab_c(:,2)(:) = (/'2','3','4','5'/)

  print*, tab_c

  do i=1,2
     tab(:,i) = char2real_1d(tab_c(:,i))
  end do

  pts%x =  char2real_1d(tab_c(:,1))
  pts%y =  char2real_1d(tab_c(:,2))

  print*, "pts ",pts
  print*, "tab ", tab

contains
  function char2real_1d (tab_c,error) result (tab_r)
    character(len=*), dimension(:), intent(in) :: tab_c
    real, intent(in), optional :: error 

    real, dimension(size(tab_c)) :: tab_r

    integer :: i
    real:: err

    if (.not. (present(error))) then
       err = 9999.99
    else
       err = error
    end if
    do i=1,size(tab_c)       
       if (verify(trim(tab_c(i)),"0123456789-+.Ee " ) == 0) then
          read (unit=tab_c(i),fmt=*) tab_r(i)
       else
          tab_r (i) = err
       end if
    end do
  end function char2real_1d

end program test_bug

-- 
           Summary: problem with structure and calling a function
           Product: gcc
           Version: 4.0.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P2
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: gruel at astro dot ufl dot edu
                CC: gcc-bugs at gcc dot gnu dot org


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
@ 2004-10-21 19:27 ` tobi at gcc dot gnu dot org
  2005-07-05 14:52 ` gruel at astro dot ufl dot edu
                   ` (19 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: tobi at gcc dot gnu dot org @ 2004-10-21 19:27 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2004-10-21 19:27 -------
This looks like it's a dupe of 15553

*** This bug has been marked as a duplicate of 15553 ***

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |RESOLVED
         Resolution|                            |DUPLICATE


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
  2004-10-21 19:27 ` [Bug fortran/18022] " tobi at gcc dot gnu dot org
@ 2005-07-05 14:52 ` gruel at astro dot ufl dot edu
  2005-07-08  9:38 ` paulthomas2 at wanadoo dot fr
                   ` (18 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: gruel at astro dot ufl dot edu @ 2005-07-05 14:52 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From gruel at astro dot ufl dot edu  2005-07-05 14:51 -------
the problem is still there with the actual version of gfortran. The result is
totally incoherent. I don't know for the bug  15553 but this one is still present.

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|RESOLVED                    |UNCONFIRMED
         Resolution|DUPLICATE                   |
            Version|4.0.0                       |4.1.0


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
  2004-10-21 19:27 ` [Bug fortran/18022] " tobi at gcc dot gnu dot org
  2005-07-05 14:52 ` gruel at astro dot ufl dot edu
@ 2005-07-08  9:38 ` paulthomas2 at wanadoo dot fr
  2005-07-08 13:02 ` paulthomas2 at wanadoo dot fr
                   ` (17 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2005-07-08  9:38 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From paulthomas2 at wanadoo dot fr  2005-07-08 09:37 -------
(In reply to comment #1)
> This looks like it's a dupe of 15553
> *** This bug has been marked as a duplicate of 15553 ***

This is not correct - 15553 has been resolved.

The present bug comes about because the scalarizer does not recognise that the 
lvalues in   pts%x =  char2real_1d(tab_c(:,1))  are components in an array of 
derived types.  It instead treats them as an array of reals. This is odd because
  rbuffer = char2real_1d(tab_c(:,1))
  pts%x = rbuffer
works correctly.

There is something screwed up in gfc_trans_arrayfunc_assign that is causing 
this problem.  This can be confirmed by rewriting the two assignments as 
pts%x =  1.0*char2real_1d(tab_c(:,1))
pts%y =  1.0*char2real_1d(tab_c(:,2)), which now works correctly!!

Thus emboldened, I emliminated the branch to gfc_trans_arrayfunc_assign, 
whereupon the bug disappears.  What is this function for?  The rest of 
gfc_trans_assignment does its job correctly.

I will regtest over the weekend and check out whether it is "de-optimising" any 
code or not.


-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (2 preceding siblings ...)
  2005-07-08  9:38 ` paulthomas2 at wanadoo dot fr
@ 2005-07-08 13:02 ` paulthomas2 at wanadoo dot fr
  2005-07-08 13:34 ` gruel at astro dot ufl dot edu
                   ` (16 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2005-07-08 13:02 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From paulthomas2 at wanadoo dot fr  2005-07-08 13:01 -------
(In reply to comment #3)
I answered my own question about the purpose of gfc_trans_arrayfunc_assign.

I have written a patch that distinguishes the case of components of derived 
types and skips this call.  This will be submitted tonight with a short 
testcase.

-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (3 preceding siblings ...)
  2005-07-08 13:02 ` paulthomas2 at wanadoo dot fr
@ 2005-07-08 13:34 ` gruel at astro dot ufl dot edu
  2005-07-09  0:29 ` tobi at gcc dot gnu dot org
                   ` (15 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: gruel at astro dot ufl dot edu @ 2005-07-08 13:34 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From gruel at astro dot ufl dot edu  2005-07-08 13:34 -------
Subject: Re:  problem with structure and calling a function



paulthomas2 at wanadoo dot fr wrote:
> ------- Additional Comments From paulthomas2 at wanadoo dot fr  2005-07-08 09:37 -------
> (In reply to comment #1)
> 
>>This looks like it's a dupe of 15553
>>*** This bug has been marked as a duplicate of 15553 ***
> 
> 
> This is not correct - 15553 has been resolved.
> 
> The present bug comes about because the scalarizer does not recognise that the 
> lvalues in   pts%x =  char2real_1d(tab_c(:,1))  are components in an array of 
> derived types.  It instead treats them as an array of reals. This is odd because
>   rbuffer = char2real_1d(tab_c(:,1))
>   pts%x = rbuffer
> works correctly.
> 
> There is something screwed up in gfc_trans_arrayfunc_assign that is causing 
> this problem.  This can be confirmed by rewriting the two assignments as 
> pts%x =  1.0*char2real_1d(tab_c(:,1))
> pts%y =  1.0*char2real_1d(tab_c(:,2)), which now works correctly!!
> 
> Thus emboldened, I emliminated the branch to gfc_trans_arrayfunc_assign, 
> whereupon the bug disappears.  What is this function for?  The rest of 
> gfc_trans_assignment does its job correctly.

I wrote this function to read some data files. This data files can have 
some format not determin at the beggining so I read it in character 
after I check if there are only numerical element and I recuperate the 
coordinate (it's why I'm usin a pts definition). In my files I can have 
some "nan" or "inf" and this is a source at problem (I don't know how to 
manage it in fortran).
Perhaps there are a something more efficient and elegant to do this but 
I don't know it if it's the case.

> I will regtest over the weekend and check out whether it is "de-optimising" any 
> code or not.


Thanks,

	Nicolas


-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (4 preceding siblings ...)
  2005-07-08 13:34 ` gruel at astro dot ufl dot edu
@ 2005-07-09  0:29 ` tobi at gcc dot gnu dot org
  2005-07-09 11:39 ` tobi at gcc dot gnu dot org
                   ` (14 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-07-09  0:29 UTC (permalink / raw)
  To: gcc-bugs



-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |tobi at gcc dot gnu dot org


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (5 preceding siblings ...)
  2005-07-09  0:29 ` tobi at gcc dot gnu dot org
@ 2005-07-09 11:39 ` tobi at gcc dot gnu dot org
  2005-07-09 11:47 ` tobi at gcc dot gnu dot org
                   ` (13 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-07-09 11:39 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-07-09 11:34 -------
Adding Paul to the CC list.

Paul, I don't understand how the "optimisation 
brought about by the call to gfc_trans_arrayfunc_assign is simply not 
applicable in this case".  Can you elaborate?

What I fail to understand is how it should make a difference if the LHS is a
derived type component or not.

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |pault at gcc dot gnu dot org
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|                            |1
   Last reconfirmed|0000-00-00 00:00:00         |2005-07-09 11:34:23
               date|                            |


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (6 preceding siblings ...)
  2005-07-09 11:39 ` tobi at gcc dot gnu dot org
@ 2005-07-09 11:47 ` tobi at gcc dot gnu dot org
  2005-07-09 11:52 ` tobi at gcc dot gnu dot org
                   ` (12 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-07-09 11:47 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-07-09 11:39 -------
Ah, ok, I guess I understand the problem now.  Not going via a temporary would
still be possible if we were able to setup an array descriptor which points to
the right elements of the structure.

-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (7 preceding siblings ...)
  2005-07-09 11:47 ` tobi at gcc dot gnu dot org
@ 2005-07-09 11:52 ` tobi at gcc dot gnu dot org
  2005-07-09 12:04 ` tobi at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-07-09 11:52 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-07-09 11:47 -------
For the record, in the testcase Paul posted together with his patch
<http://gcc.gnu.org/ml/fortran/2005-07/msg00098.html>, we call foo as follows:
    struct array1_real4 parm.11;
    struct array1_mytype parm.10;

    parm.10.dtype = 553;
    parm.10.dim[0].lbound = 1;
    parm.10.dim[0].ubound = 4;
    parm.10.dim[0].stride = 1;
    parm.10.data = (void *) (struct mytype[0:] *) &z[0];
    parm.10.offset = 0;
    parm.11.dtype = 281;
    parm.11.dim[0].lbound = 1;
    parm.11.dim[0].ubound = 4;
    parm.11.dim[0].stride = 1;
    parm.11.data = (void *) (real4[0:] *) &b[0];
    parm.11.offset = 0;
    foo (&parm.10, &parm.11);

So instead of setting up an array which points to the x (or y) components of z,
we pass z as a whole, which of course doesn't make sense.  There seem to be two
possible solutions:
- use a temporary.  This is what Paul's patch does (even though there should be
a more intuitive way to check for this case, and there are probably other cases
where we incorrectly assume that stuff is contiguous)
- setup an array descriptor which points to the right parts of the array, in our
case this would be (if I get it right):
    parm.10.dtype = 281;
    parm.10.dim[0].lbound = 1;
    parm.10.dim[0].ubound = 4;
    parm.10.dim[0].stride = 2; /* Increased stride to walk past y component */
    parm.10.data = (void *) (struct real4[0:] *) &z[0].x;
    parm.10.offset = 0;
for the x component, and
    parm.10.dtype = 281;
    parm.10.dim[0].lbound = 1;
    parm.10.dim[0].ubound = 4;
    parm.10.dim[0].stride = 2; /* Increased stride to walk past y component */
    parm.10.data = (void *) (struct real4[0:] *) &z[0].y;
    parm.10.offset = 0;
for the y component.



-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (8 preceding siblings ...)
  2005-07-09 11:52 ` tobi at gcc dot gnu dot org
@ 2005-07-09 12:04 ` tobi at gcc dot gnu dot org
  2005-07-09 12:14 ` tobi at gcc dot gnu dot org
                   ` (10 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-07-09 12:04 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-07-09 11:52 -------
Oh, and there's a third option which is probably awkward and very pessimizing:
instead of assuming REAL*4 sized objects in the array, the callee could read the
size from the array desriptor, and skip fields accordingly.  Of course, one
would then still have to point to &z[0].y instead of &z[0] in the second call.

-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (9 preceding siblings ...)
  2005-07-09 12:04 ` tobi at gcc dot gnu dot org
@ 2005-07-09 12:14 ` tobi at gcc dot gnu dot org
  2005-07-09 13:14 ` paulthomas2 at wanadoo dot fr
                   ` (9 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-07-09 12:14 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-07-09 12:04 -------
The real bug is in gfc_conv_expr_descriptor, as proven by the following
testcase, which doesn't exercise the codepath you're modifying, but the parts
Paul's patch makes us evade:
[tobi@marktplatz tests]$ cat derivedptr.f90
type a
   integer :: i, j
end type a

type(a), target :: t(5)
integer, pointer :: p(:)

t(:)%i = (/1,2,3,4,5/)
print *, t(:)%i

p => t(:)%i
print *, p
end
[tobi@marktplatz tests]$ ~/src/gcc-new/build/gcc/f951 derivedptr.f90  -quiet
[tobi@marktplatz tests]$ gfortran derivedptr.s
[tobi@marktplatz tests]$ ./a.out
           1           2           3           4           5
           1    11507280           2   134520840           3
[tobi@marktplatz tests]$  

-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (10 preceding siblings ...)
  2005-07-09 12:14 ` tobi at gcc dot gnu dot org
@ 2005-07-09 13:14 ` paulthomas2 at wanadoo dot fr
  2005-07-09 14:39 ` paulthomas2 at wanadoo dot fr
                   ` (8 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2005-07-09 13:14 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From paulthomas2 at wanadoo dot fr  2005-07-09 13:00 -------
(In reply to comment #9)
> Oh, and there's a third option which is probably awkward and very pessimizing:
> instead of assuming REAL*4 sized objects in the array, the callee could read the
> size from the array desriptor, and skip fields accordingly.  Of course, one
> would then still have to point to &z[0].y instead of &z[0] in the second call.

Yes, the derived type could contain all sorts of bizarrenesses that would
prevent an adjusted stride from working.  I agree that the third option is
awkward and pessimising; in addition, I just do not have the competence to
implement it.

This is why I went for the first option.  I have modified the test to check to
see if ->ts.derived is the same for the expression and the symbol, rather than
the type.  This allows derived_type = derived_type_function (args) to work. I
was about to try the same for the rvalue.

-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (11 preceding siblings ...)
  2005-07-09 13:14 ` paulthomas2 at wanadoo dot fr
@ 2005-07-09 14:39 ` paulthomas2 at wanadoo dot fr
  2005-07-09 15:12 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
                   ` (7 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2005-07-09 14:39 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From paulthomas2 at wanadoo dot fr  2005-07-09 13:14 -------

> The real bug is in gfc_conv_expr_descriptor, as proven by the following
> testcase, which doesn't exercise the codepath you're modifying, but the parts
> Paul's patch makes us evade:

I think that your pointer example is another bug.  Whether it should be
considered to be in gfc_trans_pointer_assignment itself or in
gfc_conv_expr_descriptor should be thought through.  It seems to me that fixing
the latter would open the same can of worms that we have discussed for
gfc_trans_assignment.  This time, I am not sure that there is solution, except
for the third.  Using temporaries will not work, since the temporary would have
to be updated each time the target value changed. Modifying the stride will not
work for the same reasons as for a non-pointer assignment.  If size is used, can
we be sure that the rest of the compiler will pick it up?


-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (12 preceding siblings ...)
  2005-07-09 14:39 ` paulthomas2 at wanadoo dot fr
@ 2005-07-09 15:12 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
  2005-07-09 17:50 ` tobi at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: Tobias dot Schlueter at physik dot uni-muenchen dot de @ 2005-07-09 15:12 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From Tobias dot Schlueter at physik dot uni-muenchen dot de  2005-07-09 15:06 -------
Subject: Re:  problem with structure and calling a function

paulthomas2 at wanadoo dot fr wrote:
> I think that your pointer example is another bug.  Whether it should be
> considered to be in gfc_trans_pointer_assignment itself or in
> gfc_conv_expr_descriptor should be thought through.  It seems to me that fixing
> the latter would open the same can of worms that we have discussed for
> gfc_trans_assignment.  This time, I am not sure that there is solution, except
> for the third.  Using temporaries will not work, since the temporary would have
> to be updated each time the target value changed. Modifying the stride will not
> work for the same reasons as for a non-pointer assignment.  If size is used, can
> we be sure that the rest of the compiler will pick it up?

I was a little surprised that the code I gave is allowed at all, given that
this opens all kinds of cans of worms.  Say,
   type a
       real*8 :: x
       integer*1 :: i
   end type
   type(a), target :: v(50)
   real, pointer :: p(:)
   p => v(:)%x
Lovely, now we have to skip something which probably has a different size and
probably alignment.

I don't agree that gfc_trans_pointer_assignment can be made out to be the
culprit -- pointer assignment to an array-valued pointer means assignment of
an array descriptor, so we have to be able to generate correct array
descriptors even in these pathological cases.


-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (13 preceding siblings ...)
  2005-07-09 15:12 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
@ 2005-07-09 17:50 ` tobi at gcc dot gnu dot org
  2005-07-10 17:22 ` tobi at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-07-09 17:50 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-07-09 17:45 -------
(In reply to comment #13)

Sorry, the code I posted for illustration had a typo:
> Say,
>    type a
>        real*8 :: x
>        integer*1 :: i
>    end type
>    type(a), target :: v(50)
>    real, pointer :: p(:)
       ^^^ should be REAL*8
>    p => v(:)%x


-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (14 preceding siblings ...)
  2005-07-09 17:50 ` tobi at gcc dot gnu dot org
@ 2005-07-10 17:22 ` tobi at gcc dot gnu dot org
  2005-07-10 17:25 ` paulthomas2 at wanadoo dot fr
                   ` (4 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-07-10 17:22 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-07-10 16:58 -------
I had an IRC conversation with Paul Brook about this.  Here's what we concluded:

<pbrook> There are two solutions. (a) Align all components of derived types to
component size boundaries. (b) Express pointer strides in bytes, not elements.
<tobi_s> yes, i wanted to evade the second option
...
<pbrook> Right. The alignment of a derived type is the maximum alignment of all
of its components. However the alignment of one component does not effect the
alignment of other components within the same parent.
<pbrook> so type t; integer(2) :: a; integer(1) :: b, c; end type;    would
still be 4 bytes.
<tobi_s> so either we use byte-sized strides or we rule out packed structures
<pbrook> Yep, pretty much.
...
<pbrook> tobi_s: byte strides might not be so bad once we build
multi-dimensional arrays properly.
...
<pbrook> Anyhow, I think the solution is to make p => v(:)%c ICE/Sorry, and
postpone it until we get round to using ARRAY_REFS properly for multi-d arrays.

IOW, fixing the underlying bug is out-of-reach.  The original bug can be fixed
by forcing the function result via a temporary as Paul's patch does.  I'll have
to think about the correct check, though.

-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (15 preceding siblings ...)
  2005-07-10 17:22 ` tobi at gcc dot gnu dot org
@ 2005-07-10 17:25 ` paulthomas2 at wanadoo dot fr
  2005-07-10 17:37 ` paulthomas2 at wanadoo dot fr
                   ` (3 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2005-07-10 17:25 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From paulthomas2 at wanadoo dot fr  2005-07-10 17:22 -------
Subject: Re:  problem with structure and calling a function

tobi at gcc dot gnu dot org wrote:

>IOW, fixing the underlying bug is out-of-reach.  The original bug can be fixed
>by forcing the function result via a temporary as Paul's patch does.  I'll have
>to think about the correct check, though.
>
>  
>
My current version of the patch compares the lvalue expr->ts.derived 
with the sym->ts.derived.  This then allows derived type valued 
functions to go through gfc_trans_arrayfunc_assign but anything too 
difficult is sent to have a temporary made.

Please find it attached.

Paul T


Index: gcc/gcc/fortran/trans-expr.c
===================================================================
RCS file: /cvs/gcc/gcc/gcc/fortran/trans-expr.c,v
retrieving revision 1.53
diff -c -3 -p -r1.53 trans-expr.c
*** gcc/gcc/fortran/trans-expr.c	25 Jun 2005 00:40:36 -0000	1.53
--- gcc/gcc/fortran/trans-expr.c	10 Jul 2005 17:19:50 -0000
*************** gfc_trans_assignment (gfc_expr * expr1, 
*** 2213,2221 ****
    tree tmp;
    stmtblock_t block;
    stmtblock_t body;
! 
!   /* Special case a single function returning an array.  */
!   if (expr2->expr_type == EXPR_FUNCTION && expr2->rank > 0)
      {
        tmp = gfc_trans_arrayfunc_assign (expr1, expr2);
        if (tmp)
--- 2213,2226 ----
    tree tmp;
    stmtblock_t block;
    stmtblock_t body;
!  
!   /* Special case a single function returning an array. Note
!      that derived type components on lhs do not benefit from
!      this optimization and so are excluded by testing that 
!      the expression and symbol types are the same.  */
!   if (expr2->expr_type == EXPR_FUNCTION && expr2->rank > 0
!       && expr1->symtree->n.sym->ts.derived
! 	  == expr1->ts.derived)
      {
        tmp = gfc_trans_arrayfunc_assign (expr1, expr2);
        if (tmp)


-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (16 preceding siblings ...)
  2005-07-10 17:25 ` paulthomas2 at wanadoo dot fr
@ 2005-07-10 17:37 ` paulthomas2 at wanadoo dot fr
  2005-07-10 17:52 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
                   ` (2 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2005-07-10 17:37 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From paulthomas2 at wanadoo dot fr  2005-07-10 17:25 -------
Subject: Re:  problem with structure and calling a function

I notice that I did not change the comment - I though that it was a 
waste of time to clean it up!

Paul T




-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (17 preceding siblings ...)
  2005-07-10 17:37 ` paulthomas2 at wanadoo dot fr
@ 2005-07-10 17:52 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
  2005-07-10 18:09 ` paulthomas2 at wanadoo dot fr
  2005-08-03 10:01 ` paulthomas2 at wanadoo dot fr
  20 siblings, 0 replies; 22+ messages in thread
From: Tobias dot Schlueter at physik dot uni-muenchen dot de @ 2005-07-10 17:52 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From Tobias dot Schlueter at physik dot uni-muenchen dot de  2005-07-10 17:37 -------
Subject: Re:  problem with structure and calling a function

paulthomas2 at wanadoo dot fr wrote:
> --- 2213,2226 ----
>     tree tmp;
>     stmtblock_t block;
>     stmtblock_t body;
> !  
> !   /* Special case a single function returning an array. Note
> !      that derived type components on lhs do not benefit from
> !      this optimization and so are excluded by testing that 
> !      the expression and symbol types are the same.  */
> !   if (expr2->expr_type == EXPR_FUNCTION && expr2->rank > 0
> !       && expr1->symtree->n.sym->ts.derived
> ! 	  == expr1->ts.derived)
>       {
>         tmp = gfc_trans_arrayfunc_assign (expr1, expr2);
>         if (tmp)

I should probably have said why I don't like this: this will probably not work
with derived types which have a component of the same type as is common e.g.
in linked lists.

Hm, thinking about it a second longer makes it seem that this is really wrong:
expr1->ts.type should be BT_REAL in our case, so you're checing something
random, but maybe I've stared at code too long today, having turned in our
second-round ICFPC submission and reviewing patches.

- Tobi


-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (18 preceding siblings ...)
  2005-07-10 17:52 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
@ 2005-07-10 18:09 ` paulthomas2 at wanadoo dot fr
  2005-08-03 10:01 ` paulthomas2 at wanadoo dot fr
  20 siblings, 0 replies; 22+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2005-07-10 18:09 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From paulthomas2 at wanadoo dot fr  2005-07-10 17:52 -------
Subject: Re:  problem with structure and calling a function

>
>
>I should probably have said why I don't like this: this will probably not work
>with derived types which have a component of the same type as is common e.g.
>in linked lists.
>  
>
I was going to try the experiment but was so put off that I haven't 
bothered.  I will give it a whirl;  I think that it might work because 
the components will have to match correctly in the assignment.

>Hm, thinking about it a second longer makes it seem that this is really wrong:
>expr1->ts.type should be BT_REAL in our case, so you're checing something
>random, but maybe I've stared at code too long today, having turned in our
>second-round ICFPC submission and reviewing patches.
>
>  
>
I have spent the day, seeking light relief by fixing library problems: 
 All the NIST problems except one are now fixed.

There are three patches on the way.  The only remaining one is that of 
an internal unit being and array.  I intend to have a stab at it but 
will divert back to 18022 if you like.  I realise, also, that I have not 
committed the patch to pr16940 either.

Will have a busy night!

Paul




-- 


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


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

* [Bug fortran/18022] problem with structure and calling a function
  2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
                   ` (19 preceding siblings ...)
  2005-07-10 18:09 ` paulthomas2 at wanadoo dot fr
@ 2005-08-03 10:01 ` paulthomas2 at wanadoo dot fr
  20 siblings, 0 replies; 22+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2005-08-03 10:01 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From paulthomas2 at wanadoo dot fr  2005-08-03 10:01 -------
Tobi,

We should agree the condition by which the call to gfc_trans_arrayfunc_assign 
is bypassed and get this one out of the way. The original, posted to the list, 
had:

expr1->symtree->n.sym->ts.type == expr1->ts.type)

the version here has:

expr1->symtree->n.sym->ts.derived == expr1->ts.derived

The first allows all derived type components of derived types, which is 
sometimes not correct.

The second was an attempt to permit arrays of derived types to work and arrays 
of linked lists.  This latter is, perhaps, more reasonably viewed as a linked 
list contained in an array!  I have somewhere (Meissner's book?) see an example 
of such a thing.  It has the advantage that memory management is simplified and 
that the entire list can be treated as an entity.

Cheers

Paul T

Maybe I should hang a diagnostic on the second, to print out the expression and 
symbol types, so that I can reassure myself that it is working as intended?



-- 


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


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

end of thread, other threads:[~2005-08-03 10:01 UTC | newest]

Thread overview: 22+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2004-10-15 19:01 [Bug fortran/18022] New: problem with structure and calling a function gruel at astro dot ufl dot edu
2004-10-21 19:27 ` [Bug fortran/18022] " tobi at gcc dot gnu dot org
2005-07-05 14:52 ` gruel at astro dot ufl dot edu
2005-07-08  9:38 ` paulthomas2 at wanadoo dot fr
2005-07-08 13:02 ` paulthomas2 at wanadoo dot fr
2005-07-08 13:34 ` gruel at astro dot ufl dot edu
2005-07-09  0:29 ` tobi at gcc dot gnu dot org
2005-07-09 11:39 ` tobi at gcc dot gnu dot org
2005-07-09 11:47 ` tobi at gcc dot gnu dot org
2005-07-09 11:52 ` tobi at gcc dot gnu dot org
2005-07-09 12:04 ` tobi at gcc dot gnu dot org
2005-07-09 12:14 ` tobi at gcc dot gnu dot org
2005-07-09 13:14 ` paulthomas2 at wanadoo dot fr
2005-07-09 14:39 ` paulthomas2 at wanadoo dot fr
2005-07-09 15:12 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
2005-07-09 17:50 ` tobi at gcc dot gnu dot org
2005-07-10 17:22 ` tobi at gcc dot gnu dot org
2005-07-10 17:25 ` paulthomas2 at wanadoo dot fr
2005-07-10 17:37 ` paulthomas2 at wanadoo dot fr
2005-07-10 17:52 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
2005-07-10 18:09 ` paulthomas2 at wanadoo dot fr
2005-08-03 10:01 ` paulthomas2 at wanadoo dot fr

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).