lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / deferred_character_9.f90
blob5dbd068108ac5a93f2bdd7ff92c60bf7f3ac4edf
1 ! { dg-do run }
3 ! Test the fix for PR64324 in which deferred length user ops
4 ! were being mistaken as assumed length and so rejected.
6 ! Contributed by Ian Harvey <ian_harvey@bigpond.com>
8 MODULE m
9 IMPLICIT NONE
10 INTERFACE OPERATOR(.ToString.)
11 MODULE PROCEDURE tostring
12 END INTERFACE OPERATOR(.ToString.)
13 CONTAINS
14 FUNCTION tostring(arg)
15 INTEGER, INTENT(IN) :: arg
16 CHARACTER(:), ALLOCATABLE :: tostring
17 allocate (character(5) :: tostring)
18 write (tostring, "(I5)") arg
19 END FUNCTION tostring
20 END MODULE m
22 use m
23 character(:), allocatable :: str
24 integer :: i = 999
25 str = .ToString. i
26 if (str .ne. " 999") STOP 1
27 end