Ignore:
Timestamp:
Oct 24, 2011, 3:56:49 PM (13 years ago)
Author:
acolaitis
Message:

Included variation of mean molar mass in potential temperature definition: this modification realistically accounts for mixing in the polar night when the atm is enriched in Ar. This follows present computations in convadj for the polar night case.

File:
1 edited

Legend:

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

    r38 r325  
    1       SUBROUTINE vdif_kc(dt,g,zlev,zlay,u,v,teta,cd,q2,km,kn)
     1      SUBROUTINE vdif_kc(dt,g,zlev,zlay,u,v,teta,cd,q2,km,kn,zq)
    22      IMPLICIT NONE
    33c.......................................................................
    44#include "dimensions.h"
    55#include "dimphys.h"
     6#include "tracer.h"
     7#include "callkeys.h"
    68c.......................................................................
    79c
     
    3739      REAL km(ngridmx,nlayermx+1)
    3840      REAL kn(ngridmx,nlayermx+1)
     41      REAL zq(ngridmx,nlayermx,nqmx)
    3942c.......................................................................
    4043c
     
    204207     &  cm4=-9.E+0 *a1*a2
    205208     &          )
     209
     210c AC: variables for theta_m computation
     211
     212      INTEGER ico2,iq
     213      SAVE ico2
     214      REAL m_co2, m_noco2, A , B
     215      SAVE A, B
     216      LOGICAL firstcall
     217      save firstcall
     218      data firstcall/.true./
     219      REAL zhc(ngridmx,nlayermx)
     220c.......................................................................
     221c  Initialization
     222c.......................................................................
     223
     224      if(firstcall) then
     225        ico2=0
     226        if (tracer) then
     227!     Prepare Special treatment if one of the tracers is CO2 gas
     228           do iq=1,nqmx
     229             if (noms(iq).eq."co2") then
     230                ico2=iq
     231                m_co2 = 44.01E-3  ! CO2 molecular mass (kg/mol)
     232                m_noco2 = 33.37E-3  ! Non condensible mol mass (kg/mol)
     233!               Compute A and B coefficient use to compute
     234!               mean molecular mass Mair defined by
     235!               1/Mair = q(ico2)/m_co2 + (1-q(ico2))/m_noco2
     236!               1/Mair = A*q(ico2) + B
     237                A =(1/m_co2 - 1/m_noco2)
     238                B=1/m_noco2
     239             end if
     240           enddo
     241        endif
     242
     243      firstcall=.false.
     244      endif !of if firstcall
     245
     246c.......................................................................
     247c  Special treatment for co2
     248c.......................................................................
     249
     250      if (ico2.ne.0) then
     251!     Special case if one of the tracers is CO2 gas
     252         DO ilay=1,nlay
     253           DO igrid=1,ngrid
     254            zhc(igrid,ilay) = teta(igrid,ilay)*(A*zq(igrid,ilay,ico2)+B)
     255           ENDDO
     256         ENDDO
     257       else
     258          zhc(:,:)=teta(:,:)
     259       end if
     260
    206261c.......................................................................
    207262c  traitment des valeur de q2 en entree
     
    272327c
    273328        n2(igrid,ilev)=g*unsdzdec(igrid,ilev)
    274      &                   *(teta(igrid,ilev)-teta(igrid,ilev-1))
    275      &                   /(teta(igrid,ilev)+teta(igrid,ilev-1)) *2.E+0
     329     &                   *(zhc(igrid,ilev)-zhc(igrid,ilev-1))
     330     &                   /(zhc(igrid,ilev)+zhc(igrid,ilev-1)) *2.E+0
    276331c
    277332c --->
Note: See TracChangeset for help on using the changeset viewer.