#define TRACEBACK write (gol,'("in ",a," (",a,i6,")")') rname, __FILE__, __LINE__ ; call goErr #define IF_NOTOK_RETURN(action) if (status/=0) then; TRACEBACK; action; return; end if #define IF_ERROR_RETURN(action) if (status> 0) then; TRACEBACK; action; return; end if ! #include "tm5.inc" ! !------------------------------------------------------------------------------ ! TM5 ! !------------------------------------------------------------------------------ !BOP ! ! !MODULE: SOURCES_SINKS ! ! !DESCRIPTION: Perform all calculations needed for CO2 transport simulation ! in TM5: this is mainly emissions, process updates after ! changes in meteo,... ! !FD: all emission are converted to kg X (fmw) /month exceptions are mentioned in the code ! !\\ !\\ ! !INTERFACE: ! MODULE SOURCES_SINKS ! ! !USES: ! use GO, only : gol, goErr, goPr, goBug, goLabel implicit none private ! ! !PUBLIC MEMBER FUNCTIONS: ! PUBLIC :: SOURCES_SINKS_INIT, SOURCES_SINKS_DONE ! Init and Done methods PUBLIC :: SS_MONTHLY_UPDATE ! monthly initialization (photolysis,..) PUBLIC :: SS_AFTER_READ_METEO_UPDATE ! Update SS after met fields are updated. Called from modelIntegration/Proces_update PUBLIC :: SOURCES_SINKS_APPLY ! apply SS ! ! !PRIVATE DATA MEMBERS: ! character(len=*), parameter :: mname = 'sources_sinks' ! ! !REVISION HISTORY: ! 19 Mar 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition ! 14 May 2014 - T. van Noije- made stripped version for CO2 version ! ! !REMARKS: ! !EOP !------------------------------------------------------------------------------ contains !------------------------------------------------------------------------------ ! TM5 ! !------------------------------------------------------------------------------ !BOP ! ! !IROUTINE: SOURCES_SINKS_INIT ! ! !DESCRIPTION: switch ON required meteo; init emissions !\\ !\\ ! !INTERFACE: ! SUBROUTINE SOURCES_SINKS_INIT( status ) ! ! !USES: ! ! use meteo, only : Set ! use meteodata, only : temper_dat, humid_dat, oro_dat, gph_dat ! use Meteodata, only : cp_dat, lsp_dat ! use Meteodata, only : cvl_dat, cvh_dat, tv_dat ! use Meteodata, only : ci_dat, sd_dat, swvl1_dat ! use Meteodata, only : t2m_dat, d2m_dat ! use Meteodata, only : u10m_dat, v10m_dat, lsmask_dat, ci_dat ! use Meteodata, only : ssr_dat, sshf_dat, slhf_dat, ewss_dat, nsss_dat ! use Meteodata, only : u10m_dat, v10m_dat, src_dat, albedo_dat, nveg #ifndef without_emission use emission, only : Emission_Init #endif use GO, only : TrcFile, Init, Done, ReadRc use global_data, only : rcfile use dims, only : iglbsfc, nregions ! ! !OUTPUT PARAMETERS: ! integer, intent(out) :: status ! ! !REVISION HISTORY: ! ! !REMARKS: ! !EOP !------------------------------------------------------------------------------ !BOC integer, parameter :: kr=31 ! standard unit to read auxiliary files character(len=*), parameter :: rname = mname//'/Sources_Sinks_Init' type(TrcFile) :: rcF integer :: region, iveg ! --- begin --------------------------------- !-------------------------------------------------- ! ** select meteo (cases not accounted for in the **_init procedures) !-------------------------------------------------- ! do region = 1, nregions ! #ifndef without_emission ! call Set( temper_dat(region), status, used=.true. ) ! call Set( humid_dat(region), status, used=.true. ) ! call Set( oro_dat(region), status, used=.true. ) ! call Set( gph_dat(region), status, used=.true. ) ! #endif ! ! other ! call Set( cvl_dat(region), status, used=.true. ) ! call Set( cvh_dat(region), status, used=.true. ) ! do iveg=1,nveg ! call Set( tv_dat(region,nveg), status, used=.true. ) ! enddo ! call Set( ci_dat(region), status, used=.true. ) ! call Set( sd_dat(region), status, used=.true. ) ! call Set( swvl1_dat(region), status, used=.true. ) ! call Set( t2m_dat(region), status, used=.true. ) ! call Set( d2m_dat(region), status, used=.true. ) ! call Set( ssr_dat(region), status, used=.true. ) ! call Set( sshf_dat(region), status, used=.true. ) ! call Set( slhf_dat(region), status, used=.true. ) ! call Set( ewss_dat(region), status, used=.true. ) ! call Set( nsss_dat(region), status, used=.true. ) ! call Set( u10m_dat(region), status, used=.true. ) ! call Set( v10m_dat(region), status, used=.true. ) ! call Set( src_dat(region), status, used=.true. ) ! call Set( albedo_dat(region), status, used=.true. ) ! enddo !-------------------------------------------------- ! ** Emissions !-------------------------------------------------- #ifndef without_emission call Emission_Init( status ) IF_NOTOK_RETURN(status=1) #endif /* EMISSIONS */ !-------------------------------------------------- ! ** Done !-------------------------------------------------- status = 0 END SUBROUTINE SOURCES_SINKS_INIT !EOC !------------------------------------------------------------------------------ ! TM5 ! !------------------------------------------------------------------------------ !BOP ! ! !IROUTINE: SOURCES_SINKS_DONE ! ! !DESCRIPTION: !\\ !\\ ! !INTERFACE: ! SUBROUTINE SOURCES_SINKS_DONE( status ) ! ! !USES: ! #ifndef without_emission use emission, only : Emission_Done #endif ! ! !OUTPUT PARAMETERS: ! integer, intent(out) :: status ! ! !REVISION HISTORY: ! !EOP !------------------------------------------------------------------------------ !BOC character(len=*), parameter :: rname = mname//'/Sources_Sinks_Done' ! --- begin -------------------------------- #ifndef without_emission call Emission_Done( status ) IF_NOTOK_RETURN(status=1) #endif status = 0 END SUBROUTINE SOURCES_SINKS_DONE !EOC !------------------------------------------------------------------------------ ! TM5 ! !------------------------------------------------------------------------------ !BOP ! ! !IROUTINE: SS_MONTHLY_UPDATE ! ! !DESCRIPTION: monthly (re)initialisation of sources/sinks !\\ !\\ ! !INTERFACE: ! SUBROUTINE SS_MONTHLY_UPDATE( status ) ! ! !USES: ! ! use GO, only : TrcFile, Init, Done, ReadRc ! use dims, only : nregions use dims, only : newmonth, idate, mlen, newsrun use dims, only : sec_day, sec_month, sec_year ! use dims, only : okdebug ! use dims, only : istart ! use dims, only : region_name ! use global_data, only : rcfile use datetime, only : calc_sm #ifndef without_emission use emission, only : declare_emission #endif ! ! !OUTPUT PARAMETERS: ! integer, intent(out) :: status ! ! !REVISION HISTORY: ! 19 Mar 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition ! ! !REMARKS: ! (1) routine is called at start and at beginning of each month ! !EOP !------------------------------------------------------------------------------ !BOC character(len=*), parameter :: rname = mname//'/ss_monthly_update' integer, parameter :: kr=31 ! standard unit to read auxiliary files ! --- begin ------------------------------------ ! calculate some conversion factors related to time... call calc_sm( mlen, sec_day, sec_month, sec_year ) ! Read monthly emissions #ifndef without_emission call declare_emission( status ) IF_NOTOK_RETURN(status=1) #endif status = 0 END SUBROUTINE SS_MONTHLY_UPDATE !EOC !------------------------------------------------------------------------------ ! TM5 ! !------------------------------------------------------------------------------ !BOP ! ! !IROUTINE: SS_AFTER_READ_METEO_UPDATE ! ! !DESCRIPTION: subroutine that is called after reading new met fields (clouds, ! surface winds, etc.). ! In this routine, 'chemistry' fields that depend on these ! data are calculated. Called from modelIntegration/Proces_update. !\\ !\\ ! !INTERFACE: ! SUBROUTINE SS_AFTER_READ_METEO_UPDATE( status ) ! ! !USES: ! use dims, only : nregions, sec_month use tm5_distgrid, only : dgrid, Get_DistGrid ! ! !OUTPUT PARAMETERS: ! integer, intent(out) :: status ! ! !REVISION HISTORY: ! 19 Mar 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition ! ! !REMARKS: ! !EOP !------------------------------------------------------------------------------ !BOC character(len=*), parameter :: rname = 'ss_after_read_meteo_update' integer :: region, i1, j1 ! --- begin ------------------------------------ call goLabel() #ifndef without_emission ! TvN: nothing is done here in CO2 version #endif /* EMISSIONS */ ! ok call goLabel() status = 0 END SUBROUTINE SS_AFTER_READ_METEO_UPDATE !EOC !------------------------------------------------------------------------------ ! TM5 ! !------------------------------------------------------------------------------ !BOP ! ! !IROUTINE: SOURCES_SINKS_APPLY ! ! !DESCRIPTION: this subroutine changes the tracer mass and its ! slopes by chemical sources. !\\ !\\ ! !INTERFACE: ! SUBROUTINE SOURCES_SINKS_APPLY( region, tr, status ) ! ! !USES: ! use GO, only : TDate #ifndef without_emission use emission, only: emission_apply #endif ! ! !INPUT PARAMETERS: ! integer, intent(in) :: region type(TDate) :: tr(2) ! ! !OUTPUT PARAMETERS: ! integer, intent(out) :: status ! ! !REVISION HISTORY: ! ! !REMARKS: ! - called each time step, during "source" step, by modelIntegration/do_steps ! !EOP !------------------------------------------------------------------------------ !BOC character(len=*), parameter :: rname = mname//'/Sources_sinks_apply' ! --- begin ---------------------------------- #ifndef without_emission call emission_apply( region, status ) IF_NOTOK_RETURN(status=1) #endif ! ok status = 0 END SUBROUTINE SOURCES_SINKS_APPLY !EOC END MODULE SOURCES_SINKS