/[lmdze]/trunk/Sources/phylmd/diagphy.f
ViewVC logotype

Annotation of /trunk/Sources/phylmd/diagphy.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 72 - (hide annotations)
Tue Jul 23 13:00:07 2013 UTC (10 years, 10 months ago) by guez
Original Path: trunk/libf/phylmd/diagphy.f90
File size: 4839 byte(s)
NaN to signalling NaN in gfortran_debug.mk.

Removed unused procedures in getincom and getincom2. In procedure
conf_interface, replaced call to getincom by new namelist. Moved
procedure conf_interface into module interface_surf.

Added variables sig1 and w01 to startphy.nc and restartphy.nc, for
procedure cv_driver. Renamed (ema_)?work1 and (ema_)?work2 to sig1 and
w01 in concvl and physiq.

Deleted unused arguments of clmain, clqh and intersurf_hq, among which
(y)?sollwdown. Following LMDZ, in physiq, read sollw instead of
sollwdown from startphy.nc, write sollw instead of sollwdown to
restartphy.nc.

In procedure sw, initialized zfs[ud][pn]a[di], for runs where ok_ade
and ok_aie are false. (Following LMDZ.)

Added dimension klev to startphy.nc and restartphy.nc, and deleted
dimension horizon_vertical. Made t_ancien and q_ancien two-dimensional
NetCDF variables. Bug fix: in phyetat0, define ratqs, clwcon and
rnebcon for vertical levels >=2.

Bug fix: set mfg, p[de]n_[ud] to 0. when iflag_con >= 3. (Following LMDZ.)

1 guez 62 module diagphy_m
2 guez 3
3 guez 62 implicit none
4 guez 3
5 guez 62 contains
6 guez 3
7 guez 62 SUBROUTINE diagphy(airephy, tit, iprt, tops, topl, sols, soll, sens, evap, &
8     rain_fall, snow_fall, ts, d_etp_tot, d_qt_tot, d_ec_tot, fs_bound, &
9     fq_bound)
10 guez 3
11 guez 62 ! From LMDZ4/libf/phylmd/diagphy.F, version 1.1.1.1 2004/05/19 12:53:08
12    
13     ! Purpose: compute the thermal flux and the water mass flux at
14     ! the atmospheric boundaries. Print them and print the atmospheric
15     ! enthalpy change and the atmospheric mass change.
16    
17     ! J.-L. Dufresne, July 2002
18    
19     USE dimphy, ONLY: klon
20     USE suphec_m, ONLY: rcpd, rcpv, rcs, rcw, rlstt, rlvtt
21    
22     ! Arguments:
23 guez 72
24     ! Input variables
25     real airephy(klon)
26 guez 62 ! airephy-------input-R- grid area
27 guez 72 CHARACTER(len=15) tit
28 guez 62 ! tit---------input-A15- Comment to be added in PRINT (CHARACTER*15)
29 guez 72 INTEGER iprt
30 guez 62 ! iprt--------input-I- PRINT level (<=0 : no PRINT)
31 guez 72 real tops(klon), sols(klon)
32 guez 62 ! tops(klon)--input-R- SW rad. at TOA (W/m2), positive up.
33     ! sols(klon)--input-R- Net SW flux above surface (W/m2), positive up
34     ! (i.e. -1 * flux absorbed by the surface)
35    
36 guez 72 real, intent(in):: soll(klon)
37     ! net longwave flux above surface (W/m2), positive up (i. e. flux emited
38     ! - flux absorbed by the surface)
39    
40 guez 62 real, intent(in):: topl(klon) !LW rad. at TOA (W/m2), positive down
41     real sens(klon)
42     ! sens(klon)--input-R- Sensible Flux at surface (W/m2), positive down
43     real evap(klon)
44     ! evap(klon)--input-R- Evaporation + sublimation water vapour mass flux
45     ! (kg/m2/s), positive up
46    
47     real, intent(in):: rain_fall(klon)
48     ! liquid water mass flux (kg/m2/s), positive down
49    
50     real snow_fall(klon)
51     ! snow_fall(klon)
52     ! --input-R- Solid water mass flux (kg/m2/s), positive down
53     REAL ts(klon)
54 guez 72 ! ts(klon)----input-R- Surface temperature (K)
55 guez 62 REAL d_etp_tot, d_qt_tot, d_ec_tot
56 guez 72 ! d_etp_tot---input-R- Heat flux equivalent to atmospheric enthalpy
57     ! change (W/m2)
58     ! d_qt_tot----input-R- Mass flux equivalent to atmospheric water mass
59     ! change (kg/m2/s)
60     ! d_ec_tot----input-R- Flux equivalent to atmospheric cinetic energy
61     ! change (W/m2)
62    
63 guez 62 ! Output variables
64 guez 72 REAL fs_bound
65     ! fs_bound---output-R- Thermal flux at the atmosphere boundaries (W/m2)
66     real fq_bound
67     ! fq_bound---output-R- Water mass flux at the atmosphere
68     ! boundaries (kg/m2/s)
69 guez 62
70 guez 72 ! Local variables:
71    
72 guez 62 real stops, stopl, ssols, ssoll
73     real ssens, sfront, slat
74     real airetot, zcpvap, zcwat, zcice
75     REAL rain_fall_tot, snow_fall_tot, evap_tot
76    
77     integer i
78     integer:: pas = 0
79    
80     !------------------------------------------------------------------
81    
82     pas=pas+1
83     stops=0.
84     stopl=0.
85     ssols=0.
86     ssoll=0.
87     ssens=0.
88     sfront = 0.
89     evap_tot = 0.
90     rain_fall_tot = 0.
91     snow_fall_tot = 0.
92     airetot=0.
93    
94     ! Pour les chaleur specifiques de la vapeur d'eau, de l'eau et de
95     ! la glace, on travaille par difference a la chaleur specifique de
96     ! l' air sec. En effet, comme on travaille a niveau de pression
97     ! donne, toute variation de la masse d'un constituant est
98     ! totalement compense par une variation de masse d'air.
99    
100     zcpvap=RCPV-RCPD
101     zcwat=RCW-RCPD
102     zcice=RCS-RCPD
103    
104     do i=1, klon
105     stops=stops+tops(i)*airephy(i)
106     stopl=stopl+topl(i)*airephy(i)
107     ssols=ssols+sols(i)*airephy(i)
108     ssoll=ssoll+soll(i)*airephy(i)
109     ssens=ssens+sens(i)*airephy(i)
110     sfront = sfront &
111     + (evap(i)*zcpvap-rain_fall(i)*zcwat-snow_fall(i)*zcice) * ts(i) &
112     * airephy(i)
113     evap_tot = evap_tot + evap(i)*airephy(i)
114     rain_fall_tot = rain_fall_tot + rain_fall(i)*airephy(i)
115     snow_fall_tot = snow_fall_tot + snow_fall(i)*airephy(i)
116     airetot=airetot+airephy(i)
117     enddo
118     stops=stops/airetot
119     stopl=stopl/airetot
120     ssols=ssols/airetot
121     ssoll=ssoll/airetot
122     ssens=ssens/airetot
123     sfront = sfront/airetot
124     evap_tot = evap_tot /airetot
125     rain_fall_tot = rain_fall_tot/airetot
126     snow_fall_tot = snow_fall_tot/airetot
127    
128     slat = RLVTT * rain_fall_tot + RLSTT * snow_fall_tot
129     ! Heat flux at atm. boundaries
130     fs_bound = stops-stopl - (ssols+ssoll)+ssens+sfront + slat
131     ! Water flux at atm. boundaries
132     fq_bound = evap_tot - rain_fall_tot -snow_fall_tot
133    
134     IF (iprt >= 1) print 6666, tit, pas, fs_bound, d_etp_tot, fq_bound, d_qt_tot
135    
136     IF (iprt >= 1) print 6668, tit, pas, d_etp_tot+d_ec_tot-fs_bound, &
137     d_qt_tot-fq_bound
138    
139     IF (iprt >= 2) print 6667, tit, pas, stops, stopl, ssols, ssoll, ssens, &
140     slat, evap_tot, rain_fall_tot+snow_fall_tot
141    
142     6666 format('Phys. Flux Budget ', a15, 1i6, 2f8.2, 2(1pE13.5))
143     6667 format('Phys. Boundary Flux ', a15, 1i6, 6f8.2, 2(1pE13.5))
144     6668 format('Phys. Total Budget ', a15, 1i6, f8.2, 2(1pE13.5))
145    
146     end SUBROUTINE diagphy
147    
148     end module diagphy_m

  ViewVC Help
Powered by ViewVC 1.1.21