Changeset 890 for trunk/LMDZ.MARS/libf


Ignore:
Timestamp:
Feb 27, 2013, 3:51:29 PM (12 years ago)
Author:
emillour
Message:

Mars GCM:
minor bug correction in newcondens.F and some code tidying (in co2snow.F also).
EM

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/co2snow.F

    r690 r890  
    2020#include "callkeys.h"
    2121
    22 c     input
    23 c     -----
     22c     Arguments
     23c     ---------
    2424
    25       INTEGER ngrid,nlayer
    26       REAL ptimestep , emisref(ngrid) ! grd or ice  emissivity without snow
    27       logical condsub(ngrid)
     25      INTEGER,INTENT(IN) :: ngrid ! number of atmospheric columns
     26      INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
     27      REAL,INTENT(IN) :: ptimestep ! timestep of the physics (s)
     28      REAL,INTENT(IN) :: emisref(ngrid) ! grd or ice  emissivity without snow
     29      logical,intent(in) :: condsub(ngrid) ! true if there is CO2 condensation
     30                                           ! or sublimation in the column
     31      REAL,INTENT(IN) :: pplev(ngrid,nlayer+1) ! interlayer pressure (Pa)
     32      REAL,INTENT(IN) :: pcondicea(ngrid,nlayer) ! CO2 condensation rate (kg/m2/s)
     33      REAL,INTENT(IN) :: pcondices(ngrid) ! CO2 condensation rate (kg/m2/s)
     34                                          ! on the surface
     35      REAL,INTENT(IN) :: pfallice(ngrid,nlayer+1) ! falling CO2 ice (kg/m2/s)
    2836
    29       REAL pplev(ngrid,nlayer+1)
    30       REAL pcondicea(ngrid,nlayer), pcondices(ngrid)
    31       REAL pfallice(ngrid,nlayer+1)
    32 
    33 c     output
    34 c     ------
    35 
    36       REAL pemisurf(ngrid)
     37      REAL,INTENT(OUT) :: pemisurf(ngrid) ! surface emissivity
    3738
    3839c     local
     
    4546c     saved
    4647c     -----
    47       REAL Kscat(2), scaveng
    48       LOGICAL firstcall
    49       SAVE firstcall
    50       save Kscat , scaveng
    51       DATA firstcall/.true./
     48      REAL,save :: Kscat(2), scaveng
     49      LOGICAL,SAVE :: firstcall=.true.
    5250
    5351c --------------
  • trunk/LMDZ.MARS/libf/phymars/newcondens.F

    r328 r890  
    6666c    Arguments :
    6767c    ---------
    68       INTEGER ngrid, nlayer, nq
    69 
    70       REAL ptimestep
    71       REAL pplay(ngrid,nlayer),pplev(ngrid,nlayer+1)
    72       REAL pcapcal(ngrid)
    73       REAL pt(ngrid,nlayer)
    74       REAL ptsrf(ngrid)
    75       REAL pphi(ngrid,nlayer)
    76       REAL pdt(ngrid,nlayer),pdtsrf(ngrid),pdtc(ngrid,nlayer)
    77       REAL pdtsrfc(ngrid),pdpsrf(ngrid)
    78       REAL piceco2(ngrid),psolaralb(ngrid,2),pemisurf(ngrid)
    79 
    80       REAL pu(ngrid,nlayer) ,  pv(ngrid,nlayer)
    81       REAL pdu(ngrid,nlayer) , pdv(ngrid,nlayer)
    82       REAL pduc(ngrid,nlayer) , pdvc(ngrid,nlayer)
    83       REAL pq(ngridmx,nlayer,nq),pdq(ngrid,nlayer,nq)
    84       REAL pdqc(ngrid,nlayer,nq)
    85       REAL fluxsurf_sw(ngrid,2) ! added to calculate flux dependent albedo
    86       real zls ! solar longitude (rad)
     68      INTEGER,INTENT(IN) :: ngrid  ! number of atmospheric columns
     69      INTEGER,INTENT(IN) :: nlayer ! number of vertical layers
     70      INTEGER,INTENT(IN) :: nq  ! number of tracers
     71
     72      REAL,INTENT(IN) :: ptimestep ! physics timestep (s)
     73      REAL,INTENT(IN) :: pcapcal(ngrid)
     74      REAL,INTENT(IN) :: pplay(ngrid,nlayer) !mid-layer pressure (Pa)
     75      REAL,INTENT(IN) :: pplev(ngrid,nlayer+1) ! inter-layer pressure (Pa)
     76      REAL,INTENT(IN) :: ptsrf(ngrid) ! surface temperature (K)
     77      REAL,INTENT(IN) :: pt(ngrid,nlayer) ! atmospheric temperature (K)
     78      REAL,INTENT(IN) :: pphi(ngrid,nlayer) ! geopotential (m2.s-2)
     79      REAL,INTENT(IN) :: pdt(ngrid,nlayer) ! tendency on temperature from
     80                                           ! previous physical processes (K/s)
     81      REAL,INTENT(IN) :: pdu(ngrid,nlayer) ! tendency on zonal wind (m/s2)
     82                                           ! from previous physical processes
     83      REAL,INTENT(IN) :: pdv(ngrid,nlayer) ! tendency on meridional wind (m/s2)
     84                                           ! from previous physical processes
     85      REAL,INTENT(IN) :: pdtsrf(ngrid) ! tendency on surface temperature from
     86                                       ! previous physical processes (K/s)
     87      REAL,INTENT(IN) :: pu(ngrid,nlayer) ! zonal wind (m/s)
     88      REAL,INTENT(IN) :: pv(ngrid,nlayer) ! meridional wind (m/s)
     89      REAL,INTENT(IN) :: pq(ngrid,nlayer,nq) ! tracers (../kg_air)
     90      REAL,INTENT(IN) :: pdq(ngrid,nlayer,nq) ! tendency on tracers from
     91                                              ! previous physical processes
     92      REAL,INTENT(INOUT) :: piceco2(ngrid) ! CO2 ice on the surface (kg.m-2)
     93      REAL,INTENT(INOUT) :: psolaralb(ngrid,2) ! albedo of the surface
     94      REAL,INTENT(INOUT) :: pemisurf(ngrid) ! emissivity of the surface
     95     
     96      ! tendencies due to CO2 condensation/sublimation:
     97      REAL,INTENT(OUT) :: pdtc(ngrid,nlayer) ! tendency on temperature (K/s)
     98      REAL,INTENT(OUT) :: pdtsrfc(ngrid) ! tendency on surface temperature (K/s)
     99      REAL,INTENT(OUT) :: pdpsrf(ngrid) ! tendency on surface pressure (Pa/s)
     100      REAL,INTENT(OUT) :: pduc(ngrid,nlayer) ! tendency on zonal wind (m.s-2)
     101      REAL,INTENT(OUT) :: pdvc(ngrid,nlayer) ! tendency on meridional wind (m.s-2)
     102      REAL,INTENT(OUT) :: pdqc(ngrid,nlayer,nq) ! tendency on tracers
     103     
     104      ! added to calculate flux dependent albedo:
     105      REAL,intent(in) :: fluxsurf_sw(ngrid,2)
     106      real,intent(in) :: zls ! solar longitude (rad)
     107
    87108c
    88109c    Local variables :
     
    100121c   the incident solar flux     
    101122      PARAMETER(fluxdependent=.false.)
    102       REAL slopy,alpha,constA,constB,constT,albediceF_new(ngridmx)
    103       REAL zt(ngridmx,nlayermx)
     123      REAL slopy,alpha,constA,constB,constT,albediceF_new(ngrid)
     124      REAL zt(ngrid,nlayer)
    104125      REAL zcpi
    105       REAL ztcond (ngridmx,nlayermx+1)
    106       REAL ztcondsol(ngridmx)
    107       REAL zdiceco2(ngridmx)
    108       REAL zcondicea(ngridmx,nlayermx)
    109       REAL zcondices(ngridmx)
    110       REAL zfallice(ngridmx,nlayermx+1) , zfallheat
    111       REAL zmflux(nlayermx+1)
    112       REAL zu(nlayermx),zv(nlayermx)
    113       REAL zq(nlayermx,nqmx),zq1(nlayermx)
    114       REAL ztsrf(ngridmx)
    115       REAL ztc(nlayermx), ztm(nlayermx+1)
    116       REAL zum(nlayermx+1) , zvm(nlayermx+1)
    117       REAL zqm(nlayermx+1,nqmx),zqm1(nlayermx+1)
    118       REAL masse(nlayermx),w(nlayermx+1)
    119       REAL Sm(nlayermx),Smq(nlayermx,nqmx),mixmas,qmix
    120       LOGICAL condsub(ngridmx)
     126      REAL ztcond (ngrid,nlayer+1)
     127      REAL ztcondsol(ngrid)
     128      REAL zdiceco2(ngrid)
     129      REAL zcondicea(ngrid,nlayer)
     130      REAL zcondices(ngrid)
     131      REAL zfallice(ngrid,nlayer+1) , zfallheat
     132      REAL zmflux(nlayer+1)
     133      REAL zu(nlayer),zv(nlayer)
     134      REAL zq(nlayer,nq),zq1(nlayer)
     135      REAL ztsrf(ngrid)
     136      REAL ztc(nlayer), ztm(nlayer+1)
     137      REAL zum(nlayer+1) , zvm(nlayer+1)
     138      REAL zqm(nlayer+1,nq),zqm1(nlayer+1)
     139      REAL masse(nlayer),w(nlayer+1)
     140      REAL Sm(nlayer),Smq(nlayer,nq),mixmas,qmix
     141      LOGICAL condsub(ngrid)
    121142
    122143c variable speciale diagnostique
    123       real tconda1(ngridmx,nlayermx)
    124       real tconda2(ngridmx,nlayermx)
    125 c     REAL zdiceco2a(ngridmx) ! for diagnostic only
    126       real zdtsig (ngridmx,nlayermx)
    127       real zdt (ngridmx,nlayermx)
    128       real vmr_co2(ngridmx,nlayermx) ! co2 volume mixing ratio
     144      real tconda1(ngrid,nlayer)
     145      real tconda2(ngrid,nlayer)
     146c     REAL zdiceco2a(ngrid) ! for diagnostic only
     147      real zdtsig (ngrid,nlayer)
     148      real zdt (ngrid,nlayer)
     149      real vmr_co2(ngrid,nlayer) ! co2 volume mixing ratio
    129150! improved_ztcond flag: If set to .true. (AND running with a 'co2' tracer)
    130151! then condensation temperature is computed using partial pressure of CO2
     
    137158
    138159c   local saved variables
    139       integer ico2
    140       real qco2min,qco2,mmean
    141       save ico2,qco2min
    142       REAL emisref(ngridmx)
    143       REAL latcond,tcond1mb
    144       REAL acond,bcond,ccond,cpice
    145 !      REAL albediceF(ngridmx)
    146       SAVE emisref
    147       SAVE latcond,acond,bcond,ccond,cpice
    148 !      SAVE albediceF
    149       real m_co2, m_noco2, A , B
    150       save A, B, m_co2, m_noco2
    151 
    152       LOGICAL firstcall !,firstcall2
    153       SAVE firstcall !,firstcall2
    154 !      REAL SSUM
    155 !      EXTERNAL SSUM
    156 
    157       DATA latcond,tcond1mb/5.9e5,136.27/
    158       DATA cpice /1000./
    159       DATA firstcall/.true./
    160 !      DATA firstcall2/.true./
     160      integer,save :: ico2 ! index of CO2 tracer
     161      real,save :: qco2min,qco2,mmean
     162      real,allocatable,save :: emisref(:)
     163      real,parameter :: latcond=5.9e5 ! (J/kg) Latent heat of solid CO2 ice
     164      real,parameter :: tcond1mb=136.27 ! condensation temperature (K) at 1 mbar
     165      real,parameter :: cpice=1000. ! (J.kg-1.K-1) specific heat of CO2 ice
     166      REAL,SAVE :: acond,bcond,ccond
     167!      REAL,SAVE :: albediceF(ngridmx)
     168      real,save :: m_co2, m_noco2, A , B
     169
     170      LOGICAL,SAVE :: firstcall = .true. !,firstcall2=.true.
    161171
    162172      integer flag
     
    168178c
    169179      IF (firstcall) THEN
     180         
     181         allocate(emisref(ngrid))
     182         
    170183         bcond=1./tcond1mb
    171184         ccond=cpp/(g*latcond)
     
    198211           qco2min =0.75 
    199212         end if
    200       ENDIF
     213      ENDIF ! of IF (firstcall)
    201214      zcpi=1./cpp
    202215c
     
    348361                 zfallheat=zfallice(ig,1)*
    349362     &           (pphi(ig,1)- phisfi(ig) +
    350      &           cpice*(ztcond(ig,1)-ztcondsol(ig)))/(latcond*ptimestep)
     363     &           cpice*(ztcond(ig,1)-ztcondsol(ig)))/latcond
    351364            ELSE
    352365                 zfallheat=0.
     
    733746!! Specific stuff to bound co2 tracer values ....
    734747      if (bound_qco2.and.(ico2.ne.0)) then
    735         do ig=1,ngridmx
    736           do l=1,nlayermx
     748        do ig=1,ngrid
     749          do l=1,nlayer
    737750            zqco2=pq(ig,l,ico2)
    738751     &            +(pdq(ig,l,ico2)+pdqc(ig,l,ico2))*ptimestep
Note: See TracChangeset for help on using the changeset viewer.