source: trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_dc.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: 5.4 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        L.Salmi  : june 2013 astuce to reduce the excess of  NIR
30c                   in the transition region LTE/LTE
31c
32c        G.Gilli  : feb  2014         
33C     ------------------------------------------------------------------
34C
35C* ARGUMENTS:
36C
37c inputs
38
39      REAL   PRMU0  ! COSINE OF ZENITHAL ANGLE
40      REAL   PFRAC  ! fraction de la journee
41      REAL   PPB(klev+1)  ! inter-couches PRESSURE (bar)
42      REAL   pt(klev)     ! mid-layer temperature
43C
44c output
45
46      REAL   PHEAT(klev)  ! SHORTWAVE HEATING (K/s) within each layer
47      REAL   PTOPSW       ! SHORTWAVE FLUX AT T.O.A. (net)
48      REAL   PSOLSW       ! SHORTWAVE FLUX AT SURFACE (net)
49      REAL   ZFSNET(klev+1) ! net solar flux at ppb levels
50
51C
52C* LOCAL VARIABLES:
53C
54      integer nldc,nszadc
55      parameter (nldc=49)  ! fichiers Crisp
56      parameter (nszadc=8) ! fichiers Crisp
57     
58      integer i,j,nsza,nsza0,nl0
59      real   solarrate               ! solar heating rate (K/earthday)
60      real   zsnet(nldc+1,nszadc)    ! net solar flux (W/m**2) (+ vers bas)
61      real   zsdn,zsup               ! downward/upward solar flux (W/m**2)
62      real   solza(nszadc)           ! solar zenith angles in table
63      real   presdc(nldc+1)          ! pressure levels in table (bar)
64      real   tempdc(nldc+1)          ! temperature in table (K)
65      real   altdc(nldc+1)           ! altitude in table (km)
66      real   coolrate                ! IR heating rate (K/earthday) ?
67      real   totalrate               ! total rate (K/earthday)
68      real   zldn                    ! downward IR flux (W/m**2) ?
69      real   zlup                    !   upward IR flux (W/m**2) ?
70      character*22 nullchar
71      real   sza0,factsza,factflux
72      logical firstcall
73      data    firstcall/.true./
74      save   solza,zsnet,presdc,tempdc,altdc
75      save   firstcall
76     
77c ------------------------
78c Loading the file
79c ------------------------
80
81      if (firstcall) then
82
83       open(11,file='dataDCrisp.dat')
84       read(11,*) nullchar
85     
86       do nsza=1,nszadc
87        read(11,*) nullchar
88        read(11,*) nullchar
89        read(11,*) nullchar
90        read(11,'(22x,F11.5)') solza(nsza)
91        read(11,*) nullchar
92        read(11,*) nullchar
93        read(11,*) nullchar
94        read(11,'(3(2x,F10.4),36x,4(2x,F11.5))')
95     .          presdc(nldc+1),tempdc(nldc+1), altdc(nldc+1),
96     .          zsdn,zsup,zldn,zlup
97        zsnet(nldc+1,nsza)=zsdn-zsup
98        do i=1,nldc
99           j = nldc+1-i        ! changing: vectors from surface to top
100           read(11,'(6(2x,F10.4),4(2x,F11.5))')
101     .          presdc(j),tempdc(j),altdc(j),
102     .          solarrate,coolrate,totalrate,
103     .          zsdn,zsup,zldn,zlup
104           zsnet(j,nsza)=zsdn-zsup
105        enddo
106       enddo
107
108       close(11)
109
110       firstcall=.false.
111      endif
112
113c --------------------------------------
114c Interpolation in the GCM vertical grid
115c --------------------------------------
116
117c Zenith angle
118c ------------
119     
120      sza0 = acos(PRMU0)/3.1416*180.
121c        print*,'Angle Zenithal =',sza0,' PFRAC=',PFRAC
122
123      do nsza=1,nszadc
124         if (solza(nsza).le.sza0) then
125              nsza0 = nsza+1
126         endif
127      enddo
128     
129      if (nsza0.ne.nszadc+1) then
130          factsza = (sza0-solza(nsza0-1))/(solza(nsza0)-solza(nsza0-1))
131      else
132          factsza = min((sza0-solza(nszadc))/(90.-solza(nszadc)), 1.)
133      endif
134
135c Pressure levels
136c ---------------
137
138      do j=1,klev+1
139        nl0 = 2
140        do i=1,nldc
141           if (presdc(i).ge.PPB(j)) then
142                nl0 = i+1
143           endif
144        enddo
145       
146        factflux = (log10(max(PPB(j),presdc(nldc+1)))
147     .                          -log10(presdc(nl0-1)))
148     .            /(log10(presdc(nl0))-log10(presdc(nl0-1)))
149c       factflux = (max(PPB(j),presdc(nldc+1))-presdc(nl0-1))
150c    .            /(presdc(nl0)-presdc(nl0-1))
151        if (nsza0.ne.nszadc+1) then
152          ZFSNET(j) =  factflux   *  factsza   *zsnet(nl0,nsza0)
153     .             +   factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
154     .             + (1.-factflux)*  factsza   *zsnet(nl0-1,nsza0)
155     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
156        else
157          ZFSNET(j) =  factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
158     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
159        endif
160       
161        ZFSNET(j) = ZFSNET(j)*PFRAC
162
163      enddo
164
165      PTOPSW = ZFSNET(klev+1)
166      PSOLSW = ZFSNET(1)
167     
168c Heating rates
169c -------------
170c On utilise le gradient du flux pour calculer le taux de chauffage:
171c   heat(K/s) = d(fluxnet)  (W/m2)
172c              *g           (m/s2)
173c              /(-dp)  (epaisseur couche, en Pa=kg/m/s2)
174c              /cp  (J/kg/K)
175
176      do j=1,klev
177! ADAPTATION GCM POUR CP(T)
178        PHEAT(j) = (ZFSNET(j+1)-ZFSNET(j))
179     .            *RG/cpdet(pt(j)) / ((PPB(j)-PPB(j+1))*1.e5)
180      enddo
181
182      return
183      end
184
Note: See TracBrowser for help on using the repository browser.