2 ! Overwrite -pedantic setting:
3 ! { dg-options "-Wall" }
5 ! Tests the fix for PR31668, in which %VAL was rejected for
6 ! module and internal procedures.
9 subroutine bmp_write(nx
)
15 end subroutine bmp_write
19 ! The following interface does in principle
20 ! not match the procedure (missing VALUE attribute)
21 ! However, this occures in real-world code calling
22 ! C routines where an interface is better than
25 subroutine bmp_write(nx
)
27 end subroutine bmp_write
30 SUBROUTINE Grid2BMP(NX
)
31 INTEGER, INTENT(IN
) :: NX
33 call bmp_write(%val(nx
))
35 END SUBROUTINE Grid2BMP
38 ! The following test is possible and
39 ! accepted by other compilers, but
40 ! does not make much sense.
41 ! Either one uses VALUE then %VAL is
42 ! not needed or the function will give
58 ! end subroutine test2