/[lmdze]/trunk/phylmd/newmicro.f
ViewVC logotype

Diff of /trunk/phylmd/newmicro.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 175 by guez, Fri Feb 5 16:02:34 2016 UTC revision 217 by guez, Thu Mar 30 14:25:18 2017 UTC
# Line 4  module newmicro_m Line 4  module newmicro_m
4    
5  contains  contains
6    
7    SUBROUTINE newmicro (paprs, play, t, qlwp, clc, cltau, clemi, cldh, &    SUBROUTINE newmicro (paprs, play, t, qlwp, clc, cltau, clemi, cldh, cldl, &
8         cldl, cldm, cldt, ctlwp, flwp, fiwp, flwc, fiwc, ok_aie, sulfate, &         cldm, cldt, ctlwp, flwp, fiwp, flwc, fiwc)
        sulfate_pi, bl95_b0, bl95_b1, cldtaupi, re, fl)  
9    
10      ! From LMDZ4/libf/phylmd/newmicro.F, version 1.2 2004/06/03 09:22:43      ! From LMDZ4/libf/phylmd/newmicro.F, version 1.2 2004/06/03 09:22:43
11    
# Line 16  contains Line 15  contains
15    
16      USE conf_phys_m, ONLY: rad_chau1, rad_chau2      USE conf_phys_m, ONLY: rad_chau1, rad_chau2
17      USE dimphy, ONLY: klev, klon      USE dimphy, ONLY: klev, klon
18      USE suphec_m, ONLY: rd, rg      USE histwrite_phy_m, ONLY: histwrite_phy
19      use nr_util, only: pi      USE suphec_m, ONLY: rg
20    
21      REAL, intent(in):: paprs(:, :) ! (klon, klev+1)      REAL, intent(in):: paprs(:, :) ! (klon, klev+1)
22      real, intent(in):: play(:, :) ! (klon, klev)      real, intent(in):: play(:, :) ! (klon, klev)
# Line 36  contains Line 35  contains
35      REAL, intent(out):: ctlwp(:) ! (klon)      REAL, intent(out):: ctlwp(:) ! (klon)
36      REAL, intent(out):: flwp(:), fiwp(:) ! (klon)      REAL, intent(out):: flwp(:), fiwp(:) ! (klon)
37      REAL, intent(out):: flwc(:, :), fiwc(:, :) ! (klon, klev)      REAL, intent(out):: flwc(:, :), fiwc(:, :) ! (klon, klev)
     LOGICAL, intent(in):: ok_aie ! apply aerosol indirect effect  
38    
39      REAL, intent(in):: sulfate(:, :) ! (klon, klev)      ! Local:
     ! sulfate aerosol mass concentration (micro g m-3)  
   
     REAL, intent(in):: sulfate_pi(:, :) ! (klon, klev)  
     ! sulfate aerosol mass concentration (micro g m-3), pre-industrial value  
   
     REAL, intent(in):: bl95_b0, bl95_b1  
     ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus  
     ! B). They link cloud droplet number concentration to aerosol mass  
     ! concentration.  
   
     REAL, intent(out):: cldtaupi(:, :) ! (klon, klev)  
     ! pre-industrial value of cloud optical thickness, needed for the  
     ! diagnosis of the aerosol indirect radiative forcing (see  
     ! radlwsw)  
40    
41      REAL, intent(out):: re(:, :) ! (klon, klev)      REAL re(klon, klev)
42      ! cloud droplet effective radius multiplied by fl (micro m)      ! cloud droplet effective radius multiplied by fl (micro m)
43    
44      REAL, intent(out):: fl(:, :) ! (klon, klev)      REAL fl(klon, klev)
45      ! Denominator to re, introduced to avoid problems in the averaging      ! Denominator to re, introduced to avoid problems in the averaging
46      ! of the output. fl is the fraction of liquid water clouds within      ! of the output. fl is the fraction of liquid water clouds within
47      ! a grid cell.      ! a grid cell.
48    
     ! Local:  
   
49      REAL, PARAMETER:: cetahb = 0.45, cetamb = 0.8      REAL, PARAMETER:: cetahb = 0.45, cetamb = 0.8
50      INTEGER i, k      INTEGER i, k
51      REAL zflwp(klon), fice      REAL zflwp(klon), fice
52      REAL radius, rad_chaud      REAL rad_chaud
53      REAL, PARAMETER:: coef_chau = 0.13      REAL, PARAMETER:: coef_chau = 0.13
54      REAL, PARAMETER:: seuil_neb = 0.001, t_glace = 273. - 15.      REAL, PARAMETER:: seuil_neb = 0.001, t_glace = 273. - 15.
55      real rel, tc, rei, zfiwp(klon)      real rel, tc, rei, zfiwp(klon)
56      real k_ice      real k_ice
57      real, parameter:: k_ice0 = 0.005 ! units=m2/g      real, parameter:: k_ice0 = 0.005 ! units=m2/g
58      real, parameter:: DF = 1.66 ! diffusivity factor      real, parameter:: DF = 1.66 ! diffusivity factor
     REAL cdnc(klon, klev) ! cloud droplet number concentration (m-3)  
   
     REAL cdnc_pi(klon, klev)  
     ! cloud droplet number concentration, pre-industrial value (m-3)  
59    
60      !-----------------------------------------------------------------      !-----------------------------------------------------------------
61    
# Line 87  contains Line 65  contains
65         flwp(i) = 0.         flwp(i) = 0.
66         fiwp(i) = 0.         fiwp(i) = 0.
67    
68         DO k = 1, klev         loop_vertical: DO k = 1, klev
69            clc(i, k) = MAX(clc(i, k), seuil_neb)            clc(i, k) = MAX(clc(i, k), seuil_neb)
70    
71            ! liquid/ice cloud water paths:            ! liquid/ice cloud water paths:
# Line 113  contains Line 91  contains
91            ! effective cloud droplet radius (microns):            ! effective cloud droplet radius (microns):
92    
93            ! for liquid water clouds:            ! for liquid water clouds:
94            IF (ok_aie) THEN            rad_chaud = merge(rad_chau2, rad_chau1, k <= 3)
95               cdnc(i, k) = 10.**(bl95_b0 + bl95_b1 &            
                   * log10(MAX(sulfate(i, k), 1e-4)) + 6.)  
              cdnc_pi(i, k) = 10.**(bl95_b0 + bl95_b1 &  
                   * log10(MAX(sulfate_pi(i, k), 1e-4)) + 6.)  
   
              ! Restrict to interval [20, 1000] cm-3:  
              cdnc(i, k) = MIN(1000e6, MAX(20e6, cdnc(i, k)))  
              cdnc_pi(i, k) = MIN(1000e6, MAX(20e6, cdnc_pi(i, k)))  
   
              ! air density: play(i, k) / (RD * T(i, k))  
              ! factor 1.1: derive effective radius from volume-mean radius  
              ! factor 1000 is the water density  
              ! "_chaud" means that this is the CDR for liquid water clouds  
   
              rad_chaud = 1.1 * ((qlwp(i, k) * play(i, k) / (RD * T(i, k))) &  
                   / (4./3. * PI * 1000. * cdnc(i, k)))**(1./3.)  
   
              ! Convert to micro m and set a lower limit:  
              rad_chaud = MAX(rad_chaud * 1e6, 5.)  
   
              ! Pre-industrial cloud optical thickness  
   
              ! "radius" is calculated as rad_chaud above (plus the  
              ! ice cloud contribution) but using cdnc_pi instead of  
              ! cdnc.  
              radius = 1.1 * ((qlwp(i, k) * play(i, k) / (RD * T(i, k))) &  
                   / (4./3. * PI * 1000. * cdnc_pi(i, k)))**(1./3.)  
              radius = MAX(radius * 1e6, 5.)  
   
              tc = t(i, k)-273.15  
              rei = merge(3.5, 0.71 * tc + 61.29, tc <= -81.4)  
              if (zflwp(i) == 0.) radius = 1.  
              if (zfiwp(i) == 0. .or. rei <= 0.) rei = 1.  
              cldtaupi(i, k) = 3. / 2. * zflwp(i) / radius &  
                   + zfiwp(i) * (3.448e-03 + 2.431 / rei)  
           else  
              rad_chaud = merge(rad_chau2, rad_chau1, k <= 3)  
           ENDIF  
96            ! For output diagnostics            ! For output diagnostics
97    
98            ! Cloud droplet effective radius (micro m)            ! Cloud droplet effective radius (micro m)
# Line 197  contains Line 138  contains
138               clc(i, k) = 0.               clc(i, k) = 0.
139               cltau(i, k) = 0.               cltau(i, k) = 0.
140               clemi(i, k) = 0.               clemi(i, k) = 0.
              cldtaupi(i, k) = 0.  
141            end if            end if
142           ENDDO loop_vertical
           IF (.NOT. ok_aie) cldtaupi(i, k) = cltau(i, k)  
        ENDDO  
143      ENDDO loop_horizontal      ENDDO loop_horizontal
144    
145      ! COMPUTE CLOUD LIQUID PATH AND TOTAL CLOUDINESS      ! COMPUTE CLOUD LIQUID PATH AND TOTAL CLOUDINESS
# Line 236  contains Line 174  contains
174         cldl(i)=1.-cldl(i)         cldl(i)=1.-cldl(i)
175      ENDDO      ENDDO
176    
177        CALL histwrite_phy("re", re)
178        CALL histwrite_phy("fl", fl)
179    
180    END SUBROUTINE newmicro    END SUBROUTINE newmicro
181    
182  end module newmicro_m  end module newmicro_m

Legend:
Removed from v.175  
changed lines
  Added in v.217

  ViewVC Help
Powered by ViewVC 1.1.21