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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 98 - (hide annotations)
Tue May 13 17:23:16 2014 UTC (10 years ago) by guez
Original Path: trunk/phylmd/diagphy.f
File size: 4672 byte(s)
Split inter_barxy.f : one procedure per module, one module per
file. Grouped the files into a directory.

Split orbite.f.

Value of raz_date read from the namelist is taken into account
(resetting the step counter) even if annee_ref == anneeref and day_ref
== dayref. raz_date is no longer modified by gcm main unit. (Following
LMDZ.)

Removed argument klon of interfsur_lim. Renamed arguments lmt_alb,
lmt_rug to alb_new, z0_new (same name as corresponding actual
arguments in interfsurf_hq).

Removed argument klon of interfsurf_hq.

Removed arguments qs and d_qs of diagetpq. Were always
zero. Downgraded arguments d_qw, d_ql of diagetpq to local variables,
they were not used in physiq. Removed all computations for solid water
in diagetpq, was just zero.


Downgraded arguments fs_bound, fq_bound of diagphy to local variables,
they were not used in physiq. Encapsulated in a test on iprt all
computations in diagphy.

Removed parameter nbtr of module dimphy. Replaced it everywhere in the
program by nqmx - 2.

Removed parameter rnpb of procedure physiq. Kept the true case in
physiq and phytrac. Could not work with false case anyway.

Removed arguments klon, llm, airephy of qcheck. Removed argument ftsol
of initrrnpb, was not used.

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

  ViewVC Help
Powered by ViewVC 1.1.21