Update ChangeLog and version files for release
[official-gcc.git] / gcc / testsuite / gfortran.dg / c_loc_test_18.f90
blobb8542002f59deeeb117646940e2fd002293207ce
1 ! { dg-do compile }
3 ! PR fortran/39288
5 ! From IR F03/0129, cf.
6 ! Fortran 2003, Technical Corrigendum 5
8 ! Was invalid before.
10 SUBROUTINE S(A,I,K)
11 USE ISO_C_BINDING
12 CHARACTER(*),TARGET :: A
13 CHARACTER(:),ALLOCATABLE,TARGET :: B
14 TYPE(C_PTR) P1,P2,P3,P4,P5
15 P1 = C_LOC(A(1:1)) ! *1
16 P2 = C_LOC(A(I:I)) ! *2
17 P3 = C_LOC(A(1:)) ! *3
18 P4 = C_LOC(A(I:K)) ! *4
19 ALLOCATE(CHARACTER(1)::B)
20 P5 = C_LOC(B) ! *5
21 END SUBROUTINE