public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function
@ 2014-11-17 18:31 mirco.valentini at polimi dot it
  2014-12-07 13:35 ` [Bug fortran/63921] " dominiq at lps dot ens.fr
                   ` (7 more replies)
  0 siblings, 8 replies; 9+ messages in thread
From: mirco.valentini at polimi dot it @ 2014-11-17 18:31 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63921

            Bug ID: 63921
           Summary: [F08] pointer function as lvalue doesn't work when the
                    function is a type bound function
           Product: gcc
           Version: 4.9.2
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: mirco.valentini at polimi dot it

Created attachment 34006
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=34006&action=edit
Source code useful to explain the bug

If I try to use a type bounded function as lvalue 
the compiler throw this error

!...COMPILER
VERSION............................................................
Using built-in specs.
COLLECT_GCC=/opt/gcc/5.0/bin/gfortran
COLLECT_LTO_WRAPPER=/opt/gcc/5.0/libexec/gcc/x86_64-unknown-linux-gnu/4.9.2/lto-wrapper
Target: x86_64-unknown-linux-gnu
Configured with: ../src/configure --prefix /opt/gcc/5.0/
Thread model: posix
gcc version 4.9.2 (GCC) 
!...............................................................................

!...COMPILER
OUTPUT.............................................................
lvalue.f90:110.2:

  STENCIL%JMP( 1, 1 ) = 10.0d0 + STENCIL%JMP( 1, 1 )
  1
Error: 'lvalue_jmp' in variable definition context (assignment) at (1) is not a
variable
make: *** [test.x] Error 1
!...............................................................................

!...COMPILING
COMMAND...........................................................
gfortran -save-temps lvalue.f90 -o test.x
!...............................................................................


If I want to modify the data pointed by the function I need to use a temporary
variable.

!... BUG ......................................................................
  ...
  !...Running version with temporary pointer
  !real_tmp_ptr => STENCIL%JMP( 1, 1 )
  !real_tmp_ptr = 10.0d0 + STENCIL%JMP( 1, 1 )

  !...Not running version
  STENCIL%JMP( 1, 1 ) = 10.0d0 + STENCIL%JMP( 1, 1 )
  ...
!..............................................................................

Mirco


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

* [Bug fortran/63921] [F08] pointer function as lvalue doesn't work when the function is a type bound function
  2014-11-17 18:31 [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function mirco.valentini at polimi dot it
@ 2014-12-07 13:35 ` dominiq at lps dot ens.fr
  2014-12-07 16:23 ` mirco.valentini at polimi dot it
                   ` (6 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: dominiq at lps dot ens.fr @ 2014-12-07 13:35 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63921

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2014-12-07
     Ever confirmed|0                           |1

--- Comment #1 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
Am I correct to understand that you are referring to C602 in

6.2 Variable
R602 variable is designator
              or expr
C601 (R602) designator shall not be a constant or a subobject of a constant.
C602 (R602) expr shall be a reference to a function that has a pointer result.
1 A variable is either the data object denoted by designator or the target of
expr.
...

? If yes, then I can confirm this PR.


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

* [Bug fortran/63921] [F08] pointer function as lvalue doesn't work when the function is a type bound function
  2014-11-17 18:31 [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function mirco.valentini at polimi dot it
  2014-12-07 13:35 ` [Bug fortran/63921] " dominiq at lps dot ens.fr
@ 2014-12-07 16:23 ` mirco.valentini at polimi dot it
  2015-08-10 21:19 ` mirco.valentini at polimi dot it
                   ` (5 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: mirco.valentini at polimi dot it @ 2014-12-07 16:23 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63921

--- Comment #2 from mirco <mirco.valentini at polimi dot it> ---
(In reply to Dominique d'Humieres from comment #1)
> Am I correct to understand that you are referring to C602 in
> 
> 6.2 Variable
> R602 variable is designator
>               or expr
> C601 (R602) designator shall not be a constant or a subobject of a constant.
> C602 (R602) expr shall be a reference to a function that has a pointer
> result.
> 1 A variable is either the data object denoted by designator or the target
> of expr.
> ...
> 
> ? If yes, then I can confirm this PR.

Yes, it is exactly what I mean. 
Thank you for your detailed explanation.

Mirco


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

* [Bug fortran/63921] [F08] pointer function as lvalue doesn't work when the function is a type bound function
  2014-11-17 18:31 [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function mirco.valentini at polimi dot it
  2014-12-07 13:35 ` [Bug fortran/63921] " dominiq at lps dot ens.fr
  2014-12-07 16:23 ` mirco.valentini at polimi dot it
@ 2015-08-10 21:19 ` mirco.valentini at polimi dot it
  2015-08-10 22:55 ` dominiq at lps dot ens.fr
                   ` (4 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: mirco.valentini at polimi dot it @ 2015-08-10 21:19 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63921

mirco <mirco.valentini at polimi dot it> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|normal                      |critical


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

* [Bug fortran/63921] [F08] pointer function as lvalue doesn't work when the function is a type bound function
  2014-11-17 18:31 [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function mirco.valentini at polimi dot it
                   ` (2 preceding siblings ...)
  2015-08-10 21:19 ` mirco.valentini at polimi dot it
@ 2015-08-10 22:55 ` dominiq at lps dot ens.fr
  2015-09-05 21:14 ` pault at gcc dot gnu.org
                   ` (3 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-08-10 22:55 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63921

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|critical                    |normal

--- Comment #3 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
Reset the importance to normal: as for today there are 854 open PRs and several
hundreds of them are more or as 'critical' than this one.

If this PR is really critical for you, you should consider to fix it yourself
(or hire someone to do it for you).


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

* [Bug fortran/63921] [F08] pointer function as lvalue doesn't work when the function is a type bound function
  2014-11-17 18:31 [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function mirco.valentini at polimi dot it
                   ` (3 preceding siblings ...)
  2015-08-10 22:55 ` dominiq at lps dot ens.fr
@ 2015-09-05 21:14 ` pault at gcc dot gnu.org
  2015-09-06 10:03 ` mirco.valentini at polimi dot it
                   ` (2 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu.org @ 2015-09-05 21:14 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63921

Paul Thomas <pault at gcc dot gnu.org> changed:

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

--- Comment #4 from Paul Thomas <pault at gcc dot gnu.org> ---
(In reply to Dominique d'Humieres from comment #3)
> Reset the importance to normal: as for today there are 854 open PRs and
> several hundreds of them are more or as 'critical' than this one.
> 
> If this PR is really critical for you, you should consider to fix it
> yourself (or hire someone to do it for you).

Dear Mirco,

You will be happy to know that I have a patch for pointer function assignment,
which fixes your problem. It will be submitted tomorrow.

Dominique tested the patch today and recalled your problem report. I have
recast your testcase and it appears below. I might not use this in the
testsuite since it largely duplicates the one that I had written. However, the
line  STENCIL%JMP (1, 1 ) = 10.0d0 + STENCIL%JMP (1, 1 ) is neat and I will
probably add something like it together with an attribution to you.

Dominique also reminded me that PR40054 covers this missing feature from
gfortran.

Thanks for the report.

Paul

! { dg-do run }
!
! Testcase for pointer function assignment from PR63921
! Contributed by Mirco Valentini  <mirco.valentini@polimi.it>
!
MODULE grid
  IMPLICIT NONE
  PRIVATE
  REAL(KIND=8), DIMENSION(100,100), TARGET :: WORKSPACE
  TYPE, PUBLIC :: grid_t
    REAL(KIND=8), DIMENSION(:,:), POINTER :: P => NULL ()
  END TYPE
  PUBLIC :: INIT
CONTAINS
  SUBROUTINE INIT( DAT )
    IMPLICIT NONE
    TYPE(grid_t), INTENT(INOUT) :: DAT
    INTEGER :: I, J
    DAT%P => WORKSPACE
    DO I = 1, 100
      DO J = 1, 100
        DAT%P(I,J) = REAL ((I - 1)*100 + J - 1 )
      END DO
    ENDDO
 END SUBROUTINE INIT
END MODULE grid

MODULE subgrid
  USE :: grid, ONLY: grid_t
  IMPLICIT NONE
  PRIVATE
  TYPE, PUBLIC :: subgrid_t
    INTEGER, DIMENSION(4) :: range
    CLASS(grid_t), POINTER    :: grd => NULL ()
  CONTAINS
    PROCEDURE, PASS :: INIT => LVALUE_INIT
    PROCEDURE, PASS :: JMP => LVALUE_JMP
  END TYPE
CONTAINS
  SUBROUTINE LVALUE_INIT(HOBJ, P, D  )
    IMPLICIT NONE
    CLASS(subgrid_t), INTENT(INOUT) :: HOBJ
    TYPE(grid_t), POINTER, INTENT(IN)    :: P
    INTEGER, DIMENSION(4),   INTENT(IN)    :: D
    HOBJ%range = D
    HOBJ%grd => P
  END SUBROUTINE LVALUE_INIT

  FUNCTION LVALUE_JMP(HOBJ, I, J ) RESULT(P)
    IMPLICIT NONE
    CLASS(subgrid_t), INTENT(INOUT) :: HOBJ
    INTEGER, INTENT(IN) :: I, J
    REAL(KIND=8), POINTER :: P
    P => HOBJ%grd%P( HOBJ%range(1) + I - 1, HOBJ%range(3) + J - 1 )
  END FUNCTION LVALUE_JMP
END MODULE subgrid

PROGRAM test_lvalue
  USE :: grid
  USE :: subgrid
  IMPLICIT NONE
  TYPE(grid_t), POINTER :: GRID
  TYPE(subgrid_t) :: STENCIL
  REAL(KIND=8), POINTER :: real_tmp_ptr
  REAL(KIND=8) :: old_val
  ALLOCATE (GRID)
  CALL INIT (GRID)
  CALL STENCIL%INIT (GRID, [50, 52, 50, 53 ])
  old_val = STENCIL%JMP (1, 1 )

  ! Workaround
  !real_tmp_ptr => STENCIL%JMP( 1, 1 )
  !real_tmp_ptr = 10.0d0 + STENCIL%JMP( 1, 1 )

  ! This failed
  STENCIL%JMP (1, 1 ) = 10.0d0 + STENCIL%JMP (1, 1 )
  if (STENCIL%JMP (1, 1 ) .ne. old_val + 10.0d0) call abort
END PROGRAM test_lvalue


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

* [Bug fortran/63921] [F08] pointer function as lvalue doesn't work when the function is a type bound function
  2014-11-17 18:31 [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function mirco.valentini at polimi dot it
                   ` (4 preceding siblings ...)
  2015-09-05 21:14 ` pault at gcc dot gnu.org
@ 2015-09-06 10:03 ` mirco.valentini at polimi dot it
  2015-09-28 21:19 ` pault at gcc dot gnu.org
  2015-09-28 21:25 ` pault at gcc dot gnu.org
  7 siblings, 0 replies; 9+ messages in thread
From: mirco.valentini at polimi dot it @ 2015-09-06 10:03 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63921

--- Comment #5 from mirco <mirco.valentini at polimi dot it> ---
Thank you Paul, 

I was trying to follow the Dominique's suggestion and to fix the problem by
myself but it was the first time I examined the gfortran's code, and I was
still trying to understand its structure.  I'm looking forward to see your
patch in order to better understand gfortran.

Best regards

Mirco


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

* [Bug fortran/63921] [F08] pointer function as lvalue doesn't work when the function is a type bound function
  2014-11-17 18:31 [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function mirco.valentini at polimi dot it
                   ` (5 preceding siblings ...)
  2015-09-06 10:03 ` mirco.valentini at polimi dot it
@ 2015-09-28 21:19 ` pault at gcc dot gnu.org
  2015-09-28 21:25 ` pault at gcc dot gnu.org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu.org @ 2015-09-28 21:19 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63921

--- Comment #6 from Paul Thomas <pault at gcc dot gnu.org> ---
Author: pault
Date: Mon Sep 28 21:18:38 2015
New Revision: 228222

URL: https://gcc.gnu.org/viewcvs?rev=228222&root=gcc&view=rev
Log:
2015-09-28  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/40054
        PR fortran/63921
        * decl.c (get_proc_name): Return if statement function is
        found.
        * expr.c (gfc_check_vardef_context): Add error return for
        derived type expression lacking the derived type itself.
        * match.c (gfc_match_ptr_fcn_assign): New function.
        * match.h : Add prototype for gfc_match_ptr_fcn_assign.
        * parse.c : Add static flag 'in_specification_block'.
        (decode_statement): If in specification block match a statement
        function, then, if no error arising from statement function
        matching, try to match pointer function assignment.
        (parse_interface): Set 'in_specification_block' on exiting from
        parse_spec.
        (parse_spec): Set and then reset 'in_specification_block'.
        (gfc_parse_file): Set 'in_specification_block'.
        * resolve.c (get_temp_from_expr): Extend to include functions
        and array constructors as rvalues..
        (resolve_ptr_fcn_assign): New function.
        (gfc_resolve_code): Call it on finding a pointer function as an
        lvalue. If valid or on error, go back to start of resolve_code.
        * symbol.c (gfc_add_procedure): Add a sentence to the error to
        flag up the ambiguity between a statement function and pointer
        function assignment at the end of the specification block.

2015-09-28  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/40054
        PR fortran/63921
        * gfortran.dg/fmt_tab_1.f90: Change from run to compile and set
        standard as legacy.
        * gfortran.dg/fmt_tab_2.f90: Add extra tab error.
        * gfortran.dg/function_types_3.f90: Change error message to
        "Type inaccessible...."
        * gfortran.dg/ptr_func_assign_1.f08: New test.
        * gfortran.dg/ptr_func_assign_2.f08: New test.

2015-09-25  Mikael Morin  <mikael.morin@sfr.fr>

        PR fortran/40054
        PR fortran/63921
        * gfortran.dg/ptr_func_assign_3.f08: New test.
        * gfortran.dg/ptr_func_assign_4.f08: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/ptr_func_assign_1.f08
    trunk/gcc/testsuite/gfortran.dg/ptr_func_assign_2.f08
    trunk/gcc/testsuite/gfortran.dg/ptr_func_assign_3.f08
    trunk/gcc/testsuite/gfortran.dg/ptr_func_assign_4.f08
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/decl.c
    trunk/gcc/fortran/expr.c
    trunk/gcc/fortran/match.c
    trunk/gcc/fortran/match.h
    trunk/gcc/fortran/parse.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/symbol.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/fmt_tab_1.f90
    trunk/gcc/testsuite/gfortran.dg/fmt_tab_2.f90
    trunk/gcc/testsuite/gfortran.dg/function_types_3.f90


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

* [Bug fortran/63921] [F08] pointer function as lvalue doesn't work when the function is a type bound function
  2014-11-17 18:31 [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function mirco.valentini at polimi dot it
                   ` (6 preceding siblings ...)
  2015-09-28 21:19 ` pault at gcc dot gnu.org
@ 2015-09-28 21:25 ` pault at gcc dot gnu.org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu.org @ 2015-09-28 21:25 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63921

Paul Thomas <pault at gcc dot gnu.org> changed:

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

--- Comment #7 from Paul Thomas <pault at gcc dot gnu.org> ---
Dear Mirco,

Your testcase got rather subsumed but thanks anyway... it still works :-)

Fixed on trunk.

Paul


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

end of thread, other threads:[~2015-09-28 21:25 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2014-11-17 18:31 [Bug fortran/63921] New: [F08] pointer function as lvalue doesn't work when the function is a type bound function mirco.valentini at polimi dot it
2014-12-07 13:35 ` [Bug fortran/63921] " dominiq at lps dot ens.fr
2014-12-07 16:23 ` mirco.valentini at polimi dot it
2015-08-10 21:19 ` mirco.valentini at polimi dot it
2015-08-10 22:55 ` dominiq at lps dot ens.fr
2015-09-05 21:14 ` pault at gcc dot gnu.org
2015-09-06 10:03 ` mirco.valentini at polimi dot it
2015-09-28 21:19 ` pault at gcc dot gnu.org
2015-09-28 21:25 ` pault at gcc dot gnu.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).