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

    r486 r517  
    11      SUBROUTINE newmicro (paprs, pplay,ok_newmicro,
    22     .                  t, pqlwp, pclc, pcltau, pclemi,
    3 cIM    .                  pch, pcl, pcm, pct, pctlwp)
    43     .                  pch, pcl, pcm, pct, pctlwp,
    5      .                  xflwp, xfiwp, xflwc, xfiwc)
    6 
     4     s                  xflwp, xfiwp, xflwc, xfiwc,
     5     e                  ok_aie,
     6     e                  sulfate, sulfate_pi,
     7     e                  bl95_b0, bl95_b1,
     8     s                  cldtaupi, re, fl)
    79      IMPLICIT none
    810c======================================================================
     
    1517c pclc----input-R-couverture nuageuse pour le rayonnement (0 a 1)
    1618c
     19c ok_aie--input-L-apply aerosol indirect effect or not
     20c sulfate-input-R-sulfate aerosol mass concentration [um/m^3]
     21c sulfate_pi-input-R-dito, pre-industrial value
     22c bl95_b0-input-R-a parameter, may be varied for tests (s-sea, l-land)
     23c bl95_b1-input-R-a parameter, may be varied for tests (    -"-      )
     24c     
     25c cldtaupi-output-R-pre-industrial value of cloud optical thickness,
     26c                   needed for the diagnostics of the aerosol indirect
     27c                   radiative forcing (see radlwsw)
     28c re------output-R-Cloud droplet effective radius multiplied by fl [um]
     29c fl------output-R-Denominator to re, introduced to avoid problems in
     30c                  the averaging of the output. fl is the fraction of liquid
     31c                  water clouds within a grid cell           
    1732c pcltau--output-R-epaisseur optique des nuages
    1833c pclemi--output-R-emissivite des nuages (0 a 1)
     
    6681      parameter (DF=1.66) ! diffusivity factor
    6782c sb --
    68 
     83cjq for the aerosol indirect effect
     84cjq introduced by Johannes Quaas (quaas@lmd.jussieu.fr), 27/11/2003
     85cjq     
     86      LOGICAL ok_aie            ! Apply AIE or not?
     87      LOGICAL ok_a1lwpdep       ! a1 LWP dependent?
     88     
     89      REAL sulfate(klon, klev)  ! sulfate aerosol mass concentration [ug m-3]
     90      REAL cdnc(klon, klev)     ! cloud droplet number concentration [m-3]
     91      REAL re(klon, klev)       ! cloud droplet effective radius [um]
     92      REAL sulfate_pi(klon, klev)  ! sulfate aerosol mass concentration [ug m-3] (pre-industrial value)
     93      REAL cdnc_pi(klon, klev)     ! cloud droplet number concentration [m-3] (pi value)
     94      REAL re_pi(klon, klev)       ! cloud droplet effective radius [um] (pi value)
     95     
     96      REAL fl(klon, klev)       ! xliq * rneb (denominator to re; fraction of liquid water clouds within the grid cell)
     97     
     98      REAL bl95_b0, bl95_b1     ! Parameter in B&L 95-Formula
     99     
     100      REAL cldtaupi(klon, klev) ! pre-industrial cloud opt thickness for diag
     101cjq-end   
    69102c
    70103c Calculer l'epaisseur optique et l'emmissivite des nuages
     
    119152
    120153c for liquid water clouds:
     154         IF (ok_aie) THEN
     155            ! Formula "D" of Boucher and Lohmann, Tellus, 1995
     156            !             
     157            cdnc(i,k) = 10.**(bl95_b0+bl95_b1*
     158     .           log(MAX(sulfate(i,k),1.e-4))/log(10.))*1.e6 !-m-3
     159            ! Cloud droplet number concentration (CDNC) is restricted
     160            ! to be within [20, 1000 cm^3]
     161            !
     162            cdnc(i,k)=MIN(1000.e6,MAX(20.e6,cdnc(i,k)))
     163            !
     164            !
     165            cdnc_pi(i,k) = 10.**(bl95_b0+bl95_b1*
     166     .           log(MAX(sulfate_pi(i,k),1.e-4))/log(10.))*1.e6 !-m-3
     167            cdnc_pi(i,k)=MIN(1000.e6,MAX(20.e6,cdnc_pi(i,k)))
     168            !           
     169            !
     170            ! air density: pplay(i,k) / (RD * zT(i,k))
     171            ! factor 1.1: derive effective radius from volume-mean radius
     172            ! factor 1000 is the water density
     173            ! _chaud means that this is the CDR for liquid water clouds
     174            !
     175            rad_chaud =
     176     .           1.1 * ( (pqlwp(i,k) * pplay(i,k) / (RD * T(i,k)) ) 
     177     .               / (4./3. * RPI * 1000. * cdnc(i,k)) )**(1./3.)
     178            !
     179            ! Convert to um. CDR shall be at least 3 um.
     180            !
     181c           rad_chaud = MAX(rad_chaud*1.e6, 3.)
     182            rad_chaud = MAX(rad_chaud*1.e6, 5.)
     183           
     184            ! Pre-industrial cloud opt thickness
     185            !
     186            ! "radius" is calculated as rad_chaud above (plus the
     187            ! ice cloud contribution) but using cdnc_pi instead of
     188            ! cdnc.
     189            radius =
     190     .           1.1 * ( (pqlwp(i,k) * pplay(i,k) / (RD * T(i,k)) ) 
     191     .               / (4./3. * RPI * 1000. * cdnc_pi(i,k)) )**(1./3.)
     192            radius = MAX(radius*1.e6, 3.)
     193           
     194            tc = t(i,k)-273.15
     195            rei = 0.71*tc + 61.29
     196            if (tc.le.-81.4) rei = 3.5
     197            if (zflwp(i).eq.0.) radius = 1.
     198            if (zfiwp(i).eq.0. .or. rei.le.0.) rei = 1.
     199            cldtaupi(i,k) = 3.0/2.0 * zflwp(i) / radius
     200     .             + zfiwp(i) * (3.448e-03  + 2.431/rei)
     201         ENDIF                  ! ok_aie
     202         ! For output diagnostics
     203         !
     204         ! Cloud droplet effective radius [um]
     205         !
     206         ! we multiply here with f * xl (fraction of liquid water
     207         ! clouds in the grid cell) to avoid problems in the
     208         ! averaging of the output.
     209         ! In the output of IOIPSL, derive the real cloud droplet
     210         ! effective radius as re/fl
     211         !
     212         fl(i,k) = pclc(i,k)*(1.-zfice)           
     213         re(i,k) = rad_chaud*fl(i,k)
     214           
     215c-jq end         
     216         
    121217         rel = rad_chaud
    122 
    123218c for ice clouds: as a function of the ambiant temperature
    124219c [formula used by Iacobellis and Somerville (2000), with an
     
    156251         IF (lo) pcltau(i,k) = 0.0
    157252         IF (lo) pclemi(i,k) = 0.0
     253         
     254         IF (lo) cldtaupi(i,k) = 0.0
     255         IF (.NOT.ok_aie) cldtaupi(i,k)=pcltau(i,k)           
    158256      ENDDO
    159257      ENDDO
Note: See TracChangeset for help on using the changeset viewer.