Ignore:
Timestamp:
Sep 23, 2013, 9:56:47 AM (11 years ago)
Author:
emillour
Message:

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

File:
1 edited

Legend:

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

    r1036 r1047  
    1       SUBROUTINE perosat(ig, ptimestep,
     1      SUBROUTINE perosat(ngrid,nlayer,nq,ig, ptimestep,
    22     $                   pplev, pplay, zt,
    33     &                   zy, pdqcloud, pdqscloud)
    4       use tracer_mod, only: nqmx, igcm_h2o2, mmol
     4     
     5      use tracer_mod, only: igcm_h2o2, mmol
     6      use conc_mod, only: mmean
    57      IMPLICIT NONE
    68
     
    2224c   -------------
    2325
    24 #include "dimensions.h"
    25 #include "dimphys.h"
     26!#include "dimensions.h"
     27!#include "dimphys.h"
    2628#include "comcstfi.h"
    27 #include "chimiedata.h"
     29!#include "chimiedata.h"
    2830!#include "tracer.h"
    29 #include "conc.h"
     31!#include "conc.h"
    3032c
    3133c   arguments:
    3234c   ----------
    3335
     36      integer,intent(in) :: ngrid   ! number of atmospheric columns
     37      integer,intent(in) :: nlayer  ! number of atmospheric layers
     38      integer,intent(in) :: nq      ! number of tracers
    3439      INTEGER ig
    3540      REAL ptimestep                ! pas de temps physique (s)
    36       REAL pplev(ngridmx,nlayermx+1)! pression aux inter-couches (Pa)
    37       REAL pplay(ngridmx,nlayermx)  ! pression au milieu des couches (Pa)
    38       REAL zt(nlayermx)             ! temperature au centre des couches (K)
     41      REAL pplev(ngrid,nlayer+1)    ! pression aux inter-couches (Pa)
     42      REAL pplay(ngrid,nlayer)      ! pression au milieu des couches (Pa)
     43      REAL zt(nlayer             ! temperature au centre des couches (K)
    3944                                    ! deja mise a jour dans calchim
    4045
    4146c   Traceurs :
    42       real zy(nlayermx,nqmx)        ! traceur (fraction molaire sortie chimie)
    43       real pdqcloud(ngridmx,nlayermx,nqmx) ! tendance condensation (kg/kg.s-1)
    44       real pdqscloud(ngridmx,nqmx)         ! flux en surface (kg.m-2.s-1)
     47      real zy(nlayer,nq)        ! traceur (fraction molaire sortie chimie)
     48      real pdqcloud(ngrid,nlayer,nq) ! tendance condensation (kg/kg.s-1)
     49      real pdqscloud(ngrid,nq)         ! flux en surface (kg.m-2.s-1)
    4550     
    4651c   local:
     
    4954      INTEGER l,iq
    5055
    51       REAL zysat(nlayermx)
    52       REAL zynew(nlayermx)             ! mole fraction after condensation
     56      REAL zysat(nlayer)
     57      REAL zynew(nlayer             ! mole fraction after condensation
    5358      REAL psat_hg                     ! pression saturante (mm Hg)
    5459      REAL psat_hpa                    ! pression saturante (hPa)
     
    5762c     Pour diagnostique :
    5863c     ~~~~~~~~~~~~~~~~~
    59       REAL taucond(ngridmx,nlayermx)   ! taux de condensation (kg/kg/s-1)
     64      REAL taucond(ngrid,nlayer)   ! taux de condensation (kg/kg/s-1)
    6065
    6166c-----------------------------------------------------------------------
     
    8085c       domaine d'application: T < 220 K
    8186c
    82         do l = 1,nlayermx
     87        do l = 1,nlayer
    8388
    8489c       print *,'ig=',ig,' l=',l,' igcm_h2o2=',igcm_h2o2
     
    103108c       (Pour diagnostic seulement !)
    104109c
    105         do l=1, nlayermx
     110        do l=1, nlayer
    106111          taucond(ig,l)=max((zy(l,igcm_h2o2)-zysat(l))*mmol(igcm_h2o2)
    107112     $                         /(mmean(ig,l)*ptimestep),0.)
     
    111116c       ~~~~~~~~~~~~~~~~~~~~~~~~~~
    112117c
    113         do l=nlayermx,2, -1
     118        do l=nlayer,2, -1
    114119           if (zynew(l).gt.zysat(l)) then
    115120              zynew(l-1) =  zynew(l-1) + (zynew(l) - zysat(l))
     
    135140c       ~~~~~~~~~~~~~~~
    136141c
    137         do l=1, nlayermx
     142        do l=1, nlayer
    138143          pdqcloud(ig,l,igcm_h2o2)=(zynew(l) - zy(l,igcm_h2o2))
    139144     &                     *mmol(igcm_h2o2)/(mmean(ig,l)*ptimestep)
Note: See TracChangeset for help on using the changeset viewer.