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

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

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

trunk/libf/phylmd/diagphy.f revision 38 by guez, Thu Jan 6 17:52:19 2011 UTC trunk/libf/phylmd/diagphy.f90 revision 72 by guez, Tue Jul 23 13:00:07 2013 UTC
# Line 1  Line 1 
1  !  module diagphy_m
2  ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/diagphy.F,v 1.1.1.1 2004/05/19 12:53:08 lmdzadmin Exp $  
3  !    implicit none
4        SUBROUTINE diagphy(airephy,tit,iprt  
5       $    , tops, topl, sols, soll, sens  contains
6       $    , evap, rain_fall, snow_fall, ts  
7       $    , d_etp_tot, d_qt_tot, d_ec_tot    SUBROUTINE diagphy(airephy, tit, iprt, tops, topl, sols, soll, sens, evap, &
8       $    , fs_bound, fq_bound)         rain_fall, snow_fall, ts, d_etp_tot, d_qt_tot, d_ec_tot, fs_bound, &
9  C======================================================================         fq_bound)
10  C  
11  C Purpose:      ! From LMDZ4/libf/phylmd/diagphy.F, version 1.1.1.1 2004/05/19 12:53:08
12  C    Compute the thermal flux and the watter mass flux at the atmosphere  
13  c    boundaries. Print them and also the atmospheric enthalpy change and      ! Purpose: compute the thermal flux and the water mass flux at
14  C    the  atmospheric mass change.      ! the atmospheric boundaries. Print them and print the atmospheric
15  C      ! enthalpy change and the atmospheric mass change.
16  C Arguments:  
17  C airephy-------input-R-  grid area      ! J.-L. Dufresne, July 2002
18  C tit---------input-A15- Comment to be added in PRINT (CHARACTER*15)  
19  C iprt--------input-I-  PRINT level ( <=0 : no PRINT)      USE dimphy, ONLY: klon
20  C tops(klon)--input-R-  SW rad. at TOA (W/m2), positive up.      USE suphec_m, ONLY: rcpd, rcpv, rcs, rcw, rlstt, rlvtt
21  C topl(klon)--input-R-  LW rad. at TOA (W/m2), positive down  
22  C sols(klon)--input-R-  Net SW flux above surface (W/m2), positive up      ! Arguments:
23  C                   (i.e. -1 * flux absorbed by the surface)  
24  C soll(klon)--input-R-  Net LW flux above surface (W/m2), positive up      ! Input variables
25  C                   (i.e. flux emited - flux absorbed by the surface)      real airephy(klon)
26  C sens(klon)--input-R-  Sensible Flux at surface  (W/m2), positive down      ! airephy-------input-R- grid area
27  C evap(klon)--input-R-  Evaporation + sublimation watter vapour mass flux      CHARACTER(len=15) tit
28  C                   (kg/m2/s), positive up      ! tit---------input-A15- Comment to be added in PRINT (CHARACTER*15)
29  C rain_fall(klon)      INTEGER iprt
30  C           --input-R- Liquid  watter mass flux (kg/m2/s), positive down      ! iprt--------input-I- PRINT level (<=0 : no PRINT)
31  C snow_fall(klon)      real tops(klon), sols(klon)
32  C           --input-R- Solid  watter mass flux (kg/m2/s), positive down      ! tops(klon)--input-R- SW rad. at TOA (W/m2), positive up.
33  C ts(klon)----input-R- Surface temperature (K)      ! sols(klon)--input-R- Net SW flux above surface (W/m2), positive up
34  C d_etp_tot---input-R- Heat flux equivalent to atmospheric enthalpy      ! (i.e. -1 * flux absorbed by the surface)
35  C                    change (W/m2)  
36  C d_qt_tot----input-R- Mass flux equivalent to atmospheric watter mass      real, intent(in):: soll(klon)
37  C                    change (kg/m2/s)      ! net longwave flux above surface (W/m2), positive up (i. e. flux emited
38  C d_ec_tot----input-R- Flux equivalent to atmospheric cinetic energy      ! - flux absorbed by the surface)
39  C                    change (W/m2)  
40  C      real, intent(in):: topl(klon) !LW rad. at TOA (W/m2), positive down
41  C fs_bound---output-R- Thermal flux at the atmosphere boundaries (W/m2)      real sens(klon)
42  C fq_bound---output-R- Watter mass flux at the atmosphere boundaries (kg/m2/s)      ! sens(klon)--input-R- Sensible Flux at surface (W/m2), positive down
43  C      real evap(klon)
44  C J.L. Dufresne, July 2002      ! evap(klon)--input-R- Evaporation + sublimation water vapour mass flux
45  C======================================================================      ! (kg/m2/s), positive up
46  C  
47        use dimens_m      real, intent(in):: rain_fall(klon)
48        use dimphy      ! liquid water mass flux (kg/m2/s), positive down
49        use SUPHEC_M  
50        use yoethf_m      real snow_fall(klon)
51        implicit none      ! snow_fall(klon)
52        ! --input-R- Solid water mass flux (kg/m2/s), positive down
53  C      REAL ts(klon)
54  C     Input variables      ! ts(klon)----input-R- Surface temperature (K)
55        real airephy(klon)      REAL d_etp_tot, d_qt_tot, d_ec_tot
56        CHARACTER*15 tit      ! d_etp_tot---input-R- Heat flux equivalent to atmospheric enthalpy
57        INTEGER iprt      ! change (W/m2)
58        real tops(klon),topl(klon),sols(klon),soll(klon)      ! d_qt_tot----input-R- Mass flux equivalent to atmospheric water mass
59        real sens(klon),evap(klon),rain_fall(klon),snow_fall(klon)      ! change (kg/m2/s)
60        REAL ts(klon)      ! d_ec_tot----input-R- Flux equivalent to atmospheric cinetic energy
61        REAL d_etp_tot, d_qt_tot, d_ec_tot      ! change (W/m2)
62  c     Output variables  
63        REAL fs_bound, fq_bound      ! Output variables
64  C      REAL fs_bound
65  C     Local variables      ! fs_bound---output-R- Thermal flux at the atmosphere boundaries (W/m2)
66        real stops,stopl,ssols,ssoll      real fq_bound
67        real ssens,sfront,slat      ! fq_bound---output-R- Water mass flux at the atmosphere
68        real airetot, zcpvap, zcwat, zcice      ! boundaries (kg/m2/s)
69        REAL rain_fall_tot, snow_fall_tot, evap_tot  
70  C      ! Local variables:
71        integer i  
72  C      real stops, stopl, ssols, ssoll
73        integer pas      real ssens, sfront, slat
74        save pas      real airetot, zcpvap, zcwat, zcice
75        data pas/0/      REAL rain_fall_tot, snow_fall_tot, evap_tot
76  C  
77        pas=pas+1      integer i
78        stops=0.      integer:: pas = 0
79        stopl=0.  
80        ssols=0.      !------------------------------------------------------------------
81        ssoll=0.  
82        ssens=0.      pas=pas+1
83        sfront = 0.      stops=0.
84        evap_tot = 0.      stopl=0.
85        rain_fall_tot = 0.      ssols=0.
86        snow_fall_tot = 0.      ssoll=0.
87        airetot=0.      ssens=0.
88  C      sfront = 0.
89  C     Pour les chaleur specifiques de la vapeur d'eau, de l'eau et de      evap_tot = 0.
90  C     la glace, on travaille par difference a la chaleur specifique de l'      rain_fall_tot = 0.
91  c     air sec. En effet, comme on travaille a niveau de pression donne,      snow_fall_tot = 0.
92  C     toute variation de la masse d'un constituant est totalement      airetot=0.
93  c     compense par une variation de masse d'air.  
94  C      ! Pour les chaleur specifiques de la vapeur d'eau, de l'eau et de
95        zcpvap=RCPV-RCPD      ! la glace, on travaille par difference a la chaleur specifique de
96        zcwat=RCW-RCPD      ! l' air sec. En effet, comme on travaille a niveau de pression
97        zcice=RCS-RCPD      ! donne, toute variation de la masse d'un constituant est
98  C      ! totalement compense par une variation de masse d'air.
99        do i=1,klon  
100             stops=stops+tops(i)*airephy(i)      zcpvap=RCPV-RCPD
101             stopl=stopl+topl(i)*airephy(i)      zcwat=RCW-RCPD
102             ssols=ssols+sols(i)*airephy(i)      zcice=RCS-RCPD
103             ssoll=ssoll+soll(i)*airephy(i)  
104             ssens=ssens+sens(i)*airephy(i)      do i=1, klon
105             sfront = sfront         stops=stops+tops(i)*airephy(i)
106       $         + ( evap(i)*zcpvap-rain_fall(i)*zcwat-snow_fall(i)*zcice         stopl=stopl+topl(i)*airephy(i)
107       $           ) *ts(i) *airephy(i)         ssols=ssols+sols(i)*airephy(i)
108             evap_tot = evap_tot + evap(i)*airephy(i)         ssoll=ssoll+soll(i)*airephy(i)
109             rain_fall_tot = rain_fall_tot + rain_fall(i)*airephy(i)         ssens=ssens+sens(i)*airephy(i)
110             snow_fall_tot = snow_fall_tot + snow_fall(i)*airephy(i)         sfront = sfront &
111             airetot=airetot+airephy(i)              + (evap(i)*zcpvap-rain_fall(i)*zcwat-snow_fall(i)*zcice) * ts(i) &
112        enddo              * airephy(i)
113        stops=stops/airetot         evap_tot = evap_tot + evap(i)*airephy(i)
114        stopl=stopl/airetot         rain_fall_tot = rain_fall_tot + rain_fall(i)*airephy(i)
115        ssols=ssols/airetot         snow_fall_tot = snow_fall_tot + snow_fall(i)*airephy(i)
116        ssoll=ssoll/airetot         airetot=airetot+airephy(i)
117        ssens=ssens/airetot      enddo
118        sfront = sfront/airetot      stops=stops/airetot
119        evap_tot = evap_tot /airetot      stopl=stopl/airetot
120        rain_fall_tot = rain_fall_tot/airetot      ssols=ssols/airetot
121        snow_fall_tot = snow_fall_tot/airetot      ssoll=ssoll/airetot
122  C      ssens=ssens/airetot
123        slat = RLVTT * rain_fall_tot + RLSTT * snow_fall_tot      sfront = sfront/airetot
124  C     Heat flux at atm. boundaries      evap_tot = evap_tot /airetot
125        fs_bound = stops-stopl - (ssols+ssoll)+ssens+sfront      rain_fall_tot = rain_fall_tot/airetot
126       $    + slat      snow_fall_tot = snow_fall_tot/airetot
127  C     Watter flux at atm. boundaries  
128        fq_bound = evap_tot - rain_fall_tot -snow_fall_tot      slat = RLVTT * rain_fall_tot + RLSTT * snow_fall_tot
129  C      ! Heat flux at atm. boundaries
130        IF (iprt.ge.1) write(6,6666)      fs_bound = stops-stopl - (ssols+ssoll)+ssens+sfront + slat
131       $    tit, pas, fs_bound, d_etp_tot, fq_bound, d_qt_tot      ! Water flux at atm. boundaries
132  C      fq_bound = evap_tot - rain_fall_tot -snow_fall_tot
133        IF (iprt.ge.1) write(6,6668)  
134       $    tit, pas, d_etp_tot+d_ec_tot-fs_bound, d_qt_tot-fq_bound      IF (iprt >= 1) print 6666, tit, pas, fs_bound, d_etp_tot, fq_bound, d_qt_tot
135  C  
136        IF (iprt.ge.2) write(6,6667)      IF (iprt >= 1) print 6668, tit, pas, d_etp_tot+d_ec_tot-fs_bound, &
137       $    tit, pas, stops,stopl,ssols,ssoll,ssens,slat,evap_tot           d_qt_tot-fq_bound
138       $    ,rain_fall_tot+snow_fall_tot  
139        IF (iprt >= 2) print 6667, tit, pas, stops, stopl, ssols, ssoll, ssens, &
140        return           slat, evap_tot, rain_fall_tot+snow_fall_tot
141    
142   6666 format('Phys. Flux Budget ',a15,1i6,2f8.2,2(1pE13.5))  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))  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))  6668 format('Phys. Total Budget ', a15, 1i6, f8.2, 2(1pE13.5))
145    
146        end    end SUBROUTINE diagphy
147    
148  C======================================================================  end module diagphy_m
       SUBROUTINE diagetpq(airephy,tit,iprt,idiag,idiag2,dtime  
      e  ,t,q,ql,qs,u,v,paprs  
      s  , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec)  
 C======================================================================  
 C  
 C Purpose:  
 C    Calcul la difference d'enthalpie et de masse d'eau entre 2 appels,  
 C    et calcul le flux de chaleur et le flux d'eau necessaire a ces  
 C    changements. Ces valeurs sont moyennees sur la surface de tout  
 C    le globe et sont exprime en W/2 et kg/s/m2  
 C    Outil pour diagnostiquer la conservation de l'energie  
 C    et de la masse dans la physique. Suppose que les niveau de  
 c    pression entre couche ne varie pas entre 2 appels.  
 C  
 C Plusieurs de ces diagnostics peuvent etre fait en parallele: les  
 c bilans sont sauvegardes dans des tableaux indices. On parlera  
 C "d'indice de diagnostic"  
 c  
 C  
 c======================================================================  
 C Arguments:  
 C airephy-------input-R-  grid area  
 C tit-----imput-A15- Comment added in PRINT (CHARACTER*15)  
 C iprt----input-I-  PRINT level ( <=1 : no PRINT)  
 C idiag---input-I- indice dans lequel sera range les nouveaux  
 C                  bilans d' entalpie et de masse  
 C idiag2--input-I-les nouveaux bilans d'entalpie et de masse  
 C                 sont compare au bilan de d'enthalpie de masse de  
 C                 l'indice numero idiag2  
 C                 Cas parriculier : si idiag2=0, pas de comparaison, on  
 c                 sort directement les bilans d'enthalpie et de masse  
 C dtime----input-R- time step (s)  
 c t--------input-R- temperature (K)  
 c q--------input-R- vapeur d'eau (kg/kg)  
 c ql-------input-R- liquid watter (kg/kg)  
 c qs-------input-R- solid watter (kg/kg)  
 c u--------input-R- vitesse u  
 c v--------input-R- vitesse v  
 c paprs----input-R- pression a intercouche (Pa)  
 c  
 C the following total value are computed by UNIT of earth surface  
 C  
 C d_h_vcol--output-R- Heat flux (W/m2) define as the Enthalpy  
 c            change (J/m2) during one time step (dtime) for the whole  
 C            atmosphere (air, watter vapour, liquid and solid)  
 C d_qt------output-R- total water mass flux (kg/m2/s) defined as the  
 C           total watter (kg/m2) change during one time step (dtime),  
 C d_qw------output-R- same, for the watter vapour only (kg/m2/s)  
 C d_ql------output-R- same, for the liquid watter only (kg/m2/s)  
 C d_qs------output-R- same, for the solid watter only (kg/m2/s)  
 C d_ec------output-R- Cinetic Energy Budget (W/m2) for vertical air column  
 C  
 C     other (COMMON...)  
 C     RCPD, RCPV, ....  
 C  
 C J.L. Dufresne, July 2002  
 c======================================================================  
   
       use dimens_m  
       use dimphy  
       use SUPHEC_M  
       use yoethf_m  
       IMPLICIT NONE  
 C  
 C  
 c     Input variables  
       real airephy(klon)  
       CHARACTER*15 tit  
       INTEGER iprt,idiag, idiag2  
       REAL, intent(in):: dtime  
       REAL t(klon,klev), q(klon,klev), ql(klon,klev), qs(klon,klev)  
       REAL u(klon,klev), v(klon,klev)  
       REAL, intent(in):: paprs(klon,klev+1)  
 c     Output variables  
       REAL d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec  
 C  
 C     Local variables  
 c  
       REAL h_vcol_tot, h_dair_tot, h_qw_tot, h_ql_tot  
      .  , h_qs_tot, qw_tot, ql_tot, qs_tot , ec_tot  
 c h_vcol_tot--  total enthalpy of vertical air column  
 C            (air with watter vapour, liquid and solid) (J/m2)  
 c h_dair_tot-- total enthalpy of dry air (J/m2)  
 c h_qw_tot----  total enthalpy of watter vapour (J/m2)  
 c h_ql_tot----  total enthalpy of liquid watter (J/m2)  
 c h_qs_tot----  total enthalpy of solid watter  (J/m2)  
 c qw_tot------  total mass of watter vapour (kg/m2)  
 c ql_tot------  total mass of liquid watter (kg/m2)  
 c qs_tot------  total mass of solid watter (kg/m2)  
 c ec_tot------  total cinetic energy (kg/m2)  
 C  
       REAL zairm(klon,klev) ! layer air mass (kg/m2)  
       REAL  zqw_col(klon)  
       REAL  zql_col(klon)  
       REAL  zqs_col(klon)  
       REAL  zec_col(klon)  
       REAL  zh_dair_col(klon)  
       REAL  zh_qw_col(klon), zh_ql_col(klon), zh_qs_col(klon)  
 C  
       REAL      d_h_dair, d_h_qw, d_h_ql, d_h_qs  
 C  
       REAL airetot, zcpvap, zcwat, zcice  
 C  
       INTEGER i, k  
 C  
       INTEGER ndiag     ! max number of diagnostic in parallel  
       PARAMETER (ndiag=10)  
       integer pas(ndiag)  
       save pas  
       data pas/ndiag*0/  
 C      
       REAL      h_vcol_pre(ndiag), h_dair_pre(ndiag), h_qw_pre(ndiag)  
      $    , h_ql_pre(ndiag), h_qs_pre(ndiag), qw_pre(ndiag)  
      $    , ql_pre(ndiag), qs_pre(ndiag) , ec_pre(ndiag)  
       SAVE      h_vcol_pre, h_dair_pre, h_qw_pre, h_ql_pre  
      $        , h_qs_pre, qw_pre, ql_pre, qs_pre , ec_pre  
   
 c======================================================================  
 C  
       DO k = 1, klev  
         DO i = 1, klon  
 C         layer air mass  
           zairm(i,k) = (paprs(i,k)-paprs(i,k+1))/RG  
         ENDDO  
       END DO  
 C  
 C     Reset variables  
       DO i = 1, klon  
         zqw_col(i)=0.  
         zql_col(i)=0.  
         zqs_col(i)=0.  
         zec_col(i) = 0.  
         zh_dair_col(i) = 0.  
         zh_qw_col(i) = 0.  
         zh_ql_col(i) = 0.  
         zh_qs_col(i) = 0.  
       ENDDO  
 C  
       zcpvap=RCPV  
       zcwat=RCW  
       zcice=RCS  
 C  
 C     Compute vertical sum for each atmospheric column  
 C     ================================================  
       DO k = 1, klev  
         DO i = 1, klon  
 C         Watter mass  
           zqw_col(i) = zqw_col(i) + q(i,k)*zairm(i,k)  
           zql_col(i) = zql_col(i) + ql(i,k)*zairm(i,k)  
           zqs_col(i) = zqs_col(i) + qs(i,k)*zairm(i,k)  
 C         Cinetic Energy  
           zec_col(i) =  zec_col(i)  
      $        +0.5*(u(i,k)**2+v(i,k)**2)*zairm(i,k)  
 C         Air enthalpy  
           zh_dair_col(i) = zh_dair_col(i)  
      $        + RCPD*(1.-q(i,k)-ql(i,k)-qs(i,k))*zairm(i,k)*t(i,k)  
           zh_qw_col(i) = zh_qw_col(i)  
      $        + zcpvap*q(i,k)*zairm(i,k)*t(i,k)  
           zh_ql_col(i) = zh_ql_col(i)  
      $        + zcwat*ql(i,k)*zairm(i,k)*t(i,k)  
      $        - RLVTT*ql(i,k)*zairm(i,k)  
           zh_qs_col(i) = zh_qs_col(i)  
      $        + zcice*qs(i,k)*zairm(i,k)*t(i,k)  
      $        - RLSTT*qs(i,k)*zairm(i,k)  
   
         END DO  
       ENDDO  
 C  
 C     Mean over the planete surface  
 C     =============================  
       qw_tot = 0.  
       ql_tot = 0.  
       qs_tot = 0.  
       ec_tot = 0.  
       h_vcol_tot = 0.  
       h_dair_tot = 0.  
       h_qw_tot = 0.  
       h_ql_tot = 0.  
       h_qs_tot = 0.  
       airetot=0.  
 C  
       do i=1,klon  
         qw_tot = qw_tot + zqw_col(i)*airephy(i)  
         ql_tot = ql_tot + zql_col(i)*airephy(i)  
         qs_tot = qs_tot + zqs_col(i)*airephy(i)  
         ec_tot = ec_tot + zec_col(i)*airephy(i)  
         h_dair_tot = h_dair_tot + zh_dair_col(i)*airephy(i)  
         h_qw_tot = h_qw_tot + zh_qw_col(i)*airephy(i)  
         h_ql_tot = h_ql_tot + zh_ql_col(i)*airephy(i)  
         h_qs_tot = h_qs_tot + zh_qs_col(i)*airephy(i)  
         airetot=airetot+airephy(i)  
       END DO  
 C  
       qw_tot = qw_tot/airetot  
       ql_tot = ql_tot/airetot  
       qs_tot = qs_tot/airetot  
       ec_tot = ec_tot/airetot  
       h_dair_tot = h_dair_tot/airetot  
       h_qw_tot = h_qw_tot/airetot  
       h_ql_tot = h_ql_tot/airetot  
       h_qs_tot = h_qs_tot/airetot  
 C  
       h_vcol_tot = h_dair_tot+h_qw_tot+h_ql_tot+h_qs_tot  
 C  
 C     Compute the change of the atmospheric state compare to the one  
 C     stored in "idiag2", and convert it in flux. THis computation  
 C     is performed IF idiag2 /= 0 and IF it is not the first CALL  
 c     for "idiag"  
 C     ===================================  
 C  
       IF ( (idiag2.gt.0) .and. (pas(idiag2) .ne. 0) ) THEN  
         d_h_vcol  = (h_vcol_tot - h_vcol_pre(idiag2) )/dtime  
         d_h_dair = (h_dair_tot- h_dair_pre(idiag2))/dtime  
         d_h_qw   = (h_qw_tot  - h_qw_pre(idiag2)  )/dtime  
         d_h_ql   = (h_ql_tot  - h_ql_pre(idiag2)  )/dtime  
         d_h_qs   = (h_qs_tot  - h_qs_pre(idiag2)  )/dtime  
         d_qw     = (qw_tot    - qw_pre(idiag2)    )/dtime  
         d_ql     = (ql_tot    - ql_pre(idiag2)    )/dtime  
         d_qs     = (qs_tot    - qs_pre(idiag2)    )/dtime  
         d_ec     = (ec_tot    - ec_pre(idiag2)    )/dtime  
         d_qt = d_qw + d_ql + d_qs  
       ELSE  
         d_h_vcol = 0.  
         d_h_dair = 0.  
         d_h_qw   = 0.  
         d_h_ql   = 0.  
         d_h_qs   = 0.  
         d_qw     = 0.  
         d_ql     = 0.  
         d_qs     = 0.  
         d_ec     = 0.  
         d_qt     = 0.  
       ENDIF  
 C  
       IF (iprt.ge.2) THEN  
         WRITE(6,9000) tit,pas(idiag),d_qt,d_qw,d_ql,d_qs  
  9000   format('Phys. Watter Mass Budget (kg/m2/s)',A15  
      $      ,1i6,10(1pE14.6))  
         WRITE(6,9001) tit,pas(idiag), d_h_vcol  
  9001   format('Phys. Enthalpy Budget (W/m2) ',A15,1i6,10(F8.2))  
         WRITE(6,9002) tit,pas(idiag), d_ec  
  9002   format('Phys. Cinetic Energy Budget (W/m2) ',A15,1i6,10(F8.2))  
       END IF  
 C  
 C     Store the new atmospheric state in "idiag"  
 C  
       pas(idiag)=pas(idiag)+1  
       h_vcol_pre(idiag)  = h_vcol_tot  
       h_dair_pre(idiag) = h_dair_tot  
       h_qw_pre(idiag)   = h_qw_tot  
       h_ql_pre(idiag)   = h_ql_tot  
       h_qs_pre(idiag)   = h_qs_tot  
       qw_pre(idiag)     = qw_tot  
       ql_pre(idiag)     = ql_tot  
       qs_pre(idiag)     = qs_tot  
       ec_pre (idiag)    = ec_tot  
 C  
       RETURN  
       END  

Legend:
Removed from v.38  
changed lines
  Added in v.72

  ViewVC Help
Powered by ViewVC 1.1.21