public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/51208] New: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice
@ 2011-11-18 10:54 burnus at gcc dot gnu.org
  2011-11-18 16:10 ` [Bug fortran/51208] " kargl at gcc dot gnu.org
                   ` (6 more replies)
  0 siblings, 7 replies; 8+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-11-18 10:54 UTC (permalink / raw)
  To: gcc-bugs

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

             Bug #: 51208
           Summary: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if
                    variable occurs twice
    Classification: Unclassified
           Product: gcc
           Version: 4.7.0
            Status: UNCONFIRMED
          Keywords: accepts-invalid, diagnostic
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: burnus@gcc.gnu.org


In ALLOCATE, one gets a diagnosis if one uses:

   integer, allocatable :: i
   allocate(i, stat=i)
   end

Namely:
   allocate(i, stat=i)
                 1
   Error: Stat-variable at (1) shall not be ALLOCATEd within
          the same ALLOCATE statement

However, for SOURCE= and MOLD= it does not work:

  type t
    integer :: i = 4
  end type t
  class(t), allocatable :: x, y

  allocate(t :: y)
  allocate(x, mold=x)   ! Not diagnosed
  allocate(x, source=x) ! Not diagnosed


The Intel compiler gives the error:
  error #8152: Neither the ERRMSG= variable nor any part of the source
  expression in SOURCE= or MOLD= specifiers may be allocated in the
  ALLOCATE statement in which it appears.   [X]


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

* [Bug fortran/51208] [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice
  2011-11-18 10:54 [Bug fortran/51208] New: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice burnus at gcc dot gnu.org
@ 2011-11-18 16:10 ` kargl at gcc dot gnu.org
  2011-11-18 16:12 ` burnus at gcc dot gnu.org
                   ` (5 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: kargl at gcc dot gnu.org @ 2011-11-18 16:10 UTC (permalink / raw)
  To: gcc-bugs

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

kargl at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |kargl at gcc dot gnu.org

--- Comment #1 from kargl at gcc dot gnu.org 2011-11-18 15:53:51 UTC ---
(In reply to comment #0)
> In ALLOCATE, one gets a diagnosis if one uses:
> 
>    integer, allocatable :: i
>    allocate(i, stat=i)
>    end
> 
> Namely:
>    allocate(i, stat=i)
>                  1
>    Error: Stat-variable at (1) shall not be ALLOCATEd within
>           the same ALLOCATE statement

The above error is easy to produce, because gfortran
only has to check if an alloc-object is used as a
stat-variable.

> 
> However, for SOURCE= and MOLD= it does not work:
> 
>   type t
>     integer :: i = 4
>   end type t
>   class(t), allocatable :: x, y
> 
>   allocate(t :: y)
>   allocate(x, mold=x)   ! Not diagnosed
>   allocate(x, source=x) ! Not diagnosed

Doing a check here requires a walk of the mold-expr
and the source-expr, which is of course much more
work (unless gfortran already has a helper function
to check if a variable is used within an expression).

Here's a simple example where walking source-expr
may find the use of the alloc-object:

module bar
  real, allocatable :: x(:)
  contains
  function f(a)
    real f
    real :: a(:)
    f = sum(a)
  end function
end module bar

program foo
  use bar
  allocate(x(2), source=f(x))
  print *, x
end program foo
!
!program foo
!  use bar
!  allocate(x(2), source=f([1., 2.]))
!  print *, x
!end program foo


and here's a more complicated example.

module bar
  real, allocatable :: x(:)
  contains
  function f(a)
    real f
    real :: a
    f = sum(a * x)  ! x used un-allocated?
  end function
end module bar

program foo
  use bar
  allocate(x(2), source=f(2.))
  print *, x
end program foo


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

* [Bug fortran/51208] [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice
  2011-11-18 10:54 [Bug fortran/51208] New: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice burnus at gcc dot gnu.org
  2011-11-18 16:10 ` [Bug fortran/51208] " kargl at gcc dot gnu.org
@ 2011-11-18 16:12 ` burnus at gcc dot gnu.org
  2011-11-18 19:03 ` sgk at troutmask dot apl.washington.edu
                   ` (4 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-11-18 16:12 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-11-18 16:03:04 UTC ---
(In reply to comment #1)
> (In reply to comment #0)
> >    allocate(i, stat=i)
> >                  1
> >    Error: Stat-variable at (1) shall not be ALLOCATEd within
> >           the same ALLOCATE statement
> 
> The above error is easy to produce, because gfortran
> only has to check if an alloc-object is used as a
> stat-variable.

Well, you can make it also more complicated:
  allocate (a(1)%i, stat=a%(2-1)%i)

Or extremely complicated:

  integer, pointer :: ptr
  allocate (ptr, stat=f())
contains
  function f()
    integer, pointer :: f
    f => ptr
  end function
end

(Recall that a pointer-function result is a variable in Fortran 2008.)


> > However, for SOURCE= and MOLD= it does not work:
> 
> Doing a check here requires a walk of the mold-expr
> and the source-expr, which is of course much more
> work

Well, it is not. One can restrict one to the common case of expr->expr_type ==
EXPR_VARIABLE and just do the same as for STAT=: Checking whether the variable
is the same.


Will that catch all wrong usage? No, but it will catch the most common mistake
of choosing the wrong variable. That's as illustrated above the same with
STAT=.

I am sure that Intel's compiler does not do anything more advanced - and it
would have found the mistake I made in PR 51207.


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

* [Bug fortran/51208] [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice
  2011-11-18 10:54 [Bug fortran/51208] New: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice burnus at gcc dot gnu.org
  2011-11-18 16:10 ` [Bug fortran/51208] " kargl at gcc dot gnu.org
  2011-11-18 16:12 ` burnus at gcc dot gnu.org
@ 2011-11-18 19:03 ` sgk at troutmask dot apl.washington.edu
  2011-11-18 19:07 ` burnus at gcc dot gnu.org
                   ` (3 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2011-11-18 19:03 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from Steve Kargl <sgk at troutmask dot apl.washington.edu> 2011-11-18 18:40:31 UTC ---
On Fri, Nov 18, 2011 at 04:03:04PM +0000, burnus at gcc dot gnu.org wrote:
> 
> Well, it is not. One can restrict one to the common case of expr->expr_type ==
> EXPR_VARIABLE and just do the same as for STAT=: Checking whether the variable
> is the same.
> 
> Will that catch all wrong usage? No, but it will catch the most common mistake
> of choosing the wrong variable. That's as illustrated above the same with
> STAT=.
> 
> I am sure that Intel's compiler does not do anything more advanced - and it
> would have found the mistake I made in PR 51207.
> 

Although I think this is equilavent to putting a bandaid
on a AK-47 bullet hole, here you go

troutmask:sgk[246] cat foo.f90

program foo
  use bar
  allocate(x(2), source=x)
end program foo


troutmask:sgk[245] gfc4x -o z -Wall -Wextra foo.f90
foo.f90:4.11-24:

  allocate(x(2), source=x)
           1            2
Error: Allocate-object at (1) shall not appear in a source-expr or mold-expr at
(2)


Index: resolve.c
===================================================================
--- resolve.c    (revision 181489)
+++ resolve.c    (working copy)
@@ -7173,6 +7173,38 @@ resolve_allocate_deallocate (gfc_code *c
       }
     }

+  /* If source-expr or mold-expr is a variable, check that it
+     is not an alloc-object.  */
+  if (code->expr3 && code->expr3->expr_type == EXPR_VARIABLE)
+    {
+      for (p = code->ext.alloc.list; p; p = p->next)
+    if (p->expr->symtree->n.sym->name == code->expr3->symtree->n.sym->name)
+      {
+        gfc_ref *ref1, *ref2;
+        bool found = true;
+
+        for (ref1 = p->expr->ref, ref2 = code->expr3->ref; ref1 && ref2;
+         ref1 = ref1->next, ref2 = ref2->next)
+          {
+        if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
+          continue;
+        if (ref1->u.c.component->name != ref2->u.c.component->name)
+          {
+            found = false;
+            break;
+          }
+          }
+
+        if (found)
+          {
+        gfc_error ("Allocate-object at %L shall not appear in a "
+               "source-expr or mold-expr at %L",
+                &p->expr->where, &code->expr3->where);
+        break;
+          }
+      }
+    }
+
   /* Check that an allocate-object appears only once in the statement.  
      FIXME: Checking derived types is disabled.  */
   for (p = code->ext.alloc.list; p; p = p->next)


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

* [Bug fortran/51208] [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice
  2011-11-18 10:54 [Bug fortran/51208] New: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2011-11-18 19:03 ` sgk at troutmask dot apl.washington.edu
@ 2011-11-18 19:07 ` burnus at gcc dot gnu.org
  2011-11-18 19:55 ` sgk at troutmask dot apl.washington.edu
                   ` (2 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-11-18 19:07 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #4 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-11-18 19:02:25 UTC ---
(In reply to comment #3)
> Although I think this is equivalent to putting a bandaid
> on a AK-47 bullet hole, here you go

Thanks for the patch. Only one remark: For
  allocate (x(2)%a, source=x(1)%a)
one gets a false positive.


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

* [Bug fortran/51208] [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice
  2011-11-18 10:54 [Bug fortran/51208] New: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2011-11-18 19:07 ` burnus at gcc dot gnu.org
@ 2011-11-18 19:55 ` sgk at troutmask dot apl.washington.edu
  2013-01-07 23:16 ` dominiq at lps dot ens.fr
  2013-01-07 23:37 ` sgk at troutmask dot apl.washington.edu
  6 siblings, 0 replies; 8+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2011-11-18 19:55 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Steve Kargl <sgk at troutmask dot apl.washington.edu> 2011-11-18 19:49:32 UTC ---
On Fri, Nov 18, 2011 at 07:02:25PM +0000, burnus at gcc dot gnu.org wrote:
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=51208
> 
> --- Comment #4 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-11-18 19:02:25 UTC ---
> (In reply to comment #3)
> > Although I think this is equivalent to putting a bandaid
> > on a AK-47 bullet hole, here you go
> 
> Thanks for the patch. Only one remark: For
>   allocate (x(2)%a, source=x(1)%a)
> one gets a false positive.
> 

bandaid (adj) -- Informal. serving as a makeshift, limited,
or temporary aid or solution

:-)

The error message can be disable for derived type objects via

  if (found && p->expr->symtree->n.sym->ts.type != BT_DERIVED)

now one may get accepts-invalid over a false-positive.


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

* [Bug fortran/51208] [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice
  2011-11-18 10:54 [Bug fortran/51208] New: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice burnus at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2011-11-18 19:55 ` sgk at troutmask dot apl.washington.edu
@ 2013-01-07 23:16 ` dominiq at lps dot ens.fr
  2013-01-07 23:37 ` sgk at troutmask dot apl.washington.edu
  6 siblings, 0 replies; 8+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-01-07 23:16 UTC (permalink / raw)
  To: gcc-bugs


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

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2013-01-07
     Ever Confirmed|0                           |1

--- Comment #6 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-01-07 23:16:13 UTC ---
(In reply to comment #2)
> Or extremely complicated:
>
>   integer, pointer :: ptr
>   allocate (ptr, stat=f())
> contains
>   function f()
>     integer, pointer :: f
>     f => ptr
>   end function
> end
>
> (Recall that a pointer-function result is a variable in Fortran 2008.)

At revision 194996, I get

  allocate (ptr, stat=f())
                       1
Error: Syntax error in ALLOCATE statement at (1)

Is this another bug or is the error correct?


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

* [Bug fortran/51208] [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice
  2011-11-18 10:54 [Bug fortran/51208] New: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice burnus at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2013-01-07 23:16 ` dominiq at lps dot ens.fr
@ 2013-01-07 23:37 ` sgk at troutmask dot apl.washington.edu
  6 siblings, 0 replies; 8+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2013-01-07 23:37 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #7 from Steve Kargl <sgk at troutmask dot apl.washington.edu> 2013-01-07 23:36:50 UTC ---
On Mon, Jan 07, 2013 at 11:16:13PM +0000, dominiq at lps dot ens.fr wrote:
> (In reply to comment #2)
> > Or extremely complicated:
> >
> >   integer, pointer :: ptr
> >   allocate (ptr, stat=f())
> > contains
> >   function f()
> >     integer, pointer :: f
> >     f => ptr
> >   end function
> > end
> >
> > (Recall that a pointer-function result is a variable in Fortran 2008.)
> 
> At revision 194996, I get
> 
>   allocate (ptr, stat=f())
>                        1
> Error: Syntax error in ALLOCATE statement at (1)
> 
> Is this another bug or is the error correct?
> 

An error is in order, but I'm not sure if the above is
the correct error.  From F08,

    The stat-variable shall not be allocated or deallocated within the
    ALLOCATE or DEALLOCATE statement in which it appears; nor shall it
    depend on the value, bounds, deferred type parameters, allocation
    status, or association status of any allocate-object in that statement.

I haven't verified the statement that "a pointer-function is a variable",
but assuming that this is true, you have 

   allocate(ptr, stat=ptr)


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

end of thread, other threads:[~2013-01-07 23:37 UTC | newest]

Thread overview: 8+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-11-18 10:54 [Bug fortran/51208] New: [OOP] ALLOCATE with SOURCE= or MOLD=: Diagnose if variable occurs twice burnus at gcc dot gnu.org
2011-11-18 16:10 ` [Bug fortran/51208] " kargl at gcc dot gnu.org
2011-11-18 16:12 ` burnus at gcc dot gnu.org
2011-11-18 19:03 ` sgk at troutmask dot apl.washington.edu
2011-11-18 19:07 ` burnus at gcc dot gnu.org
2011-11-18 19:55 ` sgk at troutmask dot apl.washington.edu
2013-01-07 23:16 ` dominiq at lps dot ens.fr
2013-01-07 23:37 ` sgk at troutmask dot apl.washington.edu

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