ApplicationSupport.F90 Source File


This file depends on

sourcefile~~applicationsupport.f90~~EfferentGraph sourcefile~applicationsupport.f90 ApplicationSupport.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~applicationsupport.f90->sourcefile~errorhandling.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~applicationsupport.f90->sourcefile~keywordenforcer.f90 sourcefile~mapl_profiler.f90 MAPL_Profiler.F90 sourcefile~applicationsupport.f90->sourcefile~mapl_profiler.f90 sourcefile~pflogger_stub.f90 pflogger_stub.F90 sourcefile~applicationsupport.f90->sourcefile~pflogger_stub.f90 sourcefile~simulationtime.f90 SimulationTime.F90 sourcefile~applicationsupport.f90->sourcefile~simulationtime.f90

Files dependent on this one

sourcefile~~applicationsupport.f90~~AfferentGraph sourcefile~applicationsupport.f90 ApplicationSupport.F90 sourcefile~base.f90 Base.F90 sourcefile~base.f90->sourcefile~applicationsupport.f90 sourcefile~cap.f90 Cap.F90 sourcefile~cap.f90->sourcefile~applicationsupport.f90 sourcefile~extdatadrivermod.f90 ExtDataDriverMod.F90 sourcefile~extdatadrivermod.f90->sourcefile~applicationsupport.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~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~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~mapl3g.f90 mapl3g.F90 sourcefile~mapl3g.f90->sourcefile~cap.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

#include "MAPL_ErrLog.h"

module MAPL_ApplicationSupport
 use MPI
 use mapl_ErrorHandlingMod
 use MAPL_KeywordEnforcerMod
 use pflogger, only: logging
 use pflogger, only: Logger
 use MAPL_Profiler, initialize_profiler =>initialize, finalize_profiler =>finalize

 implicit none
 private

 public MAPL_Initialize
 public MAPL_Finalize

 contains

   subroutine MAPL_Initialize(unusable,comm,logging_config,enable_global_timeprof, enable_global_memprof, rc)
      class (KeywordEnforcer), optional, intent(in) :: unusable
      integer, optional, intent(in) :: comm
      character(len=*), optional,intent(in) :: logging_config
      logical, optional, intent(in) :: enable_global_timeprof
      logical, optional, intent(in) :: enable_global_memprof
      integer, optional, intent(out) :: rc

      character(:), allocatable :: logging_configuration_file
      integer :: comm_world,status

      _UNUSED_DUMMY(unusable)

      call initialize_profiler(comm=comm_world, enable_global_timeprof=enable_global_timeprof, enable_global_memprof=enable_global_memprof, _RC)

      if (present(logging_config)) then
         logging_configuration_file=logging_config
      else
         logging_configuration_file=''
      end if
      if (present(comm)) then
         comm_world = comm
      else
         comm_world=MPI_COMM_WORLD
      end if

#ifdef BUILD_WITH_PFLOGGER
      call initialize_pflogger(comm=comm_world,logging_config=logging_configuration_file, _RC)
#endif

      _RETURN(_SUCCESS)
   end subroutine MAPL_Initialize

   subroutine MAPL_Finalize(unusable,comm,rc)
      class (KeywordEnforcer), optional, intent(in) :: unusable
      integer, optional, intent(in) :: comm
      integer, optional, intent(out) :: rc

      integer :: comm_world,status

      _UNUSED_DUMMY(unusable)

      if (present(comm)) then
         comm_world = comm
      else
         comm_world=MPI_COMM_WORLD
      end if

      call finalize_profiler(_RC)
      call finalize_pflogger()

      _RETURN(_SUCCESS)
      _UNUSED_DUMMY(unusable)
   end subroutine MAPL_Finalize

   subroutine finalize_pflogger()
      call logging%free()
   end subroutine finalize_pflogger

#ifdef BUILD_WITH_PFLOGGER
   subroutine initialize_pflogger(unusable,comm,logging_config,rc)
      use pflogger, only: pfl_initialize => initialize
      use pflogger, only: StreamHandler, FileHandler, HandlerVector
      use pflogger, only: MpiLock, MpiFormatter
      use pflogger, only: INFO, WARNING
      use PFL_Formatter, only: get_sim_time
      use mapl_SimulationTime, only: fill_time_dict

      use, intrinsic :: iso_fortran_env, only: OUTPUT_UNIT

      class (KeywordEnforcer), optional, intent(in) :: unusable
      integer, optional, intent(in) :: comm
      character(len=*), optional,intent(in) :: logging_config
      integer, optional, intent(out) :: rc

      type (HandlerVector) :: handlers
      type (StreamHandler) :: console
      type (FileHandler) :: file_handler
      integer :: level,rank,status
      character(:), allocatable :: logging_configuration_file
      integer :: comm_world
      type(Logger), pointer :: lgr

      _UNUSED_DUMMY(unusable)
      if (present(logging_config)) then
         logging_configuration_file=logging_config
      else
         logging_configuration_file=''
      end if
      if (present(comm)) then
         comm_world = comm
      else
         comm_world=MPI_COMM_WORLD
      end if

      call pfl_initialize()
      get_sim_time => fill_time_dict

      if (logging_configuration_file /= '') then
         call logging%load_file(logging_configuration_file)
      else

         call MPI_COMM_Rank(comm_world,rank,status)
         _VERIFY(status)
         console = StreamHandler(OUTPUT_UNIT)
         call console%set_level(INFO)
         call console%set_formatter(MpiFormatter(comm_world, fmt='%(short_name)a10~: %(message)a'))
         call handlers%push_back(console)

         file_handler = FileHandler('warnings_and_errors.log')
         call file_handler%set_level(WARNING)
         call file_handler%set_formatter(MpiFormatter(comm_world, fmt='pe=%(mpi_rank)i5.5~: %(short_name)a~: %(message)a'))
         call file_handler%set_lock(MpiLock(comm_world))
         call handlers%push_back(file_handler)

         if (rank == 0) then
            level = INFO
         else
            level = WARNING
         end if

         call logging%basic_config(level=level, handlers=handlers, rc=status)
         _VERIFY(status)

         if (rank == 0) then
            lgr => logging%get_logger('MAPL')
            call lgr%warning('No configure file specified for logging layer.  Using defaults.')
         end if

      end if
      _RETURN(_SUCCESS)

   end subroutine initialize_pflogger
#endif

end module MAPL_ApplicationSupport