view gcc/testsuite/gfortran.dg/derived_result_2.f90 @ 144:8f4e72ab4e11

fix segmentation fault caused by nothing next cur_op to end
author Takahiro SHIMIZU <anatofuz@cr.ie.u-ryukyu.ac.jp>
date Sun, 23 Dec 2018 21:23:56 +0900
parents 04ced10e8804
children 1830386684a0
line wrap: on
line source

! { dg-do compile }
!
! PR 42188: [OOP] F03:C612. The leftmost part-name shall be the name of a data object
!
! Contributed by Janus Weil <janus@gcc.gnu.org>

module grid_module
 implicit none
 type grid
 contains
   procedure :: new_grid
   procedure :: new_int
 end type
contains
 subroutine new_grid(this)
   class(grid) :: this
 end subroutine
 integer function new_int(this)
   class(grid) :: this
   new_int = 42
 end function
end module

module field_module
 use grid_module
 implicit none

 type field
   type(grid) :: mesh
 end type

contains

 type(field) function new_field()
 end function

 subroutine test
   integer :: i
   type(grid) :: g
   g = new_field()%mesh              ! { dg-error "can not be a function reference" }
   call new_field()%mesh%new_grid()  ! { dg-error "Syntax error" }
   i = new_field() % mesh%new_int()  ! { dg-error "can not be a function reference" }
 end subroutine

end module