RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / character_assign_1.f90
blob02625ad5dc0bfbe073be9227190945ecf8c42143
1 ! { dg-do compile }
2 ! Tests the fix for PR35702, which caused an ICE because the types in the assignment
3 ! were not translated to be the same.
5 ! Contributed by Dick Hendrickson <dick.hendrickson@gmail.com>
7 MODULE TESTS
8 TYPE UNSEQ
9 CHARACTER(1) :: C
10 END TYPE UNSEQ
11 CONTAINS
12 SUBROUTINE CG0028 (TDA1L, TDA1R, nf0, nf1, nf2, nf3)
13 TYPE(UNSEQ) TDA1L(NF3)
14 TDA1L(NF1:NF2:NF1)%C = TDA1L(NF0+2:NF3:NF2/2)%C
15 END SUBROUTINE
16 END MODULE TESTS