MAPL_LocStreamFactoryMod.F90 Source File


This file depends on

sourcefile~~mapl_locstreamfactorymod.f90~~EfferentGraph sourcefile~mapl_locstreamfactorymod.f90 MAPL_LocStreamFactoryMod.F90 sourcefile~constants.f90 Constants.F90 sourcefile~mapl_locstreamfactorymod.f90->sourcefile~constants.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~mapl_locstreamfactorymod.f90->sourcefile~errorhandling.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~mapl_locstreamfactorymod.f90->sourcefile~keywordenforcer.f90 sourcefile~internalconstants.f90 InternalConstants.F90 sourcefile~constants.f90->sourcefile~internalconstants.f90 sourcefile~mathconstants.f90 MathConstants.F90 sourcefile~constants.f90->sourcefile~mathconstants.f90 sourcefile~physicalconstants.f90 PhysicalConstants.F90 sourcefile~constants.f90->sourcefile~physicalconstants.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~physicalconstants.f90->sourcefile~mathconstants.f90

Files dependent on this one

sourcefile~~mapl_locstreamfactorymod.f90~~AfferentGraph sourcefile~mapl_locstreamfactorymod.f90 MAPL_LocStreamFactoryMod.F90 sourcefile~mapl_geosatmaskmod.f90 MAPL_GeosatMaskMod.F90 sourcefile~mapl_geosatmaskmod.f90->sourcefile~mapl_locstreamfactorymod.f90 sourcefile~mapl_stationsamplermod.f90 MAPL_StationSamplerMod.F90 sourcefile~mapl_stationsamplermod.f90->sourcefile~mapl_locstreamfactorymod.f90 sourcefile~mapl_trajectorymod.f90 MAPL_TrajectoryMod.F90 sourcefile~mapl_trajectorymod.f90->sourcefile~mapl_locstreamfactorymod.f90 sourcefile~mapl_trajectorymod_smod.f90 MAPL_TrajectoryMod_smod.F90 sourcefile~mapl_trajectorymod_smod.f90->sourcefile~mapl_locstreamfactorymod.f90 sourcefile~mapl_trajectorymod_smod.f90->sourcefile~mapl_trajectorymod.f90 sourcefile~mapl_geosatmaskmod_smod.f90 MAPL_GeosatMaskMod_smod.F90 sourcefile~mapl_geosatmaskmod_smod.f90->sourcefile~mapl_geosatmaskmod.f90 sourcefile~mapl_historycollection.f90 MAPL_HistoryCollection.F90 sourcefile~mapl_historycollection.f90->sourcefile~mapl_geosatmaskmod.f90 sourcefile~mapl_historycollection.f90->sourcefile~mapl_stationsamplermod.f90 sourcefile~mapl_historycollection.f90->sourcefile~mapl_trajectorymod.f90 sourcefile~mapl_historygridcomp.f90 MAPL_HistoryGridComp.F90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_geosatmaskmod.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_stationsamplermod.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_trajectorymod.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_historycollection.f90 sourcefile~extdatadrivergridcomp.f90 ExtDataDriverGridComp.F90 sourcefile~extdatadrivergridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~comp_testing_driver.f90 Comp_Testing_Driver.F90 sourcefile~comp_testing_driver.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~extdatadriver.f90 ExtDataDriver.F90 sourcefile~extdatadriver.f90->sourcefile~extdatadrivergridcomp.f90 sourcefile~extdatadrivermod.f90 ExtDataDriverMod.F90 sourcefile~extdatadrivermod.f90->sourcefile~extdatadrivergridcomp.f90 sourcefile~mapl_cap.f90 MAPL_Cap.F90 sourcefile~mapl_cap.f90->sourcefile~mapl_capgridcomp.f90

Source Code

#include "MAPL_ErrLog.h"
#include "unused_dummy.H"

module LocStreamFactoryMod

   use ESMF
   use MAPL_ErrorHandlingMod
   use MAPL_KeywordEnforcerMod
   use MAPL_Constants
   use, intrinsic :: iso_fortran_env, only: REAL32
   use, intrinsic :: iso_fortran_env, only: REAL64
   implicit none
   private

   public :: LocStreamFactory

   type :: LocStreamFactory
      private
      real(kind=REAL64), allocatable :: lons(:)
      real(kind=REAL64), allocatable :: lats(:)
      contains
        procedure :: create_locstream
        procedure :: create_locstream_on_proc
        procedure :: destroy_locstream
   end type

   interface LocStreamFactory
      module procedure LocStreamFactory_from_arrays
   end interface LocStreamFactory

   contains

      function LocStreamFactory_from_arrays(lons,lats,unusable,rc) result(factory)
         type(LocStreamFactory) :: factory
         real(kind=REAL64), intent(in) :: lons(:)
         real(kind=REAL64), intent(in) :: lats(:)
         class (KeywordEnforcer), optional, intent(in) :: unusable
         integer, optional, intent(out) :: rc
         integer :: status

         _UNUSED_DUMMY(unusable)

         _ASSERT(size(lons)==size(lats),"Lats and Lons for locstream must be same size")
         allocate(factory%lons,source=lons,stat=status)
         _VERIFY(status)
         allocate(factory%lats,source=lats,stat=status)
         _VERIFY(status)
         _RETURN(_SUCCESS)
      end function LocStreamFactory_from_arrays

      function create_locstream(this,unusable,grid,rc) result(locstream)
         type(ESMF_LocStream) :: locstream
         class (LocStreamFactory) :: this
         class (KeywordEnforcer), optional, intent(in) :: unusable
         type(ESMF_Grid), optional :: grid
         integer, optional, intent(out) :: rc

         type(ESMF_VM) :: vm
         integer :: my_pet,local_count,status
         real(kind=REAL64), allocatable :: tlons(:),tlats(:)

         _UNUSED_DUMMY(unusable)
         call ESMF_VMGetCurrent(vm,rc=status)
         _VERIFY(status)
         call ESMF_VMGet(vm,localPet=my_pet,rc=status)
         _VERIFY(status)
         if (my_pet==0) then
            local_count = size(this%lons)
            allocate(tlons(size(this%lons)),source=this%lons,stat=status)
            _VERIFY(status)
            allocate(tlats(size(this%lats)),source=this%lats,stat=status)
            _VERIFY(status)
            tlons=tlons*MAPL_PI_R8/180.0d0
            tlats=tlats*MAPL_PI_R8/180.0d0
         else
            local_count = 0
            allocate(tlons(0),stat=status)
            _VERIFY(status)
            allocate(tlats(0),stat=status)
            _VERIFY(status)
         end if

         locstream = ESMF_LocStreamCreate(localCount=local_count,coordSys=ESMF_COORDSYS_SPH_RAD,rc=status)
         _VERIFY(status)
         call ESMF_LocStreamAddKey(locstream,keyName="ESMF:Lat",farray=tlats,datacopyflag=ESMF_DATACOPY_VALUE, &
                 keyUnits="Radians", keyLongName="Latitude",rc=status)
         _VERIFY(status)
         call ESMF_LocStreamAddKey(locstream,keyName="ESMF:Lon",farray=tlons,datacopyflag=ESMF_DATACOPY_VALUE, &
                 keyUnits="Radians", keyLongName="Longitude",rc=status)
         _VERIFY(status)

         if (present(grid)) then
            locstream = ESMF_LocStreamCreate(locstream,background=grid,rc=status)
            _VERIFY(status)
         end if
         _RETURN(_SUCCESS)
      end function create_locstream

      function create_locstream_on_proc (this,unusable,grid,rc) result(locstream)
         type(ESMF_LocStream) :: locstream
         class (LocStreamFactory) :: this
         class (KeywordEnforcer), optional, intent(in) :: unusable
         type(ESMF_Grid), optional :: grid
         integer, optional, intent(out) :: rc

         integer :: local_count,status
         real(kind=REAL64), allocatable :: tlons(:),tlats(:)

         local_count = size(this%lons)
         allocate(tlons(size(this%lons)),source=this%lons,stat=status)
         _VERIFY(status)
         allocate(tlats(size(this%lats)),source=this%lats,stat=status)
         _VERIFY(status)

         tlons=tlons*MAPL_PI_R8/180.0d0
         tlats=tlats*MAPL_PI_R8/180.0d0

         locstream = ESMF_LocStreamCreate(localCount=local_count,coordSys=ESMF_COORDSYS_SPH_RAD,_RC)
         call ESMF_LocStreamAddKey(locstream,keyName="ESMF:Lat",farray=tlats,datacopyflag=ESMF_DATACOPY_VALUE, &
                 keyUnits="Radians", keyLongName="Latitude",_RC)
         call ESMF_LocStreamAddKey(locstream,keyName="ESMF:Lon",farray=tlons,datacopyflag=ESMF_DATACOPY_VALUE, &
                 keyUnits="Radians", keyLongName="Longitude",_RC)

         if (present(grid)) then
            locstream = ESMF_LocStreamCreate(locstream,background=grid,_RC)
         end if
         _RETURN(_SUCCESS)
       end function create_locstream_on_proc

      subroutine destroy_locstream(this,locstream,rc)
        class (LocStreamFactory) :: this
        type(ESMF_LocStream) :: locstream
        integer, optional, intent(out) :: rc
        integer :: status

        if (allocated(this%lons)) deallocate (this%lons)
        if (allocated(this%lats)) deallocate (this%lats)
        call ESMF_LocStreamDestroy (locstream,noGarbage=.true.,_RC)

        _RETURN(_SUCCESS)
      end subroutine destroy_locstream


end module LocStreamFactoryMod