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

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