OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [intrinsic_optional_char_arg_1.f90] - Rev 700

Go to most recent revision | Compare with Previous | Blame | View Log

! { 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" } }
! { dg-final { cleanup-tree-dump "original" } }

Go to most recent revision | Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.