Ignore:
Timestamp:
Apr 3, 2014, 9:09:47 AM (11 years ago)
Author:
emillour
Message:

Generic model:
Major cleanup, in order to ease the use of LMDZ.GENERIC with (parallel) dynamics
in LMDZ.COMMON: (NB: this will break LMDZ.UNIVERSAL, which should be thrashed
in the near future)

  • Updated makegcm_* scripts (and makdim) and added the "-full" (to enforce full recomputation of the model) option
  • In dyn3d: converted control.h to module control_mod.F90 and converted iniadvtrac.F to module infotrac.F90
  • Added module mod_const_mpi.F90 in dyn3d (not used in serial mode)
  • Rearanged input/outputs routines everywhere to handle serial/MPI cases. physdem.F => phyredem.F90 , phyetat0.F => phyetat0.F90 ; all read/write routines for startfi files are gathered in module iostart.F90
  • added parallelism related routines init_phys_lmdz.F90, comgeomphy.F90, dimphy.F90, iniphysiq.F90, mod_grid_phy_lmdz.F90, mod_phys_lmdz_mpi_data.F90, mod_phys_lmdz_mpi_transfert.F90, mod_phys_lmdz_omp_data.F90, mod_phys_lmdz_omp_transfert.F90, mod_phys_lmdz_para.F90, mod_phys_lmdz_transfert_para.F90 in phymars and mod_const_mpi.F90 in dyn3d (for compliance with parallelism)
  • added created generic routines 'planetwide_maxval' and 'planetwide_minval', in module "planetwide_mod", that enable obtaining the max and min of a field over the whole planet. This should be further imroved with computation of means (possibly area weighed), etc.

EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/lect_start_archive.F

    r993 r1216  
    33     &     q,qsurf,surfith,nid)
    44
    5       USE surfdat_h
    6       USE comsoil_h
    7       USE tracer_h
     5!      USE surfdat_h
     6      USE comsoil_h, ONLY: nsoilmx, layer, mlayer, volcapa, inertiedat
     7      USE tracer_h, ONLY: igcm_co2_ice
     8      USE infotrac, ONLY: tname, nqtot
     9!      USE control_mod
    810
    911c=======================================================================
     
    2628#include "dimensions.h"
    2729#include "dimphys.h"
    28 #include "planete.h"
     30!#include "planete.h"
    2931#include "paramet.h"
    3032#include "comconst.h"
    3133#include "comvert.h"
    3234#include "comgeom2.h"
    33 #include "control.h"
    34 #include "logic.h"
     35!#include "control.h"
     36!#include "logic.h"
    3537#include "ener.h"
    3638#include "temps.h"
    3739#include "netcdf.inc"
    38 #include"advtrac.h"
     40!#include"advtrac.h"
    3941c=======================================================================
    4042c   Declarations
     
    7981      REAL vcov(iip1,jjm,llm),ucov(iip1,jjp1,llm) ! vents covariants
    8082      REAL h(iip1,jjp1,llm),ps(iip1,jjp1)
    81       REAL q(iip1,jjp1,llm,nqmx),qtot(iip1,jjp1,llm)
     83      REAL q(iip1,jjp1,llm,nqtot),qtot(iip1,jjp1,llm)
    8284
    8385c autre variables dynamique nouvelle grille
     
    9799      REAL co2ice(ngridmx) ! CO2 ice layer
    98100      REAL emis(ngridmx)
    99       REAL q2(ngridmx,nlayermx+1),qsurf(ngridmx,nqmx)
     101      REAL q2(ngridmx,nlayermx+1),qsurf(ngridmx,nqtot)
    100102c     REAL phisfi(ngridmx)
    101103
     
    119121      real co2iceS(iip1,jjp1)
    120122      real emisS(iip1,jjp1)
    121       REAL q2S(iip1,jjp1,llm+1),qsurfS(iip1,jjp1,nqmx)
     123      REAL q2S(iip1,jjp1,llm+1),qsurfS(iip1,jjp1,nqtot)
    122124
    123125      real ptotal, co2icetotal
     
    283285      allocate(psold(imold+1,jmold+1))
    284286      allocate(phisold(imold+1,jmold+1))
    285       allocate(qold(imold+1,jmold+1,lmold,nqmx))
     287      allocate(qold(imold+1,jmold+1,lmold,nqtot))
    286288      allocate(co2iceold(imold+1,jmold+1))
    287289      allocate(tsurfold(imold+1,jmold+1))
     
    296298      allocate(surfithold(imold+1,jmold+1))
    297299      allocate(mlayerold(nsoilold))
    298       allocate(qsurfold(imold+1,jmold+1,nqmx))
     300      allocate(qsurfold(imold+1,jmold+1,nqtot))
    299301
    300302      allocate(var (imold+1,jmold+1,llm))
     
    703705
    704706! Surface tracers:     
    705       do iq=1,nqmx
     707      do iq=1,nqtot
    706708        ! initialize all surface tracers to zero
    707709        call initial0((jmold+1)*(imold+1), qsurfold(1,1,iq))
     
    709711
    710712
    711 !      print*,'tnom=',tnom
     713!      print*,'tname=',tname
    712714!      print*,'nid',nid
    713715!      print*,'nvarid',nvarid
    714716!      stop
    715717
    716       DO iq=1,nqmx
    717           txt=trim(tnom(iq))//"_surf"
     718      DO iq=1,nqtot
     719          txt=trim(tname(iq))//"_surf"
    718720          if (txt.eq."h2o_vap") then
    719721            ! There is no surface tracer for h2o_vap;
     
    748750        ENDIF
    749751
    750       ENDDO ! of DO iq=1,nqmx
     752      ENDDO ! of DO iq=1,nqtot
    751753
    752754
     
    894896
    895897! Tracers:     
    896       do iq=1,nqmx
     898      do iq=1,nqtot
    897899         call initial0((jmold+1)*(imold+1)*lmold,qold(1,1,1,iq) )
    898900      enddo
    899901
    900       DO iq=1,nqmx
    901         txt=tnom(iq)
     902      DO iq=1,nqtot
     903        txt=tname(iq)
    902904        write(*,*)"lect_start_archive: loading tracer ",trim(txt)
    903905        ierr = NF_INQ_VARID (nid,txt,nvarid)
     
    925927        ENDIF
    926928
    927       ENDDO ! of DO iq=1,nqmx
     929      ENDDO ! of DO iq=1,nqtot
    928930
    929931
     
    12541256c     write(49,*) 'ucov',vcov
    12551257
    1256       if (nqmx .gt. 0) then
     1258      if (nqtot .gt. 0) then
    12571259c traceurs surface
    1258       do iq = 1, nqmx
     1260      do iq = 1, nqtot
    12591261            call interp_horiz(qsurfold(1,1,iq) ,qsurfs(1,1,iq),
    12601262     &                  imold,jmold,iim,jjm,1,
     
    12621264      enddo
    12631265
    1264       call gr_dyn_fi (nqmx,iim+1,jjm+1,ngridmx,qsurfs,qsurf)
     1266      call gr_dyn_fi (nqtot,iim+1,jjm+1,ngridmx,qsurfs,qsurf)
    12651267
    12661268c traceurs 3D
    1267       do  iq = 1, nqmx
     1269      do  iq = 1, nqtot
    12681270            call interp_vert(qold(1,1,1,iq),var,lmold,llm,
    12691271     &        apsold,bpsold,aps,bps,psold,(imold+1)*(jmold+1))
     
    13051307
    13061308c     Periodicite :
    1307       do  iq = 1, nqmx
     1309      do  iq = 1, nqtot
    13081310         do l=1, llm
    13091311            do j = 1, jjp1
     
    13161318! no need to transfer "co2ice" any more; it is in qsurf(igcm_co2_ice)
    13171319
    1318       endif !! if nqmx .ne. 0
     1320      endif !! if nqtot .ne. 0
    13191321
    13201322c-----------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.