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

Diff of /trunk/phylmd/diagphy.f

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

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

Legend:
Removed from v.62  
changed lines
  Added in v.98

  ViewVC Help
Powered by ViewVC 1.1.21