Ignore:
Timestamp:
Apr 16, 2004, 5:43:38 PM (20 years ago)
Author:
lmdzadmin
Message:

Inclusion des modifications de O. Boucher et de J. Quaas pour le calcul des
premiers effets directs et indirects dus aux aerosols
LF

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/nuage.F

    r390 r517  
    11      SUBROUTINE nuage (paprs, pplay,
    22     .                  t, pqlwp, pclc, pcltau, pclemi,
    3      .                  pch, pcl, pcm, pct, pctlwp)
     3     .                  pch, pcl, pcm, pct, pctlwp,
     4     e                  ok_aie,
     5     e                  sulfate, sulfate_pi,
     6     e                  bl95_b0, bl95_b1,
     7     s                  cldtaupi, re, fl)
    48      IMPLICIT none
    59c======================================================================
     
    1115c pqlwp---input-R-eau liquide nuageuse dans l'atmosphere (kg/kg)
    1216c pclc----input-R-couverture nuageuse pour le rayonnement (0 a 1)
     17c ok_aie--input-L-apply aerosol indirect effect or not
     18c sulfate-input-R-sulfate aerosol mass concentration [um/m^3]
     19c sulfate_pi-input-R-dito, pre-industrial value
     20c bl95_b0-input-R-a parameter, may be varied for tests (s-sea, l-land)
     21c bl95_b1-input-R-a parameter, may be varied for tests (    -"-      )
     22c     
     23c cldtaupi-output-R-pre-industrial value of cloud optical thickness,
     24c                   needed for the diagnostics of the aerosol indirect
     25c                   radiative forcing (see radlwsw)
     26c re------output-R-Cloud droplet effective radius multiplied by fl [um]
     27c fl------output-R-Denominator to re, introduced to avoid problems in
     28c                  the averaging of the output. fl is the fraction of liquid
     29c                  water clouds within a grid cell     
    1330c
    1431c pcltau--output-R-epaisseur optique des nuages
     
    2037#include "dimensions.h"
    2138#include "dimphy.h"
    22 #include "nuage.h"
    2339      REAL paprs(klon,klev+1), pplay(klon,klev)
    2440      REAL t(klon,klev)
     
    3854      REAL zflwp, zradef, zfice, zmsac
    3955c
    40       REAL radius, rad_chaud
    41 ccc      PARAMETER (rad_chau1=13.0, rad_chau2=9.0, rad_froid=35.0)
     56      REAL radius, rad_froid, rad_chaud, rad_chau1, rad_chau2
     57      PARAMETER (rad_chau1=13.0, rad_chau2=9.0, rad_froid=35.0)
    4258ccc      PARAMETER (rad_chaud=15.0, rad_froid=35.0)
    4359c sintex initial      PARAMETER (rad_chaud=10.0, rad_froid=30.0)
     
    4864      INTEGER nexpo ! exponentiel pour glace/eau
    4965      PARAMETER (nexpo=6)
     66     
     67cjq for the aerosol indirect effect
     68cjq introduced by Johannes Quaas (quaas@lmd.jussieu.fr), 27/11/2003
     69cjq     
     70      LOGICAL ok_aie            ! Apply AIE or not?
     71     
     72      REAL sulfate(klon, klev)  ! sulfate aerosol mass concentration [ug m-3]
     73      REAL cdnc(klon, klev)     ! cloud droplet number concentration [m-3]
     74      REAL re(klon, klev)       ! cloud droplet effective radius [um]
     75      REAL sulfate_pi(klon, klev)  ! sulfate aerosol mass concentration [ug m-3] (pre-industrial value)
     76      REAL cdnc_pi(klon, klev)     ! cloud droplet number concentration [m-3] (pi value)
     77      REAL re_pi(klon, klev)       ! cloud droplet effective radius [um] (pi value)
     78     
     79      REAL fl(klon, klev)  ! xliq * rneb (denominator to re; fraction of liquid water clouds within the grid cell)
     80     
     81      REAL bl95_b0, bl95_b1     ! Parameter in B&L 95-Formula
     82     
     83      REAL cldtaupi(klon, klev) ! pre-industrial cloud opt thickness for diag
     84cjq-end     
     85     
    5086ccc      PARAMETER (nexpo=1)
    5187c
     
    5692         rad_chaud = rad_chau1
    5793         IF (k.LE.3) rad_chaud = rad_chau2
     94           
    5895         pclc(i,k) = MAX(pclc(i,k), seuil_neb)
    5996         zflwp = 1000.*pqlwp(i,k)/RG/pclc(i,k)
     
    6299         zfice = MIN(MAX(zfice,0.0),1.0)
    63100         zfice = zfice**nexpo
     101         
     102         IF (ok_aie) THEN
     103            ! Formula "D" of Boucher and Lohmann, Tellus, 1995
     104            !             
     105            cdnc(i,k) = 10.**(bl95_b0+bl95_b1*
     106     .           log(MAX(sulfate(i,k),1.e-4))/log(10.))*1.e6 !-m-3
     107            ! Cloud droplet number concentration (CDNC) is restricted
     108            ! to be within [20, 1000 cm^3]
     109            !
     110            cdnc(i,k)=MIN(1000.e6,MAX(20.e6,cdnc(i,k)))
     111            cdnc_pi(i,k) = 10.**(bl95_b0+bl95_b1*
     112     .           log(MAX(sulfate_pi(i,k),1.e-4))/log(10.))*1.e6 !-m-3
     113            cdnc_pi(i,k)=MIN(1000.e6,MAX(20.e6,cdnc_pi(i,k)))
     114            !           
     115            !
     116            ! air density: pplay(i,k) / (RD * zT(i,k))
     117            ! factor 1.1: derive effective radius from volume-mean radius
     118            ! factor 1000 is the water density
     119            ! _chaud means that this is the CDR for liquid water clouds
     120            !
     121            rad_chaud =
     122     .           1.1 * ( (pqlwp(i,k) * pplay(i,k) / (RD * T(i,k)) ) 
     123     .               / (4./3. * RPI * 1000. * cdnc(i,k)) )**(1./3.)
     124            !
     125            ! Convert to um. CDR shall be at least 3 um.
     126            !
     127            rad_chaud = MAX(rad_chaud*1.e6, 3.)
     128           
     129            ! For output diagnostics
     130            !
     131            ! Cloud droplet effective radius [um]
     132            !
     133            ! we multiply here with f * xl (fraction of liquid water
     134            ! clouds in the grid cell) to avoid problems in the
     135            ! averaging of the output.
     136            ! In the output of IOIPSL, derive the real cloud droplet
     137            ! effective radius as re/fl
     138            !
     139            fl(i,k) = pclc(i,k)*(1.-zfice)           
     140            re(i,k) = rad_chaud*fl(i,k)
     141           
     142            ! Pre-industrial cloud opt thickness
     143            !
     144            ! "radius" is calculated as rad_chaud above (plus the
     145            ! ice cloud contribution) but using cdnc_pi instead of
     146            ! cdnc.
     147            radius = MAX(1.1e6 * ( (pqlwp(i,k)*pplay(i,k)/(RD*T(i,k))) 
     148     .                / (4./3.*RPI*1000.*cdnc_pi(i,k)) )**(1./3.),
     149     .               3.) * (1.-zfice) + rad_froid * zfice           
     150            cldtaupi(i,k) = 3.0/2.0 * zflwp / radius
     151     .           
     152         ENDIF                  ! ok_aie
     153         
    64154         radius = rad_chaud * (1.-zfice) + rad_froid * zfice
    65155         coef = coef_chau * (1.-zfice) + coef_froi * zfice
     
    70160         IF (lo) pcltau(i,k) = 0.0
    71161         IF (lo) pclemi(i,k) = 0.0
     162         
     163         IF (.NOT.ok_aie) cldtaupi(i,k)=pcltau(i,k)           
    72164      ENDDO
    73165      ENDDO
Note: See TracChangeset for help on using the changeset viewer.