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

Last change on this file since 2203 was 2048, checked in by slebonnois, 6 years ago

SL: VENUS, autres details

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