SimulationTime.F90 Source File


This file depends on

sourcefile~~simulationtime.f90~~EfferentGraph sourcefile~simulationtime.f90 SimulationTime.F90 sourcefile~pflogger_stub.f90 pflogger_stub.F90 sourcefile~simulationtime.f90->sourcefile~pflogger_stub.f90 sourcefile~pfl_keywordenforcer.f90 PFL_KeywordEnforcer.F90 sourcefile~pflogger_stub.f90->sourcefile~pfl_keywordenforcer.f90 sourcefile~wraparray.f90 WrapArray.F90 sourcefile~pflogger_stub.f90->sourcefile~wraparray.f90

Files dependent on this one

sourcefile~~simulationtime.f90~~AfferentGraph sourcefile~simulationtime.f90 SimulationTime.F90 sourcefile~applicationsupport.f90 ApplicationSupport.F90 sourcefile~applicationsupport.f90->sourcefile~simulationtime.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~simulationtime.f90 sourcefile~maplframework.f90 MaplFramework.F90 sourcefile~maplframework.f90->sourcefile~simulationtime.f90 sourcefile~base.f90 Base.F90 sourcefile~base.f90->sourcefile~applicationsupport.f90 sourcefile~cap.f90 Cap.F90 sourcefile~cap.f90->sourcefile~applicationsupport.f90 sourcefile~comp_testing_driver.f90 Comp_Testing_Driver.F90 sourcefile~comp_testing_driver.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~extdatadrivermod.f90 ExtDataDriverMod.F90 sourcefile~extdatadrivermod.f90->sourcefile~applicationsupport.f90 sourcefile~mapl3g.f90 mapl3g.F90 sourcefile~mapl3g.f90->sourcefile~maplframework.f90 sourcefile~mapl3g.f90->sourcefile~cap.f90 sourcefile~mapl_bundleio_test.f90 mapl_bundleio_test.F90 sourcefile~mapl_bundleio_test.f90->sourcefile~applicationsupport.f90 sourcefile~mapl_cap.f90 MAPL_Cap.F90 sourcefile~mapl_cap.f90->sourcefile~applicationsupport.f90 sourcefile~mapl_cap.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~regrid_util.f90 Regrid_Util.F90 sourcefile~regrid_util.f90->sourcefile~applicationsupport.f90 sourcefile~cubedspheregeomspec_smod.f90 CubedSphereGeomSpec_smod.F90 sourcefile~cubedspheregeomspec_smod.f90->sourcefile~base.f90 sourcefile~equal_to.f90~2 equal_to.F90 sourcefile~equal_to.f90~2->sourcefile~base.f90 sourcefile~extdatadriver.f90 ExtDataDriver.F90 sourcefile~extdatadriver.f90->sourcefile~extdatadrivermod.f90 sourcefile~geos.f90 GEOS.F90 sourcefile~geos.f90->sourcefile~mapl3g.f90 sourcefile~make_decomposition.f90 make_decomposition.F90 sourcefile~make_decomposition.f90->sourcefile~base.f90 sourcefile~make_distribution.f90 make_distribution.F90 sourcefile~make_distribution.f90->sourcefile~base.f90 sourcefile~make_latlongeomspec_from_hconfig.f90 make_LatLonGeomSpec_from_hconfig.F90 sourcefile~make_latlongeomspec_from_hconfig.f90->sourcefile~base.f90 sourcefile~make_latlongeomspec_from_metadata.f90 make_LatLonGeomSpec_from_metadata.F90 sourcefile~make_latlongeomspec_from_metadata.f90->sourcefile~base.f90 sourcefile~mapl.f90 MAPL.F90 sourcefile~mapl.f90->sourcefile~base.f90 sourcefile~mapl_gridcomps.f90 MAPL_GridComps.F90 sourcefile~mapl_gridcomps.f90->sourcefile~mapl_cap.f90 sourcefile~mapl_nuopcwrappermod.f90 MAPL_NUOPCWrapperMod.F90 sourcefile~mapl_nuopcwrappermod.f90->sourcefile~base.f90 sourcefile~mapl_nuopcwrappermod.f90->sourcefile~mapl_cap.f90 sourcefile~supports_hconfig.f90~2 supports_hconfig.F90 sourcefile~supports_hconfig.f90~2->sourcefile~base.f90 sourcefile~supports_metadata.f90~2 supports_metadata.F90 sourcefile~supports_metadata.f90~2->sourcefile~base.f90 sourcefile~test_cfio_bundle.pf Test_CFIO_Bundle.pf sourcefile~test_cfio_bundle.pf->sourcefile~base.f90 sourcefile~tstqsat.f90 tstqsat.F90 sourcefile~tstqsat.f90->sourcefile~base.f90 sourcefile~ut_extdata.f90 ut_ExtData.F90 sourcefile~ut_extdata.f90->sourcefile~base.f90 sourcefile~utcfio_bundle.f90 utCFIO_Bundle.F90 sourcefile~utcfio_bundle.f90->sourcefile~base.f90

Source Code

! This module allows pFlogger to access the current simulation time in
! MAPL and thereby annotate log entries with the current simulation
! time.  To accomplish this, the module hold a (shallow) copy
! of the clock in CapGridComp.

module mapl_SimulationTime
   use pflogger, only: StringUnlimitedMap
   use ESMF
   implicit none
   private

   public :: set_reference_clock
   public :: fill_time_dict

   type(ESMF_Clock), save :: reference_clock

contains

   subroutine set_reference_clock(clock)
      type(ESMF_Clock), intent(in) :: clock
      reference_clock = clock
   end subroutine set_reference_clock

   subroutine fill_time_dict(dict)
      type (StringUnlimitedmap), intent(out) :: dict

      integer :: status
      type(ESMF_Time) :: time

      integer :: yy, mm, dd, h, m, s

      call ESMF_ClockValidate(reference_clock, rc=status)
      if (status /= 0) error stop "Must pass reference via set_reference_clock() before use."

      call ESMF_ClockGet(reference_clock, currTime=time, rc=status)
      if (status /= 0) error stop "could not get current time in SimulationTime.F90"

      call ESMF_TimeGet(time, yy=yy, mm=mm, dd=dd, h=h, m=m, s=s, rc=status)
      if (status /= 0) error stop "Failed to get data from ESMF_TimeGet()."

      call dict%insert('Y',yy)
      call dict%insert('M',mm)
      call dict%insert('D',dd)
      call dict%insert('HH',h)
      call dict%insert('MM',m)
      call dict%insert('SS',s)
      call dict%insert('MS',0)

   end subroutine Fill_Time_Dict

end module mapl_SimulationTime