Ignore:
Timestamp:
Sep 11, 2013, 2:34:44 PM (11 years ago)
Author:
emillour
Message:

Mars GCM: (a first step towards using parallel dynamics)

  • IMPORTANT CHANGE: Implemented dynamic tracers. It is no longer necessary to compile the model with the '-t #' option, number of tracers is simply read from tracer.def file (as before). Adapted makegcm_* scripts (and co.) accordingly. Technical aspects of the switch to dynamic tracers are:
    • advtrac.h (in dyn3d) removed and replaced by module infotrac.F
    • tracer.h (in phymars) removed and replaced by module tracer_mod.F90 (which contains nqmx, the number of tracers, etc. and can be used anywhere in the physics).
  • Included some side cleanups: removed unused files (in dyn3d) anldoppler2.F, anl_mcdstats.F and anl_stats-diag.F, and all the unecessary dimensions.* files in grid/dimension.
  • Checked that changes are clean and that GCM yields identical results (in debug mode) to previous svn version.

EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/aeronomars/concentrations.F

    r1035 r1036  
    1       SUBROUTINE concentrations(pplay,pt,pdt,pq,pdq,ptimestep)
     1      SUBROUTINE concentrations(nq,pplay,pt,pdt,pq,pdq,ptimestep)
    22                                             
     3      use tracer_mod, only: igcm_co2, igcm_co, igcm_o, igcm_o1d,
     4     &                      igcm_o2, igcm_o3, igcm_h, igcm_h2,
     5     &                      igcm_oh, igcm_ho2, igcm_n2, igcm_ar,
     6     &                      igcm_h2o_vap, igcm_n, igcm_no, igcm_no2,
     7     &                      igcm_n2d, igcm_co2plus, igcm_oplus,
     8     &                      igcm_o2plus, igcm_coplus, igcm_cplus,
     9     &                      igcm_nplus, igcm_noplus, igcm_n2plus,
     10     &                      igcm_hplus, igcm_hco2plus, mmol
    311      implicit none
    412
     
    2230#include "comdiurn.h"
    2331#include "chimiedata.h"
    24 #include "tracer.h"
     32!#include "tracer.h"
    2533#include "conc.h"
    2634
    2735!     input/output
    2836
    29       real pplay(ngridmx,nlayermx)
    30       real pt(ngridmx,nlayermx)
    31       real pdt(ngridmx,nlayermx)
    32       real pq(ngridmx,nlayermx,nqmx)
    33       real pdq(ngridmx,nlayermx,nqmx)
    34       real ptimestep
     37      integer,intent(in) :: nq ! number of tracers
     38      real,intent(in) :: pplay(ngridmx,nlayermx)
     39      real,intent(in) :: pt(ngridmx,nlayermx)
     40      real,intent(in) :: pdt(ngridmx,nlayermx)
     41      real,intent(in) :: pq(ngridmx,nlayermx,nq)
     42      real,intent(in) :: pdq(ngridmx,nlayermx,nq)
     43      real,intent(in) :: ptimestep
    3544
    3645!     local variables
    3746
    3847      integer       :: i, l, ig, iq
    39       integer, save :: nbq, niq(nqmx)
    40       real          :: ni(nqmx), ntot
    41       real          :: zq(ngridmx, nlayermx, nqmx)
     48      integer, save :: nbq
     49      integer,allocatable,save :: niq(:)
     50      real          :: ni(nq), ntot
     51      real          :: zq(ngridmx, nlayermx, nq)
    4252      real          :: zt(ngridmx, nlayermx)
    43       real, save    :: aki(nqmx)
    44       real, save    :: cpi(nqmx)
     53      real,allocatable,save    :: aki(:)
     54      real,allocatable,save    :: cpi(:)
    4555
    4656      logical, save :: firstcall = .true.
     
    4858      if (firstcall) then
    4959
     60         ! allocate local saved arrays:
     61         allocate(aki(nq))
     62         allocate(cpi(nq))
     63         allocate(niq(nq))
    5064!        find index of chemical tracers to use
    5165!        initialize thermal conductivity and specific heat coefficients
     
    217231         endif
    218232         
    219            
     233         ! tell the world about it:
     234         write(*,*) "concentrations: firstcall, nbq=",nbq
     235         write(*,*) "  niq(1:nbq)=",niq(1:nbq)
     236         write(*,*) "  aki(1:nbq)=",aki(1:nbq)
     237         write(*,*) "  cpi(1:nbq)=",cpi(1:nbq)
    220238
    221239         firstcall = .false.
Note: See TracChangeset for help on using the changeset viewer.