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/phymars/newcondens.F

    r890 r1036  
    66     $                  fluxsurf_sw,zls)
    77                                                   
     8       use tracer_mod, only: noms
    89       IMPLICIT NONE
    910c=======================================================================
     
    6162#include "paramet.h"
    6263#include "callkeys.h"
    63 #include "tracer.h"
     64!#include "tracer.h"
    6465
    6566c-----------------------------------------------------------------------
     
    195196         if (tracer) then
    196197c          Prepare Special treatment if one of the tracer is CO2 gas
    197            do iq=1,nqmx
     198           do iq=1,nq
    198199             if (noms(iq).eq."co2") then
    199200                ico2=iq
     
    238239      END DO
    239240         
    240       DO iq=1,nqmx         
     241      DO iq=1,nq
    241242      DO l=1,nlayer
    242243         DO ig=1,ngrid
     
    531532             zu(l)   =pu(ig,l)   +pdu( ig,l)  *ptimestep
    532533             zv(l)   =pv(ig,l)   +pdv( ig,l)  *ptimestep
    533             do iq=1,nqmx
     534            do iq=1,nq
    534535             zq(l,iq)=pq(ig,l,iq)+pdq(ig,l,iq)*ptimestep
    535536            enddo
     
    564565            zum(1) = 0 
    565566            zvm(1) = 0 
    566             do iq=1,nqmx
     567            do iq=1,nq
    567568              zqm(1,iq)=0. ! most tracer do not condense !
    568569            enddo
     
    577578            call vl1d(zu ,2.,masse,w,zum)
    578579            call vl1d(zv ,2.,masse,w,zvm)
    579             do iq=1,nqmx
     580            do iq=1,nq
    580581             do l=1,nlayer
    581582              zq1(l)=zq(l,iq)
     
    602603            zum(nlayer+1)= zu(nlayer)  ! should not be used, but...
    603604            zvm(nlayer+1)= zv(nlayer)  ! should not be used, but...
    604             do iq=1,nqmx
     605            do iq=1,nq
    605606             zqm(nlayer+1,iq)= zq(nlayer,iq)
    606607            enddo
     
    637638
    638639c           Tendencies on Q
    639             do iq=1,nqmx
     640            do iq=1,nq
    640641!              if (noms(iq).eq.'co2') then
    641642              if (iq.eq.ico2) then
     
    668669             if(pq(ig,1,ico2)+(pdq(ig,1,ico2)+pdqc(ig,1,ico2))*ptimestep
    669670     &       .lt.qco2min) then
    670                 do iq=1,nqmx
     671                do iq=1,nq
    671672                  zq(1,iq)=pq(ig,1,iq)
    672673     &                     +(pdq(ig,1,iq)+pdqc(ig,1,iq))*ptimestep
     
    675676                Sm(1)  = masse(1)
    676677                do l =2,nlayermx
    677                   do iq=1,nqmx
     678                  do iq=1,nq
    678679                     zq(l,iq)=pq(ig,l,iq)
    679680     &                        +(pdq(ig,l,iq)+pdqc(ig,l,iq))*ptimestep
     
    693694                 end do
    694695 99              continue
    695                  do iq=1,nqmx
     696                 do iq=1,nq
    696697                   qmix=zq(nmix,iq)
    697698     &             +(Smq(nmix-1,iq)-zq(nmix,iq)*Sm(nmix-1))/mixmas
Note: See TracChangeset for help on using the changeset viewer.