inquiry_stopwatch Subroutine

public subroutine inquiry_stopwatch(default_clock, io_unit_print, io_unit_error, print_errors, abort_errors, print_form, cpu_avail, user_avail, sys_avail, wall_avail, cpu_prec, wall_prec, version, err)

Arguments

Type IntentOptional AttributesName
character(len=*), intent(out), optional dimension(:):: default_clock
integer, intent(out), optional :: io_unit_print
integer, intent(out), optional :: io_unit_error
logical, intent(out), optional :: print_errors
logical, intent(out), optional :: abort_errors
character(len=*), intent(out), optional :: print_form
logical, intent(out), optional :: cpu_avail
logical, intent(out), optional :: user_avail
logical, intent(out), optional :: sys_avail
logical, intent(out), optional :: wall_avail
real, intent(out), optional :: cpu_prec
real, intent(out), optional :: wall_prec
character(len=*), intent(out), optional :: version
integer, intent(out), optional :: err

Contents

Source Code


Variables

TypeVisibility AttributesNameInitial
real, public :: cpu
real, public :: cpu2
character(len=*), public, parameter:: ident_inquiry_stopwatch ='M_stopwatch::inquiry_stopwatch(3f): returns M_StopWatch options and system'
integer, public :: r
real, public :: sys
real, public :: user

Source Code

subroutine inquiry_stopwatch(default_clock,io_unit_print,io_unit_error, &
                   print_errors,abort_errors,print_form,cpu_avail,user_avail, &
                   sys_avail,wall_avail,cpu_prec,wall_prec,version,err)
!          -----------------
character(len=*),parameter :: ident_inquiry_stopwatch='M_stopwatch::inquiry_stopwatch(3f): returns M_StopWatch options and system'

!----------------------------------------------------
! This routine allows the user to determine the value of options set by
! option_stopwatch and certain implementation/system dependent values.
!----------------------------------------------------
!----------------------------------------------------
! Dummy arguments

character(len=*), optional, intent(out), dimension(:) :: default_clock
integer, optional, intent(out) :: io_unit_print, io_unit_error
logical, optional, intent(out) :: print_errors, abort_errors
character(len=*), optional, intent(out) :: print_form
logical, optional, intent(out) :: cpu_avail, user_avail, sys_avail, wall_avail
real, optional, intent(out) :: cpu_prec, wall_prec
character(len=*), optional, intent(out) :: version
integer, optional, intent(out) :: err

!----------------------------------------------------
!----------------------------------------------------
! Local variables:

integer :: r
real :: cpu,cpu2,user,sys

!----------------------------------------------------
!----------------------------------------------------
! Begin executable code

if (present(err)) then
   err=0
end if

! default_clocks

if (present(default_clock)) then
   if (.not. allocated(default_clocks)) then
      call option_stopwatch(default_clock=(/"cpu ","user","sys ","wall"/),err=err)
   end if

   default_clock = "    "
   default_clock(1:ubound(default_clocks,dim=1)) = default_clocks
end if

! i/o unit numbers

if (present(io_unit_error)) then
   io_unit_error = errunit
end if
if (present(io_unit_print)) then
   io_unit_print = iounit
end if

! behavior on errors

if (present(print_errors)) then
   print_errors = errprint
end if
if (present(abort_errors)) then
   abort_errors = errabort
end if

! format for printing time

if (present(print_form)) then
   print_form = default_form
end if

! available clocks

call system_cpu_time(cpu,user,sys)

if (present(cpu_avail)) then
   if (cpu < 0.0) then
      cpu_avail = .false.
   else
      cpu_avail = .true.
   end if
end if

if (present(user_avail)) then
   if (user < 0.0) then
      user_avail = .false.
   else
      user_avail = .true.
   end if
end if

if (present(sys_avail)) then
   if (sys < 0.0) then
      sys_avail = .false.
   else
      sys_avail = .true.
   end if
end if

if (present(wall_avail)) then
   call system_clock(count_rate=r)
   if (r == 0) then
      wall_avail = .false.
   else
      wall_avail = .true.
   end if
end if

! cpu precision, by calling system_cpu_time until the cpu clock changes

if (present(cpu_prec)) then
   if (cpu >= 0.0) then
      call system_cpu_time(cpu,user,sys)
      call system_cpu_time(cpu2,user,sys)
      do
         if (cpu2 /= cpu) then
            exit
         end if
         call system_cpu_time(cpu2,user,sys)
      end do
      cpu_prec = cpu2 - cpu
   else
      cpu_prec = 0.0
   end if
end if

! wall clock precision

if (present(wall_prec)) then
   call system_clock(count_rate=r)
   if (r == 0) then
      wall_prec = 0.0
   else
      wall_prec = 1.0/r
   end if
end if

! M_StopWatch version number

if (present(version)) then
   version = sw_version
end if

end subroutine inquiry_stopwatch