public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/32842]  New: Useroperator
@ 2007-07-20 21:20 burnus at gcc dot gnu dot org
  2007-07-22 19:34 ` [Bug fortran/32842] User operator / allocateable array: Wrong code pault at gcc dot gnu dot org
                   ` (5 more replies)
  0 siblings, 6 replies; 7+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-07-20 21:20 UTC (permalink / raw)
  To: gcc-bugs

>From the ISO_VARYING_STRING testsuite (vst_2.f90)

The following program prints an empty string instead of "Hello".

PROGRAM VST_2
  USE ISO_VARYING_STRING
  IMPLICIT NONE
  CHARACTER(LEN=5)     :: char_arb(2)
  type(VARYING_STRING) :: str_ara(2)
  char_arb(1)= "Hello"
  char_arb(2)= "World"
  str_ara = char_arb
  !print *, char_arb(1)
  print *, char(str_ara(1))
END PROGRAM VST_2

The program works accidentally for an array size of 1 (instead of 2). What is
the meaning of the inner for ("while(1)") loop? Simplified dump:

for(S.1 = 1; S.1 <= 2; S.1++)
{
  for(S.3 = 1; S.3 <= 2; S3++)
  {
    struct varying_string D.1375
    struct varying_string varying_string.2
    varying_string.data = NULL
    D.1375 = varying_string.2
    deallocate(str_ara[S.3].data)
    str_ara[S.3].data = NULL
    str_ara[S.3] = D.1375
  }
  deallocate(str_ara[S.1].data)
  str_ara[S.1].data = NULL;
  op_assign_vs_ch(&str_ara[S.1], &char_arab[S1], 5)
}

Using the following as module instead of the full-fledged module gives even a
crash at "print *, char(str_ara(1))". Example works without valgrind problems
with g95 and NAG f95.

module iso_varying_string
  implicit none
  integer, parameter :: GET_BUFFER_LEN = 256
  type varying_string
     character(LEN=1), dimension(:), allocatable :: chars
  end type varying_string
  interface assignment(=)
     module procedure op_assign_VS_CH
  end interface assignment(=)
contains
  elemental subroutine op_assign_VS_CH (var, exp)
    type(varying_string), intent(out) :: var
    character(LEN=*), intent(in)      :: exp
    var = var_str(exp)
  end subroutine op_assign_VS_CH
  elemental function var_str (char) result (string)
    character(LEN=*), intent(in) :: char
    type(varying_string)         :: string
    integer                      :: length
    integer                      :: i_char
    length = LEN(char)
    ALLOCATE(string%chars(length))
    forall(i_char = 1:length)
       string%chars(i_char) = char(i_char:i_char)
    end forall
  end function var_str
end module iso_varying_string


-- 
           Summary: Useroperator
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: burnus at gcc dot gnu dot org


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


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

* [Bug fortran/32842] User operator / allocateable array: Wrong code
  2007-07-20 21:20 [Bug fortran/32842] New: Useroperator burnus at gcc dot gnu dot org
@ 2007-07-22 19:34 ` pault at gcc dot gnu dot org
  2007-07-23  9:06 ` pault at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-22 19:34 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from pault at gcc dot gnu dot org  2007-07-22 19:34 -------
s/Wong/Wrong/

As the old joke says abot the Chinese fotball team, "two wings and a Wong..."

This appears to be fixed by my patch for pr32105; which, however, breaks cp2k. 
I am onto this but have spent the entirity of this afternoon on it, without
success *sigh*

Paul


-- 

pault 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-07-22 19:34:41
               date|                            |
            Summary|User operator / allocateable|User operator / allocateable
                   |array: Wong code            |array: Wrong code


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


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

* [Bug fortran/32842] User operator / allocateable array: Wrong code
  2007-07-20 21:20 [Bug fortran/32842] New: Useroperator burnus at gcc dot gnu dot org
  2007-07-22 19:34 ` [Bug fortran/32842] User operator / allocateable array: Wrong code pault at gcc dot gnu dot org
@ 2007-07-23  9:06 ` pault at gcc dot gnu dot org
  2007-07-24 11:20 ` burnus at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-23  9:06 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pault at gcc dot gnu dot org  2007-07-23 09:06 -------
This is indeed fixed by my patch for PR31205.  I had the breakthrough in
understanding why this broke cp2K at about 3 o'clock this morning *sigh* The
fix turned out to be very easy but understanding what was broken was not!

I will leave this lot to regtest and hope to submit the composite patch
tonight.

Cheers

Paul

PS I am similarly stuck on the character patch that I keep promising;  I can
make it work but have been unable to remove all the middle-end kludges.


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2007-07-22 19:34:41         |2007-07-23 09:06:31
               date|                            |


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


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

* [Bug fortran/32842] User operator / allocateable array: Wrong code
  2007-07-20 21:20 [Bug fortran/32842] New: Useroperator burnus at gcc dot gnu dot org
  2007-07-22 19:34 ` [Bug fortran/32842] User operator / allocateable array: Wrong code pault at gcc dot gnu dot org
  2007-07-23  9:06 ` pault at gcc dot gnu dot org
@ 2007-07-24 11:20 ` burnus at gcc dot gnu dot org
  2007-07-24 19:15 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-07-24 11:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from burnus at gcc dot gnu dot org  2007-07-24 11:20 -------
Patch: http://gcc.gnu.org/ml/gcc-patches/2007-07/msg01709.html
See also PR 31205.


-- 


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


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

* [Bug fortran/32842] User operator / allocateable array: Wrong code
  2007-07-20 21:20 [Bug fortran/32842] New: Useroperator burnus at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2007-07-24 11:20 ` burnus at gcc dot gnu dot org
@ 2007-07-24 19:15 ` pault at gcc dot gnu dot org
  2007-07-24 19:16 ` pault at gcc dot gnu dot org
  2007-07-24 19:19 ` pault at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-24 19:15 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from pault at gcc dot gnu dot org  2007-07-24 19:15 -------
Subject: Bug 32842

Author: pault
Date: Tue Jul 24 19:15:27 2007
New Revision: 126885

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=126885
Log:
2007-07-24 Paul Thomas <pault@gcc.gnu.org>

        PR fortran/31205
        PR fortran/32842
        * trans-expr.c (gfc_conv_function_call): Remove the default
        initialization of intent(out) derived types.
        * symbol.c (gfc_lval_expr_from_sym): New function.
        * matchexp.c (gfc_get_parentheses): Return argument, if it is
        character and posseses a ref.
        * gfortran.h : Add prototype for gfc_lval_expr_from_sym.
        * resolve.c (has_default_initializer): Move higher up in file.
        (resolve_code): On detecting an interface assignment, check
        if the rhs and the lhs are the same symbol.  If this is so,
        enclose the rhs in parenetheses to generate a temporary and
        prevent any possible aliasing.
        (apply_default_init): Remove code making the lval and call
        gfc_lval_expr_from_sym instead.
        (resolve_operator): Give a parentheses expression a type-
        spec if it has no type.
        * trans-decl.c (gfc_trans_deferred_vars): Apply the a default
        initializer, if any, to an intent(out) derived type, using
        gfc_lval_expr_from_sym and gfc_trans_assignment.  Check if
        the dummy is present.


2007-07-24 Paul Thomas <pault@gcc.gnu.org>

        PR fortran/31205
        * gfortran.dg/alloc_comp_basics_1.f90 : Restore number of
        "deallocates" to 24, since patch has code rid of much spurious
        code.
        * gfortran.dg/interface_assignment_1.f90 : New test.

        PR fortran/32842
        * gfortran.dg/interface_assignment_2.f90 : New test.

Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/matchexp.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/symbol.c
    trunk/gcc/fortran/trans-decl.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90


-- 


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


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

* [Bug fortran/32842] User operator / allocateable array: Wrong code
  2007-07-20 21:20 [Bug fortran/32842] New: Useroperator burnus at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2007-07-24 19:15 ` pault at gcc dot gnu dot org
@ 2007-07-24 19:16 ` pault at gcc dot gnu dot org
  2007-07-24 19:19 ` pault at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-24 19:16 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2007-07-24 19:16 -------
Subject: Bug 32842

Author: pault
Date: Tue Jul 24 19:16:36 2007
New Revision: 126886

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=126886
Log:
2007-07-24 Paul Thomas <pault@gcc.gnu.org>

        PR fortran/31205
        PR fortran/32842
        * trans-expr.c (gfc_conv_function_call): Remove the default
        initialization of intent(out) derived types.
        * symbol.c (gfc_lval_expr_from_sym): New function.
        * matchexp.c (gfc_get_parentheses): Return argument, if it is
        character and posseses a ref.
        * gfortran.h : Add prototype for gfc_lval_expr_from_sym.
        * resolve.c (has_default_initializer): Move higher up in file.
        (resolve_code): On detecting an interface assignment, check
        if the rhs and the lhs are the same symbol.  If this is so,
        enclose the rhs in parenetheses to generate a temporary and
        prevent any possible aliasing.
        (apply_default_init): Remove code making the lval and call
        gfc_lval_expr_from_sym instead.
        (resolve_operator): Give a parentheses expression a type-
        spec if it has no type.
        * trans-decl.c (gfc_trans_deferred_vars): Apply the a default
        initializer, if any, to an intent(out) derived type, using
        gfc_lval_expr_from_sym and gfc_trans_assignment.  Check if
        the dummy is present.


2007-07-24 Paul Thomas <pault@gcc.gnu.org>

        PR fortran/31205
        * gfortran.dg/alloc_comp_basics_1.f90 : Restore number of
        "deallocates" to 24, since patch has code rid of much spurious
        code.
        * gfortran.dg/interface_assignment_1.f90 : New test.

        PR fortran/32842
        * gfortran.dg/interface_assignment_2.f90 : New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/interface_assignment_1.f90
    trunk/gcc/testsuite/gfortran.dg/interface_assignment_2.f90


-- 


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


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

* [Bug fortran/32842] User operator / allocateable array: Wrong code
  2007-07-20 21:20 [Bug fortran/32842] New: Useroperator burnus at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2007-07-24 19:16 ` pault at gcc dot gnu dot org
@ 2007-07-24 19:19 ` pault at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-24 19:19 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2007-07-24 19:18 -------
Fixed on trunk

Thanks

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED


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


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

end of thread, other threads:[~2007-07-24 19:19 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-07-20 21:20 [Bug fortran/32842] New: Useroperator burnus at gcc dot gnu dot org
2007-07-22 19:34 ` [Bug fortran/32842] User operator / allocateable array: Wrong code pault at gcc dot gnu dot org
2007-07-23  9:06 ` pault at gcc dot gnu dot org
2007-07-24 11:20 ` burnus at gcc dot gnu dot org
2007-07-24 19:15 ` pault at gcc dot gnu dot org
2007-07-24 19:16 ` pault at gcc dot gnu dot org
2007-07-24 19:19 ` pault 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).