#define IF_NOTOK_RETURN(action) if (status/=0) then; write (gol,'("in ",a)') rname; call goErr; action; return; end if #define IF_ERROR_RETURN(action) if (status> 0) then; write (gol,'("in ",a)') rname; call goErr; action; return; end if ! #include "tm5.inc" ! !----------------------------------------------------------------------------- ! TM5 ! !----------------------------------------------------------------------------- !BOP ! ! !MODULE: M7_DATA ! ! !DESCRIPTION: holds m7 data and methods to allocate (INIT_M7_DATA), and ! deallocate them (FREE_M7_DATA). !\\ !\\ ! !INTERFACE: ! MODULE M7_DATA ! ! !USES: ! USE GO, ONLY : gol, goErr, goPr USE mo_aero_m7, ONLY : nmod, nsol USE tm5_distgrid, ONLY : Get_DistGrid, dgrid USE chem_param, ONLY : d3_data USE dims, ONLY : im,jm,lm,nregions IMPLICIT NONE ! ! !PUBLIC DATA MEMBERS: ! INTEGER, PARAMETER :: nm7procs = 66 TYPE(d3_data), DIMENSION(nregions, nmod), TARGET :: rw_mode TYPE(d3_data), DIMENSION(nregions, nmod), TARGET :: dens_mode TYPE(d3_data), DIMENSION(nregions, nsol), TARGET :: h2o_mode, rwd_mode ! ! !REVISION HISTORY: ! 20 Jun 2012 - P. Le Sager - updated to Narcissa/Achim version : i.e. ! added rwd_mode ! - protex; all public by default ! - adapted for lon-lat MPI domain decomposition ! ! !REMARKS: ! !EOP !------------------------------------------------------------------------ CONTAINS !-------------------------------------------------------------------------- ! TM5 ! !-------------------------------------------------------------------------- !BOP ! ! !IROUTINE: INIT_M7_DATA ! ! !DESCRIPTION: !\\ !\\ ! !INTERFACE: ! SUBROUTINE INIT_M7_DATA( status ) ! ! !OUTPUT PARAMETERS: ! INTEGER, INTENT(out) :: status ! ! !REVISION HISTORY: ! 20 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition ! !EOP !------------------------------------------------------------------------ !BOC INTEGER :: region, imode, i1, i2, j1, j2, lmr INTEGER :: l_halo l_halo = 1 DO region=1,nregions call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 ) lmr = lm(region) DO imode=1,nmod ALLOCATE(rw_mode (region,imode)%d3(i1:i2, j1:j2, lmr)) ALLOCATE(dens_mode(region,imode)%d3(i1:i2, j1:j2, lmr)) rw_mode (region,imode)%d3 = 0.1e-6 ! m dens_mode(region,imode)%d3 = 1800.0 ! kg/m3 ENDDO DO imode=1,nsol ALLOCATE(rwd_mode(region,imode)%d3(i1:i2, j1:j2, lmr)) ! added halo for h2o_mode, needed for station output in USER_OUTPUT_AEROCOM h2o_mode(region,imode)%halo = l_halo ALLOCATE(h2o_mode(region,imode)%d3(i1-l_halo:i2+l_halo, j1-l_halo:j2+l_halo, lmr)) h2o_mode(region,imode)%d3 = 0.0 rwd_mode(region,imode)%d3 = 0.1e-6 ENDDO ENDDO ! ok status = 0 END SUBROUTINE INIT_M7_DATA !EOC !-------------------------------------------------------------------------- ! TM5 ! !-------------------------------------------------------------------------- !BOP ! ! !IROUTINE: FREE_M7_DATA ! ! !DESCRIPTION: !\\ !\\ ! !INTERFACE: ! SUBROUTINE FREE_M7_DATA ! ! !REVISION HISTORY: ! 20 Jun 2012 - P. Le Sager - no reference to MPI anymore ! !EOP !------------------------------------------------------------------------ !BOC INTEGER :: region, imode DO region=1,nregions DO imode=1,nmod DEALLOCATE(rw_mode(region,imode)%d3) DEALLOCATE(dens_mode(region,imode)%d3) ENDDO DO imode=1,nsol DEALLOCATE(h2o_mode(region,imode)%d3) DEALLOCATE(rwd_mode(region,imode)%d3) ENDDO ENDDO END SUBROUTINE FREE_M7_DATA !EOC END MODULE M7_DATA