view gcc/testsuite/gfortran.dg/pointer_intent_6.f90 @ 158:494b0b89df80 default tip

...
author Shinji KONO <kono@ie.u-ryukyu.ac.jp>
date Mon, 25 May 2020 18:13:55 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
!
! PR fortran/52864
!
! Assigning to an intent(in) pointer (which is valid).
!
      program test
         type PoisFFT_Solver3D
           complex, dimension(:,:,:), &
                           pointer :: work => null()
         end type PoisFFT_Solver3D
      contains
        subroutine PoisFFT_Solver3D_FullPeriodic(D, p)
          type(PoisFFT_Solver3D), intent(in) :: D
          real, intent(in), pointer :: p(:)
          D%work(i,j,k) = 0.0
          p = 0.0
        end subroutine
      end