URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [char_length_8.f90] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do run }! Test the fix for PR31197 and PR31258 in which the substrings below! would cause ICEs because the character lengths were never resolved.!! Contributed by Joost VandeVondele <jv244@cam.ac.uk>! and Thomas Koenig <tkoenig@gcc.gnu.org>!CHARACTER(LEN=3), DIMENSION(10) :: ZCHARACTER(LEN=3), DIMENSION(3,3) :: Winteger :: ctr = 0call test_reshapecall test_eoshiftcall test_cshiftcall test_spreadcall test_transposecall test_packcall test_unpackcall test_pr31197if (ctr .ne. 8) call abortcontainssubroutine test_reshapeZ(:)="123"if (any (RESHAPE(Z(:)(2:2),(/5,2/)) .ne. "2")) call abortctr = ctr + 1end subroutinesubroutine test_eoshiftCHARACTER(LEN=1), DIMENSION(10) :: chkchk(1:8) = "5"chk(9:10) = " "Z(:)="456"if (any (EOSHIFT(Z(:)(2:2),2) .ne. chk)) call abortctr = ctr + 1END subroutinesubroutine test_cshiftZ(:)="901"if (any (CSHIFT(Z(:)(2:2),2) .ne. "0")) call abortctr = ctr + 1end subroutinesubroutine test_spreadZ(:)="789"if (any (SPREAD(Z(:)(2:2),dim=1,ncopies=2) .ne. "8")) call abortctr = ctr + 1end subroutinesubroutine test_transposeW(:, :)="abc"if (any (TRANSPOSE(W(:,:)(1:2)) .ne. "ab")) call abortctr = ctr + 1end subroutinesubroutine test_packW(:, :)="def"if (any (pack(W(:,:)(2:3),mask=.true.) .ne. "ef")) call abortctr = ctr + 1end subroutinesubroutine test_unpacklogical, dimension(5,2) :: maskZ(:)="hij"mask = .true.if (any (unpack(Z(:)(2:2),mask,' ') .ne. "i")) call abortctr = ctr + 1end subroutinesubroutine test_pr31197TYPE dataCHARACTER(LEN=3) :: A = "xyz"END TYPETYPE(data), DIMENSION(10), TARGET :: Tif (any (TRANSPOSE(RESHAPE(T(:)%A(2:2),(/5,2/))) .ne. "y")) call abortctr = ctr + 1end subroutineEND
