source: trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_rh_1Dglobave.F @ 3884

Last change on this file since 3884 was 3884, checked in by ikovalenko, 4 months ago
File size: 4.8 KB
Line 
1      SUBROUTINE SW_venus_rh_1Dglobave(PRMU0, PFRAC,
2     S              PPB, pt,
3     S              PHEAT,
4     S              PTOPSW,PSOLSW,ZFSNET)
5     
6      use dimphy
7      use cpdet_phy_mod, only: cpdet
8      use YOMCST_mod
9      IMPLICIT none
10
11C#include "YOMCST.h"
12C
13C     ------------------------------------------------------------------
14C
15C     PURPOSE.
16C     --------
17C
18c      this routine loads and interpolates the shortwave radiation
19c     fluxes taken from Rainer Haus calculations for Venus.
20c     Ref: Haus et al. 2016
21C
22C     AUTHOR.
23C     -------
24C        Sebastien Lebonnois
25C
26C     MODIFICATIONS.
27C     --------------
28C        ORIGINAL : 5/2016
29C     ------------------------------------------------------------------
30C
31C* ARGUMENTS:
32C
33c inputs
34
35      REAL   PRMU0  ! COSINE OF ZENITHAL ANGLE
36      REAL   PFRAC  ! fraction de la journee
37      REAL   PPB(klev+1)  ! inter-couches PRESSURE (bar)
38      REAL   pt(klev)     ! mid-layer temperature
39C
40c output
41
42      REAL   PHEAT(klev)  ! SHORTWAVE HEATING (K/s) within each layer
43      REAL   PTOPSW       ! SHORTWAVE FLUX AT T.O.A. (net)
44      REAL   PSOLSW       ! SHORTWAVE FLUX AT SURFACE (net)
45      REAL   ZFSNET(klev+1) ! net solar flux at ppb levels
46
47C
48C* LOCAL VARIABLES:
49C
50      integer nlrh,nszarh,nlatrh
51      parameter (nlrh=118)  ! fichiers Rainer Haus
52      parameter (nszarh=7) ! fichiers Rainer Haus
53      parameter (nlatrh=19) ! fichiers Rainer Haus
54     
55      integer i,j,lat,nsza,nsza0,nl0
56      real   zsnetmoy(nlrh+1,nlatrh)    ! net solar flux (W/m**2) (+ vers bas)
57      real   presrh(nlrh+1)             ! pressure in table (bar)
58      real   altrh(nlrh+1)              ! altitude in table (km)
59      real   latrh(nlatrh)              ! latitude in table (degrees)
60      real   zsolnet(nlrh+1)            ! for mean net solar flux in RH
61      character*22 nullchar
62      real   factflux
63      real   zsnet(nszarh)    ! net solar flux (W/m**2) (+ vers bas)
64      real   deltalat
65      logical firstcall
66      data    firstcall/.true./
67      save   zsolnet,altrh,presrh
68      save   firstcall
69     
70c ------------------------
71c Loading the file
72c ------------------------
73
74      if (firstcall) then
75
76       open(11,file='SolarNetFlux_RH.dat')
77
78       do i=1,nlrh+1
79          read(11,'(E5.1,4x,F8.2)') altrh(i),presrh(i)
80       enddo
81
82       do lat=1,nlatrh
83         latrh(lat)=5.*(lat-1)
84         read(11,*) nullchar
85         read(11,*) nullchar
86         read(11,*) nullchar
87         read(11,*) nullchar
88
89         do i=1,nlrh+1
90          read(11,'(E6.1,7(2x,F11.5),7x,F11.5)')
91     .          altrh(i),zsnet,zsnetmoy(i,lat)
92         enddo
93         read(11,*) nullchar
94       enddo
95       latrh(nlatrh)=89.
96
97       close(11)
98
99c ----------- TEST ------------
100c      Moyenne planetaire
101c -----------------------------
102
103      zsolnet=0.
104      do lat=1,nlatrh-1
105        deltalat=(latrh(lat+1)-latrh(lat))*RPI/180.
106        do j=1,nlrh+1
107        zsolnet(j) = zsolnet(j)+
108     .         (zsnetmoy(j,lat+1)+zsnetmoy(j,lat))/2.*
109     .       deltalat*cos((latrh(lat+1)+latrh(lat))*RPI/360.)
110        enddo
111      enddo
112c -----------------------------
113c --------  FIN TEST ----------
114
115       firstcall=.false.
116      endif
117
118c --------------------------------------
119c Interpolation in the GCM vertical grid
120c --------------------------------------
121
122c Pressure levels
123c ---------------
124
125      do j=1,klev+1
126        nl0 = nlrh
127        do i=nlrh+1,2,-1
128           if (presrh(i).ge.PPB(j)) then
129                nl0 = i-1
130           endif
131        enddo
132       
133        factflux = (log10(max(PPB(j),presrh(1)))-log10(presrh(nl0+1)))
134     .            /(log10(presrh(nl0))-log10(presrh(nl0+1)))
135
136        ZFSNET(j) =  factflux     *zsolnet(nl0)
137     .             + (1.-factflux)*zsolnet(nl0+1)
138       
139c-----TEST-------
140c tayloring the solar flux...
141c        if ((PPB(j).gt.0.236).and.(PPB(j).le.22.52)) then
142c         ZFSNET(j) = ZFSNET(j)+2.5*(1.+cos((log10(PPB(j)/3.5)/
143c     .                                  log10(0.236/3.5))*RPI))
144c        endif
145c----------------
146      enddo
147
148      PTOPSW = ZFSNET(klev+1)
149      PSOLSW = ZFSNET(1)
150     
151c Heating rates
152c -------------
153c On utilise le gradient du flux pour calculer le taux de chauffage:
154c   heat(K/s) = d(fluxnet)  (W/m2)
155c              *g           (m/s2)
156c              /(-dp)  (epaisseur couche, en Pa=kg/m/s2)
157c              /cp  (J/kg/K)
158
159      do j=1,klev
160! ADAPTATION GCM POUR CP(T)
161        PHEAT(j) = (ZFSNET(j+1)-ZFSNET(j))
162     .            *RG/cpdet(pt(j)) / ((PPB(j)-PPB(j+1))*1.e5)
163c-----TEST-------
164c tayloring the solar flux...
165        if ((PPB(j).gt.1.4).and.(PPB(j).le.10.)) then
166          PHEAT(j) = PHEAT(j)*3
167c       elseif ((PPB(j).gt.10.).and.(PPB(j).le.30.)) then
168c         PHEAT(j) = PHEAT(j)*1.5
169        endif
170c----------------
171c       print*,PPB(j),ZFSNET(j),PHEAT(j)
172      enddo
173c     stop
174      return
175      end
176
Note: See TracBrowser for help on using the repository browser.