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/] [value_1.f90] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do run }! { dg-options "-std=f2003 -fall-intrinsics" }! Tests the functionality of the patch for PR29642, which requested the! implementation of the F2003 VALUE attribute for gfortran.!! Contributed by Paul Thomas <pault@gcc.gnu.org>!module globaltype :: mytypereal(4) :: xcharacter(4) :: cend type mytypecontainssubroutine typhoo (dt)type(mytype), value :: dtif (dtne (dt, mytype (42.0, "lmno"))) call abort ()dt = mytype (21.0, "wxyz")if (dtne (dt, mytype (21.0, "wxyz"))) call abort ()end subroutine typhoological function dtne (a, b)type(mytype) :: a, bdtne = .FALSE.if ((a%x /= b%x) .or. (a%c /= b%c)) dtne = .TRUE.end function dtneend module globalprogram test_valueuse globalinteger(8) :: i = 42real(8) :: r = 42.0character(2) :: c = "ab"complex(8) :: z = (-99.0, 199.0)type(mytype) :: dt = mytype (42.0, "lmno")call foo (c)if (c /= "ab") call abort ()call bar (i)if (i /= 42) call abort ()call foobar (r)if (r /= 42.0) call abort ()call complex_foo (z)if (z /= (-99.0, 199.0)) call abort ()call typhoo (dt)if (dtne (dt, mytype (42.0, "lmno"))) call abort ()r = 20.0call foobar (r*2.0 + 2.0)containssubroutine foo (c)character(2), value :: cif (c /= "ab") call abort ()c = "cd"if (c /= "cd") call abort ()end subroutine foosubroutine bar (i)integer(8), value :: iif (i /= 42) call abort ()i = 99if (i /= 99) call abort ()end subroutine barsubroutine foobar (r)real(8), value :: rif (r /= 42.0) call abort ()r = 99.0if (r /= 99.0) call abort ()end subroutine foobarsubroutine complex_foo (z)COMPLEX(8), value :: zif (z /= (-99.0, 199.0)) call abort ()z = (77.0, -42.0)if (z /= (77.0, -42.0)) call abort ()end subroutine complex_fooend program test_value! { dg-final { cleanup-modules "global" } }
