source: trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_cl.F @ 1453

Last change on this file since 1453 was 1442, checked in by slebonnois, 9 years ago

SL: update of the Venus GCM, + corrections on routines used for newstart/start2archive for Titan and Venus, + some modifications on tools

File size: 4.7 KB
Line 
1      SUBROUTINE SW_venus_cl(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 Chris Lee calculations for Venus.
20c     Ref: Lee and Richardson 2011
21C
22C     AUTHOR.
23C     -------
24C        Sebastien Lebonnois
25C
26C     MODIFICATIONS.
27C     --------------
28C        ORIGINAL : 11/2014
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 nlcl,nszacl
51      parameter (nlcl=80)  ! fichiers Crisp
52      parameter (nszacl=18) ! fichiers Crisp
53     
54      integer i,j,nsza,nsza0,nl0
55      real   solarrate               ! solar heating rate (K/earthday)
56      real   zsnet(nlcl+1,nszacl)    ! net solar flux (W/m**2) (+ vers bas)
57      real   zsdn,zsup               ! downward/upward solar flux (W/m**2)
58      real   solza(nszacl)           ! solar zenith angles in table
59      real   prescl(nlcl+1)          ! pressure levels in table (bar)
60      real   tempcl(nlcl+1)          ! temperature in table (K)
61      real   altcl(nlcl+1)           ! altitude in table (km)
62      real   coolrate                ! IR heating rate (K/earthday) ?
63      real   totalrate               ! total rate (K/earthday)
64      character*22 nullchar
65      real   sza0,factsza,factflux
66      real   zlnet,tmpzsnet(nszacl)
67      logical firstcall
68      data    firstcall/.true./
69      save   solza,zsnet,prescl,tempcl,altcl
70      save   firstcall
71     
72c ------------------------
73c Loading the file
74c ------------------------
75
76      if (firstcall) then
77
78       do nsza=1,nszacl
79          solza(nsza)=(nsza-1)*5.
80       enddo
81       
82       open(11,file='CLee-SW.dat')
83       read(11,*) nullchar
84       
85       do i=1,nlcl+1
86        read(11,'(4(F10.4,1x),18(F11.4,1x))')
87     .          altcl(i),prescl(i),tempcl(i),zlnet,tmpzsnet
88c change of sign convention:
89        zsnet(i,:)=tmpzsnet*(-1.)
90        prescl(i)=prescl(i)*1.e-5 ! conversion to bars...
91       enddo
92
93       close(11)
94
95       firstcall=.false.
96      endif
97
98c --------------------------------------
99c Interpolation in the GCM vertical grid
100c --------------------------------------
101
102c Zenith angle
103c ------------
104     
105      sza0 = acos(PRMU0)/3.1416*180.
106c        print*,'Angle Zenithal =',sza0,' PFRAC=',PFRAC
107
108      do nsza=1,nszacl
109         if (solza(nsza).le.sza0) then
110              nsza0 = nsza+1
111         endif
112      enddo
113     
114      if (nsza0.ne.nszacl+1) then
115          factsza = (sza0-solza(nsza0-1))/(solza(nsza0)-solza(nsza0-1))
116      else
117          factsza = min((sza0-solza(nszacl))/(90.-solza(nszacl)), 1.)
118      endif
119
120c Pressure levels
121c ---------------
122
123      do j=1,klev+1
124        nl0 = 2
125        do i=1,nlcl
126           if (prescl(i).ge.PPB(j)) then
127                nl0 = i+1
128           endif
129        enddo
130       
131        factflux = (log10(max(PPB(j),prescl(nlcl+1)))
132     .                          -log10(prescl(nl0-1)))
133     .            /(log10(prescl(nl0))-log10(prescl(nl0-1)))
134        if (nsza0.ne.nszacl+1) then
135          ZFSNET(j) =  factflux   *  factsza   *zsnet(nl0,nsza0)
136     .             +   factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
137     .             + (1.-factflux)*  factsza   *zsnet(nl0-1,nsza0)
138     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
139        else
140          ZFSNET(j) =  factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
141     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
142        endif
143       
144        ZFSNET(j) = ZFSNET(j)*PFRAC
145
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)
163      enddo
164
165      return
166      end
167
Note: See TracBrowser for help on using the repository browser.