source: trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_rh.F @ 3885

Last change on this file since 3885 was 3884, checked in by ikovalenko, 4 months ago
File size: 10.2 KB
Line 
1      SUBROUTINE SW_venus_rh(PRMU0, PFRAC, latdeg,
2     S              PPA, PPB, pt,
3     S              PHEAT,
4     S              PTOPSW,PSOLSW,ZFSNET)
5     
6      use dimphy, only: klev
7      use cpdet_phy_mod, only: cpdet
8      use clesphys_mod
9      use YOMCST_mod
10      IMPLICIT none
11
12C      include "YOMCST.h"
13C      include "clesphys.h"
14C
15C     ------------------------------------------------------------------
16C
17C     PURPOSE.
18C     --------
19C
20c      this routine loads and interpolates the shortwave radiation
21c     fluxes taken from Rainer Haus calculations for Venus.
22c     Ref: Haus et al. 2016
23C
24C     AUTHOR.
25C     -------
26C        Sebastien Lebonnois
27C
28C     MODIFICATIONS.
29C     --------------
30C        ORIGINAL : 5/2016
31C     ------------------------------------------------------------------
32C
33C* ARGUMENTS:
34C
35c inputs
36
37      REAL,INTENT(IN) ::   PRMU0  ! COSINE OF ZENITHAL ANGLE
38      REAL,INTENT(IN) ::   PFRAC  ! fraction de la journee
39      REAL,INTENT(IN) ::   latdeg ! |latitude| (in degrees)
40      REAL,INTENT(IN) ::   PPB(klev+1)  ! inter-couches PRESSURE (bar)
41      REAL,INTENT(IN) ::   PPA(klev)
42      REAL,INTENT(IN) ::   pt(klev)     ! mid-layer temperature
43C
44c output
45
46      REAL,INTENT(OUT) ::   PHEAT(klev)  ! SHORTWAVE HEATING (K/s) within each layer
47      REAL   PHEATPPA(klev)
48      REAL,INTENT(OUT) ::   PTOPSW       ! SHORTWAVE FLUX AT T.O.A. (net)
49      REAL,INTENT(OUT) ::   PSOLSW       ! SHORTWAVE FLUX AT SURFACE (net)
50      REAL,INTENT(OUT) ::   ZFSNET(klev+1) ! net solar flux at ppb levels
51
52C
53C* LOCAL VARIABLES:
54C
55      integer nlrh,nszarh,nlatrh
56      parameter (nlrh=118)  ! fichiers Rainer Haus
57      parameter (nszarh=7) ! fichiers Rainer Haus
58      parameter (nlatrh=19) ! fichiers Rainer Haus
59     
60      integer i,j,k,lat,nsza,nsza0(2),nl0,nlat0
61      real   zsnet(nlrh+1,nszarh+1,nlatrh+1)! net solar flux (W/m**2) (+ vers bas)
62      real   solza(nszarh,nlatrh)       ! solar zenith angles in table
63      real   presrh(nlrh+1)             ! pressure in table (bar)
64      real   logplayrh(nlrh)
65      real   altrh(nlrh+1)              ! altitude in table (km)
66      real   latrh(nlatrh)              ! latitude in table (degrees)
67      character*22 nullchar
68      real   sza0,factsza(2),factflux,factlat
69      real   zsnetmoy
70      logical firstcall
71      data    firstcall/.true./
72      save   solza,zsnet,altrh,latrh,presrh
73      save   firstcall
74      real   Tplay(nlrh)
75      real   Qrh1(nlrh)
76      real   Qrh2(nlrh)
77      real   Qrh3(nlrh)
78      real   Qrh4(nlrh)
79     
80c ------------------------
81c Loading the file
82c ------------------------
83      if (firstcall) then
84
85       zsnet=0.
86
87       open(11,file='SolarNetFlux_RH.dat')
88
89       do i=1,nlrh+1
90          read(11,'(E5.1,4x,F8.2)') altrh(i),presrh(i)
91       enddo
92
93       do lat=1,nlatrh
94         latrh(lat)=5.*(lat-1)
95         read(11,*) nullchar
96         read(11,*) nullchar
97         read(11,'(3x,7(5x,E8.5))') solza(:,lat)
98         read(11,*) nullchar
99
100         do i=1,nlrh+1
101          read(11,'(E6.1,7(2x,F11.5),7x,F11.5)')
102     .          altrh(i),zsnet(i,1:nszarh,lat),zsnetmoy
103         enddo
104         read(11,*) nullchar
105       enddo
106       latrh(nlatrh)=89.
107
108c Correction of factor 2 in the table...
109       zsnet=zsnet*2.
110
111       close(11)
112
113       firstcall=.false.
114      endif
115
116c --------------------------------------
117c Interpolation in the GCM vertical grid
118c --------------------------------------
119
120c Latitude
121c ---------
122     
123      do lat=1,nlatrh
124         if (latrh(lat).le.latdeg) then
125              nlat0 = lat+1
126         endif
127      enddo
128
129      if (nlat0.ne.nlatrh+1) then
130        factlat = (latdeg-latrh(nlat0-1))/(latrh(nlat0)-latrh(nlat0-1))
131      else
132        factlat = min((latdeg-latrh(nlatrh))/(90.-latrh(nlatrh)), 1.)
133      endif
134
135c Zenith angle
136c ------------
137     
138      sza0 = acos(PRMU0)/3.1416*180.
139      nsza0(:)=2
140
141      if (.not.cycle_diurne) then
142        ! without a diurnal cycle, no need for any elaborate weights of sza
143        factsza(1)=1
144        factsza(2)=0
145      else
146        ! standard case with diurnal cycle
147        do nsza=1,nszarh
148          if (solza(nsza,nlat0-1).le.sza0) then
149              nsza0(1) = nsza+1
150          endif
151        enddo
152        if (nsza0(1).ne.nszarh+1) then
153            factsza(1) = (sza0-solza(nsza0(1)-1,nlat0-1))/
154     .          (solza(nsza0(1),nlat0-1)-solza(nsza0(1)-1,nlat0-1))
155        else
156            factsza(1) = min((sza0-solza(nszarh,nlat0-1))/
157     .           (90.-solza(nszarh,nlat0-1)), 1.)
158        endif
159        if (nlat0.ne.nlatrh+1) then
160          do nsza=1,nszarh
161            if (solza(nsza,nlat0).le.sza0) then
162              nsza0(2) = nsza+1
163            endif
164          enddo
165          if (nsza0(2).eq.nszarh+1) then
166             factsza(2) = min((sza0-solza(nszarh,nlat0))/
167     .           (90.-solza(nszarh,nlat0)), 1.)
168          elseif ((nsza0(2).eq.2).and.(solza(1,nlat0).gt.sza0)) then
169            factsza(2) = 0.
170          else
171            factsza(2) = (sza0-solza(nsza0(2)-1,nlat0))/
172     .          (solza(nsza0(2),nlat0)-solza(nsza0(2)-1,nlat0))
173          endif
174        else
175          nsza0(2)   = nszarh+1
176          factsza(2) = 1.
177        endif ! of if (nlat0.ne.nlatrh+1)
178      endif ! of if (.not.cycle_diurne)
179
180c Pressure levels
181c ---------------
182      do j=1,klev+1
183        nl0 = nlrh
184        do i=nlrh+1,2,-1
185           if (presrh(i).ge.PPB(j)) then
186                nl0 = i-1
187           endif
188        enddo
189
190        factflux = (log10(max(PPB(j),presrh(1)))-log10(presrh(nl0+1)))
191     .            /(log10(presrh(nl0))-log10(presrh(nl0+1)))
192
193        ZFSNET(j) =  factlat*(
194     .      factflux   *  factsza(2)   *zsnet(nl0,nsza0(2),nlat0)
195     . +   factflux   *(1.-factsza(2))*zsnet(nl0,nsza0(2)-1,nlat0)
196     . + (1.-factflux)*  factsza(2)   *zsnet(nl0+1,nsza0(2),nlat0)
197     . + (1.-factflux)*(1.-factsza(2))*zsnet(nl0+1,nsza0(2)-1,nlat0) )
198     .            + (1.-factlat)*(
199     .      factflux   *  factsza(1)   *zsnet(nl0,nsza0(1),nlat0-1)
200     . +   factflux   *(1.-factsza(1))*zsnet(nl0,nsza0(1)-1,nlat0-1)
201     . + (1.-factflux)*  factsza(1)   *zsnet(nl0+1,nsza0(1),nlat0-1)
202     . + (1.-factflux)*(1.-factsza(1))*zsnet(nl0+1,nsza0(1)-1,nlat0-1) )
203
204        ZFSNET(j) = ZFSNET(j)*PFRAC
205       
206      enddo
207      PTOPSW = ZFSNET(klev+1)
208      PSOLSW = ZFSNET(1)
209
210#ifdef MESOSCALE
211! extrapolation play RH pressure
212      do j=1,nlrh
213         logplayrh(j)=(log(presrh(j+1))+log(presrh(j)))/2.
214      enddo
215! Extrapolation of temperature over RH play pressure
216      do i=nlrh,2,-1
217        nl0 = 2
218        do j=1,klev-1
219           if (exp(logplayrh(i)).le.PPA(j)) then
220                nl0 = j+1
221           endif
222        enddo
223        factflux = (log10(max(exp(logplayrh(i)),PPA(klev)))
224     .                         -log10(PPA(nl0-1)))
225     .       /(log10(PPA(nl0))-log10(PPA(nl0-1)))
226        Tplay(i)=factflux*pt(nl0)
227     .             + (1.-factflux)*pt(nl0-1)
228
229      ENDDO
230! RH PHEAT over RH play pressure
231      DO k=1,nlrh
232c
233       Qrh1(k)=((RG/cpdet(Tplay(k)))
234     .     *((zsnet(k+1,nsza0(1),nlat0-1)-zsnet(k,nsza0(1),nlat0-1))
235     .         *PFRAC))
236     .      /((presrh(k)-presrh(k+1))*1.e5)
237       Qrh2(k)=((RG/cpdet(Tplay(k)))
238     . *((zsnet(k+1,nsza0(1)-1,nlat0-1)-zsnet(k,nsza0(1)-1,nlat0-1))
239     .         *PFRAC))
240     .      /((presrh(k)-presrh(k+1))*1.e5)
241       Qrh3(k)=((RG/cpdet(Tplay(k)))
242     .       *((zsnet(k+1,nsza0(2),nlat0)-zsnet(k,nsza0(2),nlat0))
243     .         *PFRAC))
244     .      /((presrh(k)-presrh(k+1))*1.e5)
245       Qrh4(k)=((RG/cpdet(Tplay(k)))
246     .       *((zsnet(k+1,nsza0(2)-1,nlat0)-zsnet(k,nsza0(2)-1,nlat0))
247     .        *PFRAC))
248     .      /((presrh(k)-presrh(k+1))*1.e5)
249      ENDDO
250! Interapolation of PHEAT over GCM/MESOSCALE play levels
251      do j=1,klev
252        nl0 = nlrh-1
253        do i=nlrh,2,-1
254           if (exp(logplayrh(i)).ge.PPA(j)) then
255                nl0 = i-1
256           endif
257        enddo
258c        factflux = (log10(max(PPB(j),presrh(1)))-log10(presrh(nl0+1)))
259c     .            /(log10(presrh(nl0))-log10(presrh(nl0+1)))
260        factflux = (log10(max(PPA(j),exp(logplayrh(1))))
261     .                         -log10(exp(logplayrh(nl0+1))))
262     .     /(log10(exp(logplayrh(nl0)))-log10(exp(logplayrh(nl0+1))))
263        PHEATPPA(j)=factlat*(
264     .      factflux   *  factsza(2)  *Qrh3(nl0)
265     . +   factflux   *(1.-factsza(2))*Qrh4(nl0)
266     . + (1.-factflux)*  factsza(2)   *Qrh3(nl0+1)
267     . + (1.-factflux)*(1.-factsza(2))*Qrh4(nl0+1))
268     .            + (1.-factlat)*(
269     .      factflux   *  factsza(1)  *Qrh1(nl0)
270     . +   factflux   *(1.-factsza(1))*Qrh2(nl0)
271     . + (1.-factflux)*  factsza(1)   *Qrh1(nl0+1)
272     . + (1.-factflux)*(1.-factsza(1))*Qrh2(nl0+1) )
273        PHEAT(j)=PHEATPPA(j)
274      ENDDO
275
276
277#else     
278c Heating rates
279c -------------
280c On utilise le gradient du flux pour calculer le taux de chauffage:
281c   heat(K/s) = d(fluxnet)  (W/m2)
282c              *g           (m/s2)
283c              /(-dp)  (epaisseur couche, en Pa=kg/m/s2)
284c              /cp  (J/kg/K)
285
286      do j=1,klev
287! ADAPTATION GCM POUR CP(T)
288        PHEAT(j) = (ZFSNET(j+1)-ZFSNET(j))
289     .            *RG/cpdet(pt(j)) / ((PPB(j)-PPB(j+1))*1.e5)
290c-----TEST-------
291c tayloring the solar flux...
292c        if ((PPB(j).gt.0.04).and.(PPB(j).le.0.1)) then
293c         PHEAT(j) = PHEAT(j)*1.5
294c        endif
295c        if ((PPB(j).gt.0.1).and.(PPB(j).le.0.5)) then
296c         PHEAT(j) = PHEAT(j)*2.
297c        endif
298c BASE:
299c        if ((PPB(j).gt.1.4).and.(PPB(j).le.10.)) then
300c          PHEAT(j) = PHEAT(j)*3
301c        endif
302c AFTER Tayloring TdeepD
303         if ((PPB(j).gt.1.4).and.(PPB(j).le.10.)) then
304           PHEAT(j) = PHEAT(j)*3.5
305         endif
306         if ((PPB(j).gt.10.).and.(PPB(j).le.50.)) then
307           PHEAT(j) = PHEAT(j)*1.5
308         endif
309c Options:
310c        if ((PPB(j).gt.1.4).and.(PPB(j).le.10.)) then
311c        if ((PPB(j).gt.2.0).and.(PPB(j).le.10.)) then
312c        if ((PPB(j).gt.1.4).and.(PPB(j).le.100.)) then
313c          PHEAT(j) = PHEAT(j)*3.5
314c          PHEAT(j) = PHEAT(j)*3
315c          PHEAT(j) = PHEAT(j)*2.5
316c        endif
317c        if ((PPB(j).gt.10.).and.(PPB(j).le.35.)) then
318c        if ((PPB(j).gt.10.).and.(PPB(j).le.50.)) then
319c          PHEAT(j) = PHEAT(j)*2
320c          PHEAT(j) = PHEAT(j)*1.5
321c          PHEAT(j) = PHEAT(j)*1.3
322c        endif
323c        if ((PPB(j).gt.35.).and.(PPB(j).le.120.)) then
324c          PHEAT(j) = PHEAT(j)*2
325c          PHEAT(j) = PHEAT(j)*1.5
326c        endif
327c----------------
328      enddo
329#endif
330     
331
332      end
333
Note: See TracBrowser for help on using the repository browser.