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/initracer.F

    r1005 r1036  
    1       SUBROUTINE initracer(qsurf,co2ice)
    2 
     1      SUBROUTINE initracer(ngrid,nq,qsurf,co2ice)
     2
     3       use infotrac, only: tnom
     4       use tracer_mod
    35       IMPLICIT NONE
    46c=======================================================================
     
    1113c
    1214c   Test of dimension :
    13 c   Initialize COMMON tracer in tracer.h, using tracer names provided
    14 c   by the dynamics in "advtrac.h"
     15c   Initialize tracer related data in tracer_mod, using tracer names provided
     16c   by the dynamics in "infotrac"
    1517c
    1618c
     
    2628#include "comcstfi.h"
    2729#include "callkeys.h"
    28 #include "tracer.h"
    29 #include "advtrac.h"
     30!#include "tracer.h"
     31!#include "advtrac.h"
    3032#include "comgeomfi.h"
    3133
    3234#include "surfdat.h"
    3335
    34       real qsurf(ngridmx,nqmx)       ! tracer on surface (e.g.  kg.m-2)
    35       real co2ice(ngridmx)           ! co2 ice mass on surface (e.g.  kg.m-2)
     36      integer,intent(in) :: ngrid ! number of atmospheric columns
     37      integer,intent(in) :: nq ! number of tracers
     38      real,intent(out) :: qsurf(ngrid,nq) ! tracer on surface (e.g.  kg.m-2)
     39      real,intent(out) :: co2ice(ngrid) ! co2 ice mass on surface (e.g.  kg.m-2)
     40
    3641      integer iq,ig,count
    3742      real r0_lift , reff_lift, nueff_lift
     
    4348
    4449c-----------------------------------------------------------------------
    45 c  radius(nqmx)      ! aerosol particle radius (m)
    46 c  rho_q(nqmx)       ! tracer densities (kg.m-3)
    47 c  alpha_lift(nqmx)  ! saltation vertical flux/horiz flux ratio (m-1)
    48 c  alpha_devil(nqmx) ! lifting coeeficient by dust devil
     50c  radius(nq)      ! aerosol particle radius (m)
     51c  rho_q(nq)       ! tracer densities (kg.m-3)
     52c  alpha_lift(nq)  ! saltation vertical flux/horiz flux ratio (m-1)
     53c  alpha_devil(nq) ! lifting coeeficient by dust devil
    4954c  rho_dust          ! Mars dust density
    5055c  rho_ice           ! Water ice density
     
    5560c-----------------------------------------------------------------------
    5661
     62! Initialization: allocate arrays in tracer_mod
     63      allocate(noms(nq))
     64      allocate(mmol(nq))
     65      allocate(radius(nq))
     66      allocate(rho_q(nq))
     67      allocate(alpha_lift(nq))
     68      allocate(alpha_devil(nq))
     69      allocate(dryness(ngridmx))
     70      allocate(igcm_dustbin(nq))
     71
    5772! Initialization: get tracer names from the dynamics and check if we are
    5873!                 using 'old' tracer convention ('q01',q02',...)
     
    6075      ! check if tracers have 'old' names
    6176      count=0
    62       do iq=1,nqmx
     77      do iq=1,nq
    6378        txt=" "
    6479        write(txt,'(a1,i2.2)') 'q',iq
     
    6681          count=count+1
    6782        endif
    68       enddo ! of do iq=1,nqmx
     83      enddo ! of do iq=1,nq
    6984     
    70       if (count.eq.nqmx) then
     85      if (count.eq.nq) then
    7186        write(*,*) "initracer: tracers seem to follow old naming ",
    7287     &             "convention (q01,q02,...)"
     
    7691
    7792      ! copy tracer names from dynamics
    78       do iq=1,nqmx
     93      do iq=1,nq
    7994        noms(iq)=tnom(iq)
    8095      enddo
     
    86101! Identify tracers by their names: (and set corresponding values of mmol)
    87102      ! 0. initialize tracer indexes to zero:
    88       do iq=1,nqmx
    89         igcm_dustbin(iq)=0
    90       enddo
     103      igcm_dustbin(1:nq)=0
     104
    91105      igcm_dust_mass=0
    92106      igcm_dust_number=0
     
    130144      count=0
    131145      if (dustbin.gt.0) then
    132         do iq=1,nqmx
     146        do iq=1,nq
    133147          txt=" "
    134148          write(txt,'(a4,i2.2)')'dust',count+1
     
    138152            mmol(iq)=100.
    139153          endif
    140         enddo !do iq=1,nqmx
     154        enddo !do iq=1,nq
    141155      endif ! of if (dustbin.gt.0)
    142156      if (doubleq) then
    143         do iq=1,nqmx
     157        do iq=1,nq
    144158          if (noms(iq).eq."dust_mass") then
    145159            igcm_dust_mass=iq
     
    153167      endif ! of if (doubleq)
    154168      if (microphys) then
    155         do iq=1,nqmx
     169        do iq=1,nq
    156170          if (noms(iq).eq."ccn_mass") then
    157171            igcm_ccn_mass=iq
     
    165179      endif ! of if (microphys)
    166180      if (submicron) then
    167         do iq=1,nqmx
     181        do iq=1,nq
    168182          if (noms(iq).eq."dust_submicron") then
    169183            igcm_dust_submicron=iq
     
    174188      endif ! of if (submicron)
    175189      ! 2. find chemistry and water tracers
    176       do iq=1,nqmx
     190      do iq=1,nq
    177191        if (noms(iq).eq."co2") then
    178192          igcm_co2=iq
     
    337351        endif
    338352
    339       enddo ! of do iq=1,nqmx
     353      enddo ! of do iq=1,nq
    340354     
    341355      ! check that we identified all tracers:
    342       if (count.ne.nqmx) then
     356      if (count.ne.nq) then
    343357        write(*,*) "initracer: found only ",count," tracers"
    344         write(*,*) "               expected ",nqmx
     358        write(*,*) "               expected ",nq
    345359        do iq=1,count
    346360          write(*,*)'      ',iq,' ',trim(noms(iq))
     
    349363      else
    350364        write(*,*) "initracer: found all expected tracers, namely:"
    351         do iq=1,nqmx
     365        do iq=1,nq
    352366          write(*,*)'      ',iq,' ',trim(noms(iq))
    353367        enddo
     
    365379       ! as qsurf(i_h2o_vap) & as qsurf(i_h2o_ice), so to be clean:
    366380       if (igcm_h2o_vap.ne.0) then
    367          qsurf(1:ngridmx,igcm_h2o_vap)=0
     381         qsurf(1:ngrid,igcm_h2o_vap)=0
    368382       endif
    369383      endif
    370384
    371385c------------------------------------------------------------
    372 c     Initialize tracers .... (in tracer.h)
     386c     Initialize tracers .... (in tracer_mod)
    373387c------------------------------------------------------------
    374388      ! start by setting everything to (default) zero
    375       rho_q(1:nqmx)=0     ! tracer density (kg.m-3)
    376       radius(1:nqmx)=0.   ! tracer particle radius (m)
    377       alpha_lift(1:nqmx) =0.  ! tracer saltation vertical flux/horiz flux ratio (m-1)
    378       alpha_devil(1:nqmx)=0.  ! tracer lifting coefficient by dust devils
     389      rho_q(1:nq)=0     ! tracer density (kg.m-3)
     390      radius(1:nq)=0.   ! tracer particle radius (m)
     391      alpha_lift(1:nq) =0.  ! tracer saltation vertical flux/horiz flux ratio (m-1)
     392      alpha_devil(1:nq)=0.  ! tracer lifting coefficient by dust devils
    379393
    380394
     
    393407c       iq=1: Q mass mixing ratio, iq=2: N number mixing ratio
    394408
    395         if( (nqmx.lt.2).or.(water.and.(nqmx.lt.4)) ) then
    396           write(*,*)'initracer: nqmx is too low : nqmx=', nqmx
     409        if( (nq.lt.2).or.(water.and.(nq.lt.4)) ) then
     410          write(*,*)'initracer: nq is too low : nq=', nq
    397411          write(*,*)'water= ',water,' doubleq= ',doubleq   
    398412        end if
     
    499513         alpha_lift(igcm_h2o_vap) =0.
    500514         alpha_devil(igcm_h2o_vap)=0.
    501          if(water.and.(nqmx.ge.2)) then
     515         if(water.and.(nq.ge.2)) then
    502516           radius(igcm_h2o_ice)=3.e-6
    503517           rho_q(igcm_h2o_ice)=rho_ice
    504518           alpha_lift(igcm_h2o_ice) =0.
    505519           alpha_devil(igcm_h2o_ice)=0.
    506          elseif(water.and.(nqmx.lt.2)) then
    507             write(*,*) 'nqmx is too low : nqmx=', nqmx
     520         elseif(water.and.(nq.lt.2)) then
     521            write(*,*) 'nq is too low : nq=', nq
    508522            write(*,*) 'water= ',water
    509523         endif
Note: See TracChangeset for help on using the changeset viewer.