aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/deferred_character_9.f90
blob: f88de7a4ad5397a1332e1f2f6fe16fe552320a88 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
! { 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") call abort
end