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

Subversion Repositories openrisc

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc2/] [gcc/] [testsuite/] [gfortran.dg/] [intrinsic_optional_char_arg_1.f90] - Blame information for rev 302

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

Line No. Rev Author Line
1 302 jeremybenn
! { dg-do compile }
2
! { dg-options "-fdump-tree-original" }
3
 
4
! PR fortran/36403
5
! Check that string lengths of optional arguments are added to the library-call
6
! even if those arguments are missing.
7
 
8
PROGRAM main
9
  IMPLICIT NONE
10
 
11
  CHARACTER(len=1) :: vect(4)
12
  CHARACTER(len=1) :: matrix(2, 2)
13
 
14
  matrix(1, 1) = ""
15
  matrix(2, 1) = "a"
16
  matrix(1, 2) = "b"
17
  matrix(2, 2) = ""
18
  vect = (/ "w", "x", "y", "z" /)
19
 
20
  ! Call the affected intrinsics
21
  vect = EOSHIFT (vect, 2)
22
  vect = PACK (matrix, matrix /= "")
23
  matrix = RESHAPE (vect, (/ 2, 2 /))
24
 
25
END PROGRAM main
26
 
27
! All library function should be called with *two* trailing arguments "1" for
28
! the string lengths of both the main array and the optional argument:
29
! { dg-final { scan-tree-dump "_eoshift\[0-9_\]+char \\(\[&a-zA-Z0-9._, \]+, 1, 0\\)" "original" } }
30
! { dg-final { scan-tree-dump "_reshape\[0-9_\]+char \\(\[&a-zA-Z0-9._, \]+, 1, 0\\)" "original" } }
31
! { dg-final { scan-tree-dump "_pack\[0-9_\]+char \\(\[&a-zA-Z0-9._, \]+, 1, 0\\)" "original" } }
32
! { dg-final { cleanup-tree-dump "original" } }

powered by: WebSVN 2.1.0

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