Mercurial > hg > CbC > CbC_gcc
view gcc/testsuite/gfortran.dg/deferred_character_9.f90 @ 145:1830386684a0
gcc-9.2.0
author | anatofuz |
---|---|
date | Thu, 13 Feb 2020 11:34:05 +0900 |
parents | 84e7813d76e9 |
children |
line wrap: on
line source
! { dg-do run } ! ! Test the fix for PR64324 in which deferred length user ops ! were being mistaken as assumed length and so rejected. ! ! Contributed by Ian Harvey <ian_harvey@bigpond.com> ! MODULE m IMPLICIT NONE INTERFACE OPERATOR(.ToString.) MODULE PROCEDURE tostring END INTERFACE OPERATOR(.ToString.) CONTAINS FUNCTION tostring(arg) INTEGER, INTENT(IN) :: arg CHARACTER(:), ALLOCATABLE :: tostring allocate (character(5) :: tostring) write (tostring, "(I5)") arg END FUNCTION tostring END MODULE m use m character(:), allocatable :: str integer :: i = 999 str = .ToString. i if (str .ne. " 999") STOP 1 end