MAPL_Sleep.F90 Source File


Files dependent on this one

sourcefile~~mapl_sleep.f90~~AfferentGraph sourcefile~mapl_sleep.f90 MAPL_Sleep.F90 sourcefile~maplshared.f90 MaplShared.F90 sourcefile~maplshared.f90->sourcefile~mapl_sleep.f90 sourcefile~componentdriver.f90 ComponentDriver.F90 sourcefile~componentdriver.f90->sourcefile~maplshared.f90 sourcefile~extdataroot_gridcomp.f90 ExtDataRoot_GridComp.F90 sourcefile~extdataroot_gridcomp.f90->sourcefile~maplshared.f90 sourcefile~fieldunits.f90 FieldUnits.F90 sourcefile~fieldunits.f90->sourcefile~maplshared.f90 sourcefile~mapl_generic.f90 MAPL_Generic.F90 sourcefile~mapl_generic.f90->sourcefile~maplshared.f90 sourcefile~capdriver.f90 CapDriver.F90 sourcefile~capdriver.f90->sourcefile~extdataroot_gridcomp.f90 sourcefile~comp_testing_driver.f90 Comp_Testing_Driver.F90 sourcefile~comp_testing_driver.f90->sourcefile~mapl_generic.f90 sourcefile~componentdriverptrvector.f90 ComponentDriverPtrVector.F90 sourcefile~componentdriverptrvector.f90->sourcefile~componentdriver.f90 sourcefile~componentdrivervector.f90 ComponentDriverVector.F90 sourcefile~componentdrivervector.f90->sourcefile~componentdriver.f90 sourcefile~couplermetacomponent.f90 CouplerMetaComponent.F90 sourcefile~couplermetacomponent.f90->sourcefile~componentdriver.f90 sourcefile~extdatadriver.f90 ExtDataDriver.F90 sourcefile~extdatadriver.f90->sourcefile~extdataroot_gridcomp.f90 sourcefile~extdatadrivermod.f90 ExtDataDriverMod.F90 sourcefile~extdatadrivermod.f90->sourcefile~extdataroot_gridcomp.f90 sourcefile~extdatagridcompmod.f90 ExtDataGridCompMod.F90 sourcefile~extdatagridcompmod.f90->sourcefile~mapl_generic.f90 sourcefile~extdatagridcompng.f90 ExtDataGridCompNG.F90 sourcefile~extdatagridcompng.f90->sourcefile~mapl_generic.f90 sourcefile~generic3g.f90 Generic3g.F90 sourcefile~generic3g.f90->sourcefile~componentdriver.f90 sourcefile~griddedcomponentdriver.f90 GriddedComponentDriver.F90 sourcefile~griddedcomponentdriver.f90->sourcefile~componentdriver.f90 sourcefile~mapl.f90 MAPL.F90 sourcefile~mapl.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_geosatmaskmod.f90 MAPL_GeosatMaskMod.F90 sourcefile~mapl_geosatmaskmod.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_historycollection.f90 MAPL_HistoryCollection.F90 sourcefile~mapl_historycollection.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_historygridcomp.f90 MAPL_HistoryGridComp.F90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_orbgridcompmod.f90 MAPL_OrbGridCompMod.F90 sourcefile~mapl_orbgridcompmod.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_stationsamplermod.f90 MAPL_StationSamplerMod.F90 sourcefile~mapl_stationsamplermod.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_trajectorymod.f90 MAPL_TrajectoryMod.F90 sourcefile~mapl_trajectorymod.f90->sourcefile~mapl_generic.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~outermetacomponent.f90->sourcefile~componentdriver.f90 sourcefile~stateitemextension.f90 StateItemExtension.F90 sourcefile~stateitemextension.f90->sourcefile~componentdriver.f90 sourcefile~stateregistry.f90 StateRegistry.F90 sourcefile~stateregistry.f90->sourcefile~componentdriver.f90 sourcefile~test_modelverticalgrid.pf Test_ModelVerticalGrid.pf sourcefile~test_modelverticalgrid.pf->sourcefile~componentdriver.f90

Source Code

module MAPL_SleepMod

use, intrinsic :: iso_fortran_env, only: REAL64,INT64
implicit none
private

public MAPL_Sleep

contains

! wait time in seconds
subroutine MAPL_Sleep(wait_time)
real, intent(in) :: wait_time

integer(kind=INT64) :: s1,s2,count_max,count_rate,delta
real(kind=REAL64) :: seconds_elapsed

call system_clock(count=s1,count_rate=count_rate,count_max=count_max)

do 

   call system_clock(count=s2)
   delta = s2-s1
   if (delta < 0) delta= s2 + (count_max - mod(s1,count_max))
   seconds_elapsed = dble(delta)/dble(count_rate)
   if (seconds_elapsed > wait_time) exit

enddo

end subroutine
end module MAPL_SleepMod