source: trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_dc.F @ 1240

Last change on this file since 1240 was 1017, checked in by emillour, 11 years ago

Common dynamics: (and collateral adaptations in Venus physics)
Improved cpdet routines in and additional sponge mode:

  • Additionnal sponge mode (trigered with "callsponge" flag), in line with the one used in the Generic and Martian GCM. This sponge is called whenever there is a dissipation step.
  • Improvement of the cpdet routines : created routines tpot2t_glo_p and t2tpot_glo_p which handle fields on the whole dynamics (scaler) grid, which are more efficient than calling tpot2t_p or t2tpot_p with slabs of data (generated use of intermediate copies of these chunks of data at every call)
  • Turned cpdet.F into a module cpdet_mod.F90 (and correspondingly adapted all routines in the Venus physics).

EM

File size: 7.2 KB
Line 
1      SUBROUTINE SW_venus_dc( PRMU0, PFRAC,
2     S              PPB, pt,
3     S              PHEAT,
4     S              PTOPSW,PSOLSW,ZFSNET)
5     
6      use dimphy
7      use cpdet_mod, only: cpdet
8      IMPLICIT none
9
10#include "dimensions.h"
11#include "YOMCST.h"
12C
13C     ------------------------------------------------------------------
14C
15C     PURPOSE.
16C     --------
17C
18c      this routine loads and interpolates the shortwave radiation
19c     fluxes taken from Dave Crisp calculations for Venus.
20c     Ref: Crisp 1986.
21C
22C     AUTHOR.
23C     -------
24C        Sebastien Lebonnois
25C
26C     MODIFICATIONS.
27C     --------------
28C        ORIGINAL : 27/07/2005
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/VENUSDAY) 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 nldc,nszadc
51      real    dureejour
52      parameter (nldc=49)  ! fichiers Crisp
53      parameter (nszadc=8) ! fichiers Crisp
54      parameter (dureejour=10.087e6)
55     
56      integer i,j,nsza,nsza0,nl0
57      real   solarrate               ! solar heating rate (K/earthday)
58      real   zsnet(nldc+1,nszadc)    ! net solar flux (W/m**2) (+ vers bas)
59      real   zsdn,zsup               ! downward/upward solar flux (W/m**2)
60      real   solza(nszadc)           ! solar zenith angles in table
61      real   presdc(nldc+1)          ! pressure levels in table (bar)
62      real   tempdc(nldc+1)          ! temperature in table (K)
63      real   altdc(nldc+1)           ! altitude in table (km)
64      real   coolrate                ! IR heating rate (K/earthday) ?
65      real   totalrate               ! total rate (K/earthday)
66      real   zldn                    ! downward IR flux (W/m**2) ?
67      real   zlup                    !   upward IR flux (W/m**2) ?
68      real   zsolnet(nldc)           ! for testing mean net solar flux in DC
69      character*22 nullchar
70      real   sza0,factsza,factflux
71      logical firstcall
72      data    firstcall/.true./
73      REAL,save,allocatable :: zsolVE(:) ! net solar flux at ppb levels, fichiers VE
74      save   solza,zsnet,presdc,tempdc,altdc
75      save   firstcall
76     
77c ------------------------
78c Loading the file
79c ------------------------
80
81      if (firstcall) then
82       allocate(zsolVE(klevp1))
83
84       open(11,file='dataDCrisp.dat')
85       read(11,*) nullchar
86     
87       do nsza=1,nszadc
88        read(11,*) nullchar
89        read(11,*) nullchar
90        read(11,*) nullchar
91        read(11,'(22x,F11.5)') solza(nsza)
92        read(11,*) nullchar
93        read(11,*) nullchar
94        read(11,*) nullchar
95        read(11,'(3(2x,F10.4),36x,4(2x,F11.5))')
96     .          presdc(nldc+1),tempdc(nldc+1), altdc(nldc+1),
97     .          zsdn,zsup,zldn,zlup
98        zsnet(nldc+1,nsza)=zsdn-zsup
99        do i=1,nldc
100           j = nldc+1-i        ! changing: vectors from surface to top
101           read(11,'(6(2x,F10.4),4(2x,F11.5))')
102     .          presdc(j),tempdc(j),altdc(j),
103     .          solarrate,coolrate,totalrate,
104     .          zsdn,zsup,zldn,zlup
105           zsnet(j,nsza)=zsdn-zsup
106        enddo
107       enddo
108
109       close(11)
110
111c ----------- TEST ------------
112c      Fichiers de Vincent
113c -----------------------------
114c      open(12,file='flux_vis_dcGCM.txt')
115c      read(12,*) nullchar
116c
117c       do j=1,klev+1
118c          read(12,*) zlup,zldn,zsolVE(j)
119c       enddo
120c       
121c      close(12)
122c -----------------------------
123c --------  FIN TEST ----------
124     
125       firstcall=.false.
126      endif
127
128c ----------- TEST ------------
129c      Moyenne planetaire
130c -----------------------------
131c     do j=1,nldc
132c  ---
133c       zsolnet(j) = zsnet(j,1)*0.5*
134c    .             sin(solza(1)*RPI/180.)*solza(2)*RPI/180./2.
135c       do nsza=2,nszadc-1
136c       zsolnet(j) = zsolnet(j)+zsnet(j,nsza)*0.5*
137c    .             sin(solza(nsza)*RPI/180.)*
138c    .             (solza(nsza+1)-solza(nsza-1))*RPI/180./2.
139c       enddo
140c       zsolnet(j) = zsolnet(j)+zsdn(j,nszadc)*0.5*
141c    .             sin(solza(nszadc)*RPI/180.)*
142c    .             (90.-solza(nszadc-1))*RPI/180./2.
143c  ---
144c       zsolnet(j) = 0.0
145c       do nsza=1,nszadc-1
146c       zsolnet(j) = zsolnet(j)+(zsnet(j,nsza  )
147c    .                          +zsnet(j,nsza+1))*0.5*
148c    .             (cos(solza(nsza  )*RPI/180.)-
149c    .              cos(solza(nsza+1)*RPI/180.) )
150c       enddo
151c       zsolnet(j) = zsolnet(j)+zsnet(j,nszadc)*0.25*
152c      .             cos(solza(nszadc)*RPI/180.)
153c  ---
154c       print*,j,altdc(j),zsolnet(j)
155c     enddo
156c     stop
157c -----------------------------
158c --------  FIN TEST ----------
159
160c --------------------------------------
161c Interpolation in the GCM vertical grid
162c --------------------------------------
163
164c Zenith angle
165c ------------
166     
167      sza0 = acos(PRMU0)/3.1416*180.
168c        print*,'Angle Zenithal =',sza0,' PFRAC=',PFRAC
169
170      do nsza=1,nszadc
171         if (solza(nsza).le.sza0) then
172              nsza0 = nsza+1
173         endif
174      enddo
175     
176      if (nsza0.ne.nszadc+1) then
177          factsza = (sza0-solza(nsza0-1))/(solza(nsza0)-solza(nsza0-1))
178      else
179          factsza = min((sza0-solza(nszadc))/(90.-solza(nszadc)), 1.)
180      endif
181
182c Pressure levels
183c ---------------
184
185      do j=1,klev+1
186        nl0 = 2
187        do i=1,nldc
188           if (presdc(i).ge.PPB(j)) then
189                nl0 = i+1
190           endif
191        enddo
192       
193        factflux = (log10(max(PPB(j),presdc(nldc+1)))
194     .                          -log10(presdc(nl0-1)))
195     .            /(log10(presdc(nl0))-log10(presdc(nl0-1)))
196c       factflux = (max(PPB(j),presdc(nldc+1))-presdc(nl0-1))
197c    .            /(presdc(nl0)-presdc(nl0-1))
198        if (nsza0.ne.nszadc+1) then
199          ZFSNET(j) =  factflux   *  factsza   *zsnet(nl0,nsza0)
200     .             +   factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
201     .             + (1.-factflux)*  factsza   *zsnet(nl0-1,nsza0)
202     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
203        else
204          ZFSNET(j) =  factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
205     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
206        endif
207       
208        ZFSNET(j) = ZFSNET(j)*PFRAC
209
210      enddo
211
212c ----------- TEST ------------
213c      Fichiers de Vincent
214c -----------------------------
215c     do j=1,klev+1
216c       ZFSNET(j)=zsolVE(j)
217c     enddo
218c -----------------------------
219c --------  FIN TEST ----------
220
221      PTOPSW = ZFSNET(klev+1)
222      PSOLSW = ZFSNET(1)
223     
224c Heating rates
225c -------------
226c On utilise le gradient du flux pour calculer le taux de chauffage:
227c   heat(K/s) = d(fluxnet)  (W/m2)
228c              *g           (m/s2)
229c              /(-dp)  (epaisseur couche, en Pa=kg/m/s2)
230c              /cp  (J/kg/K)
231
232      do j=1,klev
233! ADAPTATION GCM POUR CP(T)
234        PHEAT(j) = (ZFSNET(j+1)-ZFSNET(j))
235     .            *RG/cpdet(pt(j)) / ((PPB(j)-PPB(j+1))*1.e5)
236        PHEAT(j) = PHEAT(j)*dureejour  ! K/venus_day
237      enddo
238
239      return
240      end
241
Note: See TracBrowser for help on using the repository browser.