public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/35723]  New: Can't use run-time array element in character declaration
@ 2008-03-27 20:34 dick dot hendrickson at gmail dot com
  2008-03-28 19:40 ` [Bug fortran/35723] " burnus at gcc dot gnu dot org
                   ` (4 more replies)
  0 siblings, 5 replies; 6+ messages in thread
From: dick dot hendrickson at gmail dot com @ 2008-03-27 20:34 UTC (permalink / raw)
  To: gcc-bugs

The following program gives an error message for valid use of
an array element in an expression for an automatic character
array.  

The error message is repeated twice.

Changing from a run-time subscript in the parameter array to a
constant fixes the problem.

Dick Hendrickson

      program try_vf0016
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]
! syntax error for valid syntax

      call       vf0016(  1,  2,  3)

      end
      SUBROUTINE VF0016(nf1,nf2,nf3)
      CHARACTER(LEN=9,KIND=1),DIMENSION(3), PARAMETER
     $     ::  TEST_STRINGS =
     $  (/'       HI','ABC      ','  CDEFG  '/)
      CHARACTER :: TEST_ARRAY
     $(LEN_TRIM(ADJUSTL(TEST_STRINGS(nf1))),  ! changing nf1 to 1 fixes it
     $ SUM(LEN_TRIM(ADJUSTL(TEST_STRINGS))),
     $ LEN_TRIM(ADJUSTL(ADJUSTR(TEST_STRINGS(3)))),
     $ SUM(LEN_TRIM(ADJUSTL(ADJUSTR(TEST_STRINGS(NF1:NF3:NF2)))))   )

       print *, 2, 10, 5, 7
       print *, shape (test_array)
         end



C:\g_experiments\gfortran>gfortran vf0016.f
vf0016.f:14.24:

     $(LEN_TRIM(ADJUSTL(TEST_STRINGS(nf1))),  ! changing nf1 to 1 fixes
                       1
Error: Variable 'test_strings' cannot appear in the expression at (1)
vf0016.f:14.24:

     $(LEN_TRIM(ADJUSTL(TEST_STRINGS(nf1))),  ! changing nf1 to 1 fixes
                       1
Error: Variable 'test_strings' cannot appear in the expression at (1)


-- 
           Summary: Can't use run-time array element in character
                    declaration
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dick dot hendrickson at gmail dot com


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


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

* [Bug fortran/35723] Can't use run-time array element in character declaration
  2008-03-27 20:34 [Bug fortran/35723] New: Can't use run-time array element in character declaration dick dot hendrickson at gmail dot com
@ 2008-03-28 19:40 ` burnus at gcc dot gnu dot org
  2008-09-24 10:01 ` domob at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-03-28 19:40 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2008-03-28 19:40 -------
Confirmed.

A simple patch would be the following:

Index: expr.c
===================================================================
--- expr.c      (Revision 133693)
+++ expr.c      (Arbeitskopie)
@@ -2502,6 +2502,7 @@ check_restricted (gfc_expr *e)
          || sym->attr.use_assoc
          || sym->attr.dummy
          || sym->attr.implied_index
+         || sym->attr.flavor == FL_PARAMETER
          || sym->ns != gfc_current_ns
          || (sym->ns->proc_name != NULL
              && sym->ns->proc_name->attr.flavor == FL_MODULE)

However, this also accepts the following invalid program (note the "i"):

      program try_vf0016
      call    vf0016(  1,  2,  3)
      end
      SUBROUTINE VF0016(nf1,nf2,nf3)
      CHARACTER(LEN=9,KIND=1),DIMENSION(3) , PARAMETER
     $     ::  TEST_STRINGS =
     $  (/'       HI','ABC      ','  CDEFG  '/)
      integer :: i = 2
      CHARACTER :: TEST_ARRAY
     $(LEN_TRIM(ADJUSTL(TEST_STRINGS(i))),  ! changing nf1 to 1 fixes it
     $ SUM(LEN_TRIM(ADJUSTL(TEST_STRINGS))),
     $ LEN_TRIM(ADJUSTL(ADJUSTR(TEST_STRINGS(3)))),
     $ SUM(LEN_TRIM(ADJUSTL(ADJUSTR(TEST_STRINGS(NF1:NF3:NF2)))))   )

       print *, 2, 10, 5, 7
       print *, shape (test_array)
         end

We therefore need to loop over expr->ref and check_restricted() these
expressions as well. I think that we can throw in another half a dozen checks
as well. ;-)


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu dot
                   |                            |org
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |rejects-valid
   Last reconfirmed|0000-00-00 00:00:00         |2008-03-28 19:40:15
               date|                            |


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


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

* [Bug fortran/35723] Can't use run-time array element in character declaration
  2008-03-27 20:34 [Bug fortran/35723] New: Can't use run-time array element in character declaration dick dot hendrickson at gmail dot com
  2008-03-28 19:40 ` [Bug fortran/35723] " burnus at gcc dot gnu dot org
@ 2008-09-24 10:01 ` domob at gcc dot gnu dot org
  2008-09-25 10:30 ` domob at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: domob at gcc dot gnu dot org @ 2008-09-24 10:01 UTC (permalink / raw)
  To: gcc-bugs



-- 

domob at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |domob at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2008-03-28 19:40:15         |2008-09-24 09:59:41
               date|                            |


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


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

* [Bug fortran/35723] Can't use run-time array element in character declaration
  2008-03-27 20:34 [Bug fortran/35723] New: Can't use run-time array element in character declaration dick dot hendrickson at gmail dot com
  2008-03-28 19:40 ` [Bug fortran/35723] " burnus at gcc dot gnu dot org
  2008-09-24 10:01 ` domob at gcc dot gnu dot org
@ 2008-09-25 10:30 ` domob at gcc dot gnu dot org
  2008-10-09  7:31 ` domob at gcc dot gnu dot org
  2008-10-09  7:35 ` domob at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: domob at gcc dot gnu dot org @ 2008-09-25 10:30 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from domob at gcc dot gnu dot org  2008-09-25 10:28 -------
I guess this is illegal, too:

PROGRAM main
  IMPLICIT NONE
  CALL test (5, (/ 1, 2, 3, 4, 5, 6, 7, 8, 9 /) )

CONTAINS

  SUBROUTINE test (n, arr)
    IMPLICIT NONE
    INTEGER :: n, arr(:)

    INTEGER :: i = 5
    INTEGER :: local(arr(n))
    INTEGER :: local2(arr(i)) ! { dg-error "XXX" }
  END SUBROUTINE test

END PROGRAM main

where the definition of local is ok, but local2 is illegal.  This program is
however accepted with gfortran without your patch.  I will implement general
checking of the references for EXPR_VARIABLEs that have one.


-- 


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


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

* [Bug fortran/35723] Can't use run-time array element in character declaration
  2008-03-27 20:34 [Bug fortran/35723] New: Can't use run-time array element in character declaration dick dot hendrickson at gmail dot com
                   ` (2 preceding siblings ...)
  2008-09-25 10:30 ` domob at gcc dot gnu dot org
@ 2008-10-09  7:31 ` domob at gcc dot gnu dot org
  2008-10-09  7:35 ` domob at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: domob at gcc dot gnu dot org @ 2008-10-09  7:31 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from domob at gcc dot gnu dot org  2008-10-09 07:29 -------
Subject: Bug 35723

Author: domob
Date: Thu Oct  9 07:28:22 2008
New Revision: 141001

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=141001
Log:
2008-10-09  Daniel Kraft  <d@domob.eu>

        PR fortran/35723
        * gfortran.h (gfc_suppress_error): Removed from header.
        (gfc_push_suppress_errors), (gfc_pop_suppress_errors): New methods.
        * array.c (gfc_array_size): Use new gfc_push/pop_suppress_errors
        instead of directly changing gfc_suppress_error.
        * intrinsic.c (gfc_intrinsic_func_interface): Ditto.
        (gfc_intrinsic_sub_interface): Ditto.
        * error.c (suppress_errors): Made static from `gfc_suppress_error'.
        (gfc_push_suppress_errors), (gfc_pop_suppress_errors): New methods.
        (gfc_notify_std), (gfc_error): Use new static name of global.
        * expr.c (check_arglist), (check_references): New methods.
        (check_restricted): Check arglists and references of EXPR_FUNCTIONs
        and EXPR_VARAIBALEs, respectively.  Allow PARAMETER symbols.

2008-10-09  Daniel Kraft  <d@domob.eu>

        PR fortran/35723
        * gfortran.dg/restricted_expression_1.f90: New test.
        * gfortran.dg/restricted_expression_2.f90: New test.
        * gfortran.dg/restricted_expression_3.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/restricted_expression_1.f90
    trunk/gcc/testsuite/gfortran.dg/restricted_expression_2.f90
    trunk/gcc/testsuite/gfortran.dg/restricted_expression_3.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/array.c
    trunk/gcc/fortran/error.c
    trunk/gcc/fortran/expr.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/intrinsic.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/35723] Can't use run-time array element in character declaration
  2008-03-27 20:34 [Bug fortran/35723] New: Can't use run-time array element in character declaration dick dot hendrickson at gmail dot com
                   ` (3 preceding siblings ...)
  2008-10-09  7:31 ` domob at gcc dot gnu dot org
@ 2008-10-09  7:35 ` domob at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: domob at gcc dot gnu dot org @ 2008-10-09  7:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from domob at gcc dot gnu dot org  2008-10-09 07:33 -------
Fixed.


-- 

domob at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2008-10-09  7:35 UTC | newest]

Thread overview: 6+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-03-27 20:34 [Bug fortran/35723] New: Can't use run-time array element in character declaration dick dot hendrickson at gmail dot com
2008-03-28 19:40 ` [Bug fortran/35723] " burnus at gcc dot gnu dot org
2008-09-24 10:01 ` domob at gcc dot gnu dot org
2008-09-25 10:30 ` domob at gcc dot gnu dot org
2008-10-09  7:31 ` domob at gcc dot gnu dot org
2008-10-09  7:35 ` domob 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).