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/dyn3d/gcm.F

    r999 r1036  
    11      PROGRAM gcm
    22
     3      use infotrac, only: iniadvtrac, nqtot, iadv
    34      IMPLICIT NONE
    45
     
    4849#include "tracstoke.h"
    4950#include "sponge.h"
    50 #include"advtrac.h"
     51!#include"advtrac.h"
    5152
    5253      INTEGER*4  iday ! jour julien
     
    5758      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    5859      real, dimension(ip1jmp1,llm) :: teta   ! temperature potentielle
    59       REAL q(ip1jmp1,llm,nqmx)               ! champs advectes
     60      REAL,allocatable :: q(:,:,:)           ! champs advectes
    6061      REAL ps(ip1jmp1)                       ! pression  au sol
    6162      REAL pext(ip1jmp1)                     ! pression  extensive
     
    8081c   tendances dynamiques
    8182      REAL dv(ip1jm,llm),du(ip1jmp1,llm)
    82       REAL dteta(ip1jmp1,llm),dq(ip1jmp1,llm,nqmx),dp(ip1jmp1)
     83      REAL dteta(ip1jmp1,llm),dp(ip1jmp1)
     84      REAL,ALLOCATABLE :: dq(:,:,:)
    8385
    8486c   tendances de la dissipation
     
    8890c   tendances physiques
    8991      REAL dvfi(ip1jm,llm),dufi(ip1jmp1,llm)
    90       REAL dhfi(ip1jmp1,llm),dqfi(ip1jmp1,llm,nqmx),dpfi(ip1jmp1)
     92      REAL dhfi(ip1jmp1,llm),dpfi(ip1jmp1)
     93      REAL,ALLOCATABLE :: dqfi(:,:,:)
    9194
    9295c   variables pour le fichier histoire
     
    9598      REAL tppn(iim),tpps(iim),tpn,tps
    9699c
    97 !      INTEGER iadv(nqmx) ! indice schema de transport pour le traceur iq
    98100
    99101      INTEGER itau,itaufinp1,iav
     
    124126      LOGICAL tracer
    125127          data tracer/.true./
    126       INTEGER nq
     128!      INTEGER nq
    127129
    128130C Calendrier
     
    142144
    143145c-----------------------------------------------------------------------
    144 c  Initialize tracers using iniadvtrac (Ehouarn, oct 2008)
    145146      CALL defrun_new( 99, .TRUE. )
    146147
    147       CALL iniadvtrac(nq,numvanle)
    148      
    149       CALL dynetat0("start.nc",nqmx,vcov,ucov,
     148! Initialize tracers
     149      call iniadvtrac(nqtot,numvanle)
     150! Allocation de la tableau q : champs advectes   
     151      allocate(q(ip1jmp1,llm,nqtot))
     152      allocate(dq(ip1jmp1,llm,nqtot))
     153      allocate(dqfi(ip1jmp1,llm,nqtot))
     154
     155      CALL dynetat0("start.nc",nqtot,vcov,ucov,
    150156     .              teta,q,masse,ps,phis,time_0)
    151157
     
    245251     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
    246252
    247       CALL dynredem0("restart.nc",day_ini,anne_ini,phis,nqmx)
     253      CALL dynredem0("restart.nc",day_ini,anne_ini,phis,nqtot)
    248254
    249255      ecripar = .TRUE.
     
    253259
    254260c   Quelques initialisations pour les traceurs
    255       call initial0(ijp1llm*nqmx,dq)
     261      dq(:,:,:)=0
    256262c     istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
    257263c     istphy=istdyn/iphysiq
     
    348354       IF( forward. OR . leapf )  THEN
    349355
    350         DO iq = 1, nqmx
     356        DO iq = 1, nqtot
    351357c
    352358         IF ( iadv(iq).EQ.1.OR.iadv(iq).EQ.2 )  THEN
    353359            CALL traceur( iq,iadv,q,teta,pk,w, pbaru, pbarv, dq )
    354360
    355          ELSE IF( iq.EQ. nqmx )   THEN
     361         ELSE IF( iq.EQ. nqtot )   THEN
    356362c
    357363            iapp_tracvl = 5
     
    361367c
    362368
    363             CALL vanleer(numvanle,iapp_tracvl,nqmx,q,pbaru,pbarv,
     369            CALL vanleer(numvanle,iapp_tracvl,nqtot,q,pbaru,pbarv,
    364370     *                      p, masse, dq,  iadv(1), teta, pk     )
    365371
     
    422428           ENDIF
    423429c
    424         CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
     430        CALL calfis( nqtot, lafin ,rdayvrai,rday_ecri,time  ,
    425431     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
    426432     $     du,dv,dteta,dq,w, dufi,dvfi,dhfi,dqfi,dpfi,tracer)
     
    429435c      ajout des tendances physiques:
    430436c      ------------------------------
    431           CALL addfi( nqmx, dtphys, leapf, forward   ,
     437          CALL addfi( nqtot, dtphys, leapf, forward   ,
    432438     $                  ucov, vcov, teta , q   ,ps , masse,
    433439     $                 dufi, dvfi, dhfi , dqfi ,dpfi  )
     
    540546c                 iav=0
    541547c              ENDIF
    542 c              CALL writedynav(histaveid, nqmx, itau,vcov ,
     548c              CALL writedynav(histaveid, nqtot, itau,vcov ,
    543549c    ,                          ucov,teta,pk,phi,q,masse,ps,phis)
    544550c           ENDIF
     
    556562     .  ' date=',REAL(itau)/REAL(day_step)
    557563       CALL dynredem1("restart.nc",REAL(itau)/REAL(day_step),
    558      .                vcov,ucov,teta,q,nqmx,masse,ps)
     564     .                vcov,ucov,teta,q,nqtot,masse,ps)
    559565     
    560566      CLOSE(99)
     
    625631                  iav=0
    626632               ENDIF
    627 c              CALL writedynav(histaveid, nqmx, itau,vcov ,
     633c              CALL writedynav(histaveid, nqtot, itau,vcov ,
    628634c    ,                          ucov,teta,pk,phi,q,masse,ps,phis)
    629635
     
    636642              CALL dynredem1("restart.nc",
    637643     .                REAL(itau)/REAL(day_step),
    638      .                vcov,ucov,teta,q,nqmx,masse,ps)
     644     .                vcov,ucov,teta,q,nqtot,masse,ps)
    639645     
    640646              forward = .TRUE.
Note: See TracChangeset for help on using the changeset viewer.