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

Annotation of /trunk/phylmd/nuage.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 175 - (hide annotations)
Fri Feb 5 16:02:34 2016 UTC (8 years, 3 months ago) by guez
Original Path: trunk/Sources/phylmd/nuage.f
File size: 7727 byte(s)
Added argument itau_phy to ini_histins, phyetat0, phytrac and
phyredem0. Removed variable itau_phy of module temps. Avoiding side
effect in etat0 and phyetat0. The procedures ini_histins, phyetat0,
phytrac and phyredem0 are all called by physiq so there is no
cascading variable penalty.

In procedure inifilr, made the condition on colat0 weaker to allow for
rounding error.

Removed arguments flux_o, flux_g and t_slab of clmain, flux_o and
flux_g of clqh and interfsurf_hq, tslab and seaice of phyetat0 and
phyredem. NetCDF variables TSLAB and SEAICE no longer in
restartphy.nc. All these variables were related to the not-implemented
slab ocean. seaice and tslab were just set to 0 in phyetat0 and never
used nor changed. flux_o and flux_g were computed in clmain but never
used in physiq.

Removed argument swnet of clqh. Was used only to compute a local
variable, swdown, which was not used.

1 guez 175 module nuage_m
2    
3 guez 51 IMPLICIT none
4 guez 3
5 guez 175 contains
6 guez 3
7 guez 175 SUBROUTINE nuage (paprs, pplay, t, pqlwp, pclc, pcltau, pclemi, pch, pcl, &
8     pcm, pct, pctlwp, ok_aie, sulfate, sulfate_pi, bl95_b0, bl95_b1, &
9     cldtaupi, re, fl)
10     !
11     ! From LMDZ4/libf/phylmd/nuage.F, version 1.1.1.1 2004/05/19 12:53:07
12     !
13     use dimens_m
14     use dimphy
15     use nr_util, only: pi
16     use SUPHEC_M
17     !======================================================================
18     ! Auteur(s): Z.X. Li (LMD/CNRS) date: 19930910
19     ! Objet: Calculer epaisseur optique et emmissivite des nuages
20     !======================================================================
21     ! Arguments:
22     ! t-------input-R-temperature
23     ! pqlwp---input-R-eau liquide nuageuse dans l'atmosphere (kg/kg)
24     ! pclc----input-R-couverture nuageuse pour le rayonnement (0 a 1)
25     ! ok_aie--input-L-apply aerosol indirect effect or not
26     ! sulfate-input-R-sulfate aerosol mass concentration [um/m^3]
27     ! sulfate_pi-input-R-dito, pre-industrial value
28     ! bl95_b0-input-R-a parameter, may be varied for tests (s-sea, l-land)
29     ! bl95_b1-input-R-a parameter, may be varied for tests ( -"- )
30     !
31     ! cldtaupi-output-R-pre-industrial value of cloud optical thickness,
32     ! needed for the diagnostics of the aerosol indirect
33     ! radiative forcing (see radlwsw)
34     ! re------output-R-Cloud droplet effective radius multiplied by fl [um]
35     ! fl------output-R-Denominator to re, introduced to avoid problems in
36     ! the averaging of the output. fl is the fraction of liquid
37     ! water clouds within a grid cell
38     !
39     ! pcltau--output-R-epaisseur optique des nuages
40     ! pclemi--output-R-emissivite des nuages (0 a 1)
41     !======================================================================
42     !
43     !
44     REAL, intent(in):: paprs(klon,klev+1)
45     real, intent(in):: pplay(klon,klev)
46     REAL, intent(in):: t(klon,klev)
47     !
48     REAL pclc(klon,klev)
49     REAL pqlwp(klon,klev)
50     REAL pcltau(klon,klev), pclemi(klon,klev)
51     !
52     REAL pct(klon), pctlwp(klon), pch(klon), pcl(klon), pcm(klon)
53     !
54     LOGICAL lo
55     !
56     REAL cetahb, cetamb
57     PARAMETER (cetahb = 0.45, cetamb = 0.80)
58     !
59     INTEGER i, k
60     REAL zflwp, zfice
61     !
62     REAL radius, rad_froid, rad_chaud, rad_chau1, rad_chau2
63     PARAMETER (rad_chau1=13.0, rad_chau2=9.0, rad_froid=35.0)
64     !cc PARAMETER (rad_chaud=15.0, rad_froid=35.0)
65     ! sintex initial PARAMETER (rad_chaud=10.0, rad_froid=30.0)
66     REAL coef, coef_froi, coef_chau
67     PARAMETER (coef_chau=0.13, coef_froi=0.09)
68     REAL seuil_neb, t_glace
69     PARAMETER (seuil_neb=0.001, t_glace=273.0-15.0)
70     INTEGER nexpo ! exponentiel pour glace/eau
71     PARAMETER (nexpo=6)
72 guez 51
73 guez 175 !jq for the aerosol indirect effect
74     !jq introduced by Johannes Quaas (quaas@lmd.jussieu.fr), 27/11/2003
75     !jq
76     LOGICAL ok_aie ! Apply AIE or not?
77 guez 51
78 guez 175 REAL sulfate(klon, klev) ! sulfate aerosol mass concentration [ug m-3]
79     REAL cdnc(klon, klev) ! cloud droplet number concentration [m-3]
80     REAL re(klon, klev) ! cloud droplet effective radius [um]
81     REAL, intent(in):: sulfate_pi(klon, klev) ! sulfate aerosol mass concentration [ug m-3] (pre-industrial value)
82     REAL cdnc_pi(klon, klev) ! cloud droplet number concentration [m-3] (pi value)
83 guez 51
84 guez 175 REAL fl(klon, klev) ! xliq * rneb (denominator to re ; fraction of liquid water clouds within the grid cell)
85 guez 51
86 guez 175 REAL bl95_b0, bl95_b1 ! Parameter in B&L 95-Formula
87 guez 51
88 guez 175 REAL cldtaupi(klon, klev) ! pre-industrial cloud opt thickness for diag
89 guez 51
90 guez 175 !cc PARAMETER (nexpo=1)
91     !
92     ! Calculer l'epaisseur optique et l'emmissivite des nuages
93     !
94     DO k = 1, klev
95     DO i = 1, klon
96     rad_chaud = rad_chau1
97     IF (k.LE.3) rad_chaud = rad_chau2
98 guez 51
99 guez 175 pclc(i,k) = MAX(pclc(i,k), seuil_neb)
100     zflwp = 1000.*pqlwp(i,k)/RG/pclc(i,k) &
101     *(paprs(i,k)-paprs(i,k+1))
102     zfice = 1.0 - (t(i,k)-t_glace) / (273.13-t_glace)
103     zfice = MIN(MAX(zfice,0.0),1.0)
104     zfice = zfice**nexpo
105 guez 51
106 guez 175 IF (ok_aie) THEN
107     ! Formula "D" of Boucher and Lohmann, Tellus, 1995
108     !
109     cdnc(i,k) = 10.**(bl95_b0+bl95_b1* &
110     log(MAX(sulfate(i,k),1.e-4))/log(10.))*1.e6 !-m-3
111     ! Cloud droplet number concentration (CDNC) is restricted
112     ! to be within [20, 1000 cm^3]
113     !
114     cdnc(i,k)=MIN(1000.e6,MAX(20.e6,cdnc(i,k)))
115     cdnc_pi(i,k) = 10.**(bl95_b0+bl95_b1* &
116     log(MAX(sulfate_pi(i,k),1.e-4))/log(10.))*1.e6 !-m-3
117     cdnc_pi(i,k)=MIN(1000.e6,MAX(20.e6,cdnc_pi(i,k)))
118     !
119     !
120     ! air density: pplay(i,k) / (RD * zT(i,k))
121     ! factor 1.1: derive effective radius from volume-mean radius
122     ! factor 1000 is the water density
123     ! _chaud means that this is the CDR for liquid water clouds
124     !
125     rad_chaud = &
126     1.1 * ( (pqlwp(i,k) * pplay(i,k) / (RD * T(i,k)) ) &
127     / (4./3. * PI * 1000. * cdnc(i,k)) )**(1./3.)
128     !
129     ! Convert to um. CDR shall be at least 3 um.
130     !
131     rad_chaud = MAX(rad_chaud*1.e6, 3.)
132 guez 51
133 guez 175 ! For output diagnostics
134     !
135     ! Cloud droplet effective radius [um]
136     !
137     ! we multiply here with f * xl (fraction of liquid water
138     ! clouds in the grid cell) to avoid problems in the
139     ! averaging of the output.
140     ! In the output of IOIPSL, derive the real cloud droplet
141     ! effective radius as re/fl
142     !
143     fl(i,k) = pclc(i,k)*(1.-zfice)
144     re(i,k) = rad_chaud*fl(i,k)
145 guez 51
146 guez 175 ! Pre-industrial cloud opt thickness
147     !
148     ! "radius" is calculated as rad_chaud above (plus the
149     ! ice cloud contribution) but using cdnc_pi instead of
150     ! cdnc.
151     radius = MAX(1.1e6 * ( (pqlwp(i,k)*pplay(i,k)/(RD*T(i,k))) &
152     / (4./3.*PI*1000.*cdnc_pi(i,k)) )**(1./3.), &
153     3.) * (1.-zfice) + rad_froid * zfice
154     cldtaupi(i,k) = 3.0/2.0 * zflwp / radius
155 guez 51
156 guez 175 END IF ! ok_aie
157    
158     radius = rad_chaud * (1.-zfice) + rad_froid * zfice
159     coef = coef_chau * (1.-zfice) + coef_froi * zfice
160     pcltau(i,k) = 3.0/2.0 * zflwp / radius
161     pclemi(i,k) = 1.0 - EXP( - coef * zflwp)
162     lo = (pclc(i,k) .LE. seuil_neb)
163     IF (lo) pclc(i,k) = 0.0
164     IF (lo) pcltau(i,k) = 0.0
165     IF (lo) pclemi(i,k) = 0.0
166    
167     IF (.NOT.ok_aie) cldtaupi(i,k)=pcltau(i,k)
168     END DO
169     END DO
170     !
171     ! COMPUTE CLOUD LIQUID PATH AND TOTAL CLOUDINESS
172     !
173     DO i = 1, klon
174     pct(i)=1.0
175     pch(i)=1.0
176     pcm(i) = 1.0
177     pcl(i) = 1.0
178     pctlwp(i) = 0.0
179     END DO
180     !
181     DO k = klev, 1, -1
182     DO i = 1, klon
183     pctlwp(i) = pctlwp(i) &
184     + pqlwp(i,k)*(paprs(i,k)-paprs(i,k+1))/RG
185     pct(i) = pct(i)*(1.0-pclc(i,k))
186     if (pplay(i,k).LE.cetahb*paprs(i,1)) &
187     pch(i) = pch(i)*(1.0-pclc(i,k))
188     if (pplay(i,k).GT.cetahb*paprs(i,1) .AND. &
189     pplay(i,k).LE.cetamb*paprs(i,1)) &
190     pcm(i) = pcm(i)*(1.0-pclc(i,k))
191     if (pplay(i,k).GT.cetamb*paprs(i,1)) &
192     pcl(i) = pcl(i)*(1.0-pclc(i,k))
193     END DO
194     END DO
195     !
196     DO i = 1, klon
197     pct(i)=1.-pct(i)
198     pch(i)=1.-pch(i)
199     pcm(i)=1.-pcm(i)
200     pcl(i)=1.-pcl(i)
201     END DO
202     !
203     END SUBROUTINE nuage
204    
205     end module nuage_m

  ViewVC Help
Powered by ViewVC 1.1.21