source: trunk/LMDZ.GENERIC/libf/phystd/sfluxi.F @ 601

Last change on this file since 601 was 600, checked in by jleconte, 13 years ago
  • Corrects the computation of planck function at the surface in sfluxi

so that its integral is equal to sigma Tsurf4.

  • This ensure that no flux is lost due to:

-truncation of the planck function at high/low wavenumber
-numerical error during first spectral computation of the planck function
-discrepancy between Tsurf and NTS/NTfac in sfluxi

  • OLR now equal to LW net heating/cooling at equilibrium!
  • As much as possible, only the value of the stephan boltzmann constant defined in racommon_h (and the

corresponding variable, sigma) should be used. Now done in physics, vdifc and turbdiff.

File size: 6.1 KB
Line 
1      SUBROUTINE SFLUXI(PLEV,TLEV,DTAUI,TAUCUMI,UBARI,RSFI,WNOI,DWNI,
2     *                  COSBI,WBARI,GWEIGHT,NFLUXTOPI,NFLUXTOPI_nu,
3     *                  FMNETI,fluxupi,fluxdni,fluxupi_nu,
4     *                  FZEROI,TAUGSURF)
5
6      use radinc_h
7      use radcommon_h, only: planckir, tlimit,sigma
8
9      implicit none
10
11#include "comcstfi.h"
12
13      integer NLEVRAD, L, NW, NG, NTS, NTT
14
15      real*8 TLEV(L_LEVELS), PLEV(L_LEVELS)
16      real*8 TAUCUMI(L_LEVELS,L_NSPECTI,L_NGAUSS)
17      real*8 FMNETI(L_NLAYRAD)
18      real*8 WNOI(L_NSPECTI), DWNI(L_NSPECTI)
19      real*8 DTAUI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
20      real*8 FMUPI(L_NLEVRAD), FMDI(L_NLEVRAD)
21      real*8 COSBI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
22      real*8 WBARI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
23      real*8 GWEIGHT(L_NGAUSS), NFLUXTOPI
24      real*8 NFLUXTOPI_nu(L_NSPECTI)
25      real*8 fluxupi_nu(L_NLAYRAD,L_NSPECTI)
26      real*8 FTOPUP
27
28      real*8 UBARI, RSFI, TSURF, BSURF, TTOP, BTOP, TAUTOP
29      real*8 PLANCK, PLTOP
30      real*8 fluxupi(L_NLAYRAD), fluxdni(L_NLAYRAD)
31      real*8 FZEROI(L_NSPECTI)
32      real*8 taugsurf(L_NSPECTI,L_NGAUSS-1), fzero
33
34      real*8 fup_tmp(L_NSPECTI),fdn_tmp(L_NSPECTI)
35      real*8 PLANCKSUM,PLANCKREF
36
37
38C======================================================================C
39 
40      NLEVRAD = L_NLEVRAD
41 
42
43C     ZERO THE NET FLUXES
44   
45      NFLUXTOPI = 0.0
46
47      DO NW=1,L_NSPECTI
48        NFLUXTOPI_nu(NW) = 0.0
49        DO L=1,L_NLAYRAD
50           FLUXUPI_nu(L,NW) = 0.0
51
52              fup_tmp(nw)=0.0
53              fdn_tmp(nw)=0.0
54
55        END DO
56      END DO
57
58      DO L=1,L_NLAYRAD
59        FMNETI(L)  = 0.0
60        FLUXUPI(L) = 0.0
61        FLUXDNI(L) = 0.0
62      END DO
63 
64C     WE NOW ENTER A MAJOR LOOP OVER SPECTRAL INTERVALS IN THE INFRARED
65C     TO CALCULATE THE NET FLUX IN EACH SPECTRAL INTERVAL
66
67      TTOP  = TLEV(2)  ! JL12 why not (1) ???
68      TSURF = TLEV(L_LEVELS)
69
70      NTS   = int(TSURF*NTfac)-NTstar+1
71      NTT   = int(TTOP *NTfac)-NTstar+1
72!      NTS   = TSURF*10.0D0-499
73!      NTT   = TTOP *10.0D0-499
74
75!JL12 corrects the surface planck function so that its integral is equal to sigma Tsurf^4
76!JL12   this ensure that no flux is lost due to:
77!JL12          -truncation of the planck function at high/low wavenumber
78!JL12          -numerical error during first spectral integration
79!JL12          -discrepancy between Tsurf and NTS/NTfac
80      PLANCKSUM=0.d0
81      PLANCKREF=TSURF*TSURF
82      PLANCKREF=sigma*PLANCKREF*PLANCKREF
83      DO NW=1,L_NSPECTI
84         PLANCKSUM=PLANCKSUM+PLANCKIR(NW,NTS)*DWNI(NW)
85      ENDDO
86      PLANCKSUM=PLANCKREF/(PLANCKSUM*Pi)
87!JL12
88
89      DO 501 NW=1,L_NSPECTI
90
91C       SURFACE EMISSIONS - INDEPENDENT OF GAUSS POINTS
92        BSURF = (1.-RSFI)*PLANCKIR(NW,NTS)*PLANCKSUM !JL12 plancksum see above
93        PLTOP = PLANCKIR(NW,NTT)
94
95C  If FZEROI(NW) = 1, then the k-coefficients are zero - skip to the
96C  special Gauss point at the end.
97 
98        FZERO = FZEROI(NW)
99        IF(FZERO.ge.0.99) goto 40
100 
101        DO NG=1,L_NGAUSS-1
102         
103          if(TAUGSURF(NW,NG).lt. TLIMIT) then
104            fzero = fzero + (1.0-FZEROI(NW))*GWEIGHT(NG)
105            goto 30
106          end if
107
108C         SET UP THE UPPER AND LOWER BOUNDARY CONDITIONS ON THE IR
109C         CALCULATE THE DOWNWELLING RADIATION AT THE TOP OF THE MODEL
110C         OR THE TOP LAYER WILL COOL TO SPACE UNPHYSICALLY
111 
112          TAUTOP = DTAUI(1,NW,NG)*PLEV(2)/(PLEV(4)-PLEV(2))
113          BTOP   = (1.0-EXP(-TAUTOP/UBARI))*PLTOP
114 
115C         WE CAN NOW SOLVE FOR THE COEFFICIENTS OF THE TWO STREAM
116C         CALL A SUBROUTINE THAT SOLVES  FOR THE FLUX TERMS
117C         WITHIN EACH INTERVAL AT THE MIDPOINT WAVENUMBER
118         
119          CALL GFLUXI(NLEVRAD,TLEV,NW,DWNI(NW),DTAUI(1,NW,NG),
120     *                TAUCUMI(1,NW,NG),
121     *                WBARI(1,NW,NG),COSBI(1,NW,NG),UBARI,RSFI,BTOP,
122     *                BSURF,FTOPUP,FMUPI,FMDI)
123
124
125
126C         NOW CALCULATE THE CUMULATIVE IR NET FLUX
127
128          NFLUXTOPI = NFLUXTOPI+FTOPUP*DWNI(NW)*GWEIGHT(NG)*
129     *                           (1.0-FZEROI(NW))
130
131c         and same thing by spectral band... (RDW)
132          NFLUXTOPI_nu(NW) = NFLUXTOPI_nu(NW)
133     *      +FTOPUP*DWNI(NW)*GWEIGHT(NG)*(1.0-FZEROI(NW))
134
135
136          DO L=1,L_NLEVRAD-1
137
138C           CORRECT FOR THE WAVENUMBER INTERVALS
139
140            FMNETI(L)  = FMNETI(L)+(FMUPI(L)-FMDI(L))*DWNI(NW)*
141     *                              GWEIGHT(NG)*(1.0-FZEROI(NW))
142            FLUXUPI(L) = FLUXUPI(L) + FMUPI(L)*DWNI(NW)*GWEIGHT(NG)*
143     *                                (1.0-FZEROI(NW))
144            FLUXDNI(L) = FLUXDNI(L) + FMDI(L)*DWNI(NW)*GWEIGHT(NG)*
145     *                                (1.0-FZEROI(NW))
146
147c         and same thing by spectral band... (RW)
148            FLUXUPI_nu(L,NW) = FLUXUPI_nu(L,NW) +
149     *                FMUPI(L)*DWNI(NW)*GWEIGHT(NG)*(1.0-FZEROI(NW))
150
151          END DO
152
153   30     CONTINUE
154
155       END DO       !End NGAUSS LOOP
156
157   40  CONTINUE
158
159C      SPECIAL 17th Gauss point
160
161       NG     = L_NGAUSS
162
163       TAUTOP = DTAUI(1,NW,NG)*PLEV(2)/(PLEV(4)-PLEV(2))
164       BTOP   = (1.0-EXP(-TAUTOP/UBARI))*PLTOP
165
166C      WE CAN NOW SOLVE FOR THE COEFFICIENTS OF THE TWO STREAM
167C      CALL A SUBROUTINE THAT SOLVES  FOR THE FLUX TERMS
168C      WITHIN EACH INTERVAL AT THE MIDPOINT WAVENUMBER
169
170
171       CALL GFLUXI(NLEVRAD,TLEV,NW,DWNI(NW),DTAUI(1,NW,NG),
172     *                TAUCUMI(1,NW,NG),
173     *                WBARI(1,NW,NG),COSBI(1,NW,NG),UBARI,RSFI,BTOP,
174     *                BSURF,FTOPUP,FMUPI,FMDI)
175 
176C      NOW CALCULATE THE CUMULATIVE IR NET FLUX
177
178       NFLUXTOPI = NFLUXTOPI+FTOPUP*DWNI(NW)*FZERO
179
180c         and same thing by spectral band... (RW)
181          NFLUXTOPI_nu(NW) = NFLUXTOPI_nu(NW)
182     *      +FTOPUP*DWNI(NW)*FZERO
183
184       DO L=1,L_NLEVRAD-1
185
186C        CORRECT FOR THE WAVENUMBER INTERVALS
187
188         FMNETI(L)  = FMNETI(L)+(FMUPI(L)-FMDI(L))*DWNI(NW)*FZERO
189         FLUXUPI(L) = FLUXUPI(L) + FMUPI(L)*DWNI(NW)*FZERO
190         FLUXDNI(L) = FLUXDNI(L) + FMDI(L)*DWNI(NW)*FZERO
191
192c         and same thing by spectral band... (RW)
193         FLUXUPI_nu(L,NW) = FLUXUPI_nu(L,NW) + FMUPI(L)*DWNI(NW)*FZERO
194
195       END DO
196
197  501 CONTINUE      !End Spectral Interval LOOP
198
199C *** END OF MAJOR SPECTRAL INTERVAL LOOP IN THE INFRARED****
200
201      RETURN
202      END
Note: See TracBrowser for help on using the repository browser.