view gcc/testsuite/gfortran.dg/intrinsic_optional_char_arg_1.f90 @ 145:1830386684a0

gcc-9.2.0
author anatofuz
date Thu, 13 Feb 2020 11:34:05 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
! { dg-options "-fdump-tree-original" }

! PR fortran/36403
! Check that string lengths of optional arguments are added to the library-call
! even if those arguments are missing.

PROGRAM main
  IMPLICIT NONE

  CHARACTER(len=1) :: vect(4)
  CHARACTER(len=1) :: matrix(2, 2)

  matrix(1, 1) = ""
  matrix(2, 1) = "a"
  matrix(1, 2) = "b"
  matrix(2, 2) = ""
  vect = (/ "w", "x", "y", "z" /)

  ! Call the affected intrinsics
  vect = EOSHIFT (vect, 2)
  vect = PACK (matrix, matrix /= "")
  matrix = RESHAPE (vect, (/ 2, 2 /))

END PROGRAM main

! All library function should be called with *two* trailing arguments "1" for
! the string lengths of both the main array and the optional argument:
! { dg-final { scan-tree-dump "_eoshift\[0-9_\]+char \\(\[&a-zA-Z0-9._, \]+, 1, 0\\)" "original" } }
! { dg-final { scan-tree-dump "_reshape\[0-9_\]+char \\(\[&a-zA-Z0-9._, \]+, 1, 0\\)" "original" } }
! { dg-final { scan-tree-dump "_pack\[0-9_\]+char \\(\[&a-zA-Z0-9._, \]+, 1, 0\\)" "original" } }