OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc1/] [gcc/] [testsuite/] [gfortran.fortran-torture/] [execute/] [userop.f90] - Diff between revs 303 and 338

Only display areas with differences | Details | Blame | View Log

Rev 303 Rev 338
module uops
module uops
   implicit none
   implicit none
   interface operator (.foo.)
   interface operator (.foo.)
      module procedure myfoo
      module procedure myfoo
   end interface
   end interface
   interface operator (*)
   interface operator (*)
      module procedure boolmul
      module procedure boolmul
   end interface
   end interface
   interface assignment (=)
   interface assignment (=)
      module procedure int2bool
      module procedure int2bool
   end interface
   end interface
contains
contains
function myfoo (lhs, rhs)
function myfoo (lhs, rhs)
   implicit none
   implicit none
   integer myfoo
   integer myfoo
   integer, intent(in) :: lhs, rhs
   integer, intent(in) :: lhs, rhs
   myfoo = lhs + rhs
   myfoo = lhs + rhs
end function
end function
! This is deliberately different from integer multiplication
! This is deliberately different from integer multiplication
function boolmul (lhs, rhs)
function boolmul (lhs, rhs)
   implicit none
   implicit none
   logical boolmul
   logical boolmul
   logical, intent(IN) :: lhs, rhs
   logical, intent(IN) :: lhs, rhs
   boolmul = lhs .and. .not. rhs
   boolmul = lhs .and. .not. rhs
end function
end function
subroutine int2bool (lhs, rhs)
subroutine int2bool (lhs, rhs)
   implicit none
   implicit none
   logical, intent(out) :: lhs
   logical, intent(out) :: lhs
   integer, intent(in) :: rhs
   integer, intent(in) :: rhs
   lhs = rhs .ne. 0
   lhs = rhs .ne. 0
end subroutine
end subroutine
end module
end module
program me
program me
   use uops
   use uops
   implicit none
   implicit none
   integer i, j
   integer i, j
   logical b, c
   logical b, c
   b = .true.
   b = .true.
   c = .true.
   c = .true.
   if (b * c) call abort
   if (b * c) call abort
   c = .false.
   c = .false.
   if (.not. (b * c)) call abort
   if (.not. (b * c)) call abort
   if (c * b) call abort
   if (c * b) call abort
   b = .false.
   b = .false.
   if (b * c) call abort
   if (b * c) call abort
   i = 0
   i = 0
   b = i
   b = i
   if (b) call abort
   if (b) call abort
   i = 2
   i = 2
   b = i
   b = i
   if (.not. b) call abort
   if (.not. b) call abort
   j = 3
   j = 3
   if ((i .foo. j) .ne. 5) call abort
   if ((i .foo. j) .ne. 5) call abort
end program
end program
 
 

powered by: WebSVN 2.1.0

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