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

Last change on this file since 1453 was 1442, checked in by slebonnois, 10 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.5 KB
Line 
1      SUBROUTINE SW_venus_dc_1Dglobave(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      real   zsolnet(nldc+1)         ! for testing mean net solar flux in DC
71      character*22 nullchar
72      real   deltasza
73      real   sza0,factflux
74      logical firstcall
75      data    firstcall/.true./
76      save   solza,zsnet,presdc,tempdc,altdc,zsolnet
77      save   firstcall
78     
79c ------------------------
80c Loading the file
81c ------------------------
82
83      if (firstcall) then
84
85       open(11,file='dataDCrisp.dat')
86       read(11,*) nullchar
87     
88       do nsza=1,nszadc
89        read(11,*) nullchar
90        read(11,*) nullchar
91        read(11,*) nullchar
92        read(11,'(22x,F11.5)') solza(nsza)
93        read(11,*) nullchar
94        read(11,*) nullchar
95        read(11,*) nullchar
96        read(11,'(3(2x,F10.4),36x,4(2x,F11.5))')
97     .          presdc(nldc+1),tempdc(nldc+1), altdc(nldc+1),
98     .          zsdn,zsup,zldn,zlup
99        zsnet(nldc+1,nsza)=zsdn-zsup
100        do i=1,nldc
101           j = nldc+1-i        ! changing: vectors from surface to top
102           read(11,'(6(2x,F10.4),4(2x,F11.5))')
103     .          presdc(j),tempdc(j),altdc(j),
104     .          solarrate,coolrate,totalrate,
105     .          zsdn,zsup,zldn,zlup
106           zsnet(j,nsza)=zsdn-zsup
107        enddo
108       enddo
109
110       close(11)
111
112c ----------- TEST ------------
113c      Moyenne planetaire
114c -----------------------------
115     
116      deltasza=(solza(2)-solza(1))*RPI/180.
117
118      do j=1,nldc+1
119        zsolnet(j) = zsnet(j,1)*deltasza*deltasza/16.
120        do nsza=2,nszadc
121        zsolnet(j) = zsolnet(j)+zsnet(j,nsza)*0.5*deltasza*
122     .             sin(solza(nsza)*RPI/180.)
123        enddo
124c overestimation:
125        zsolnet(j) = zsolnet(j)*0.84 
126c        print*,j,altdc(j),zsolnet(j)
127      enddo
128c      stop
129c -----------------------------
130c --------  FIN TEST ----------
131
132       firstcall=.false.
133      endif
134
135c --------------------------------------
136c Interpolation in the GCM vertical grid
137c --------------------------------------
138
139c Pressure levels
140c ---------------
141
142      do j=1,klev+1
143        nl0 = 2
144        do i=1,nldc
145           if (presdc(i).ge.PPB(j)) then
146                nl0 = i+1
147           endif
148        enddo
149       
150        factflux = (log10(max(PPB(j),presdc(nldc+1)))
151     .                          -log10(presdc(nl0-1)))
152     .            /(log10(presdc(nl0))-log10(presdc(nl0-1)))
153        ZFSNET(j) =  factflux     *zsolnet(nl0)
154     .             + (1.-factflux)*zsolnet(nl0-1)
155       
156      enddo
157
158      PTOPSW = ZFSNET(klev+1)
159      PSOLSW = ZFSNET(1)
160     
161c Heating rates
162c -------------
163c On utilise le gradient du flux pour calculer le taux de chauffage:
164c   heat(K/s) = d(fluxnet)  (W/m2)
165c              *g           (m/s2)
166c              /(-dp)  (epaisseur couche, en Pa=kg/m/s2)
167c              /cp  (J/kg/K)
168
169      do j=1,klev
170! ADAPTATION GCM POUR CP(T)
171        PHEAT(j) = (ZFSNET(j+1)-ZFSNET(j))
172     .            *RG/cpdet(pt(j)) / ((PPB(j)-PPB(j+1))*1.e5)
173c--------------
174c BIDOUILLE POUR AJUSTEMENT ET TEST
175c       if (PPB(j).lt.1.e-2) then
176c         PHEAT(j) = PHEAT(j)*0.3
177c       endif
178c       if ((PPB(j).gt.1.e-2).and.(PPB(j).lt.2.e-1)) then
179c         PHEAT(j) = PHEAT(j)*0.7
180c       endif
181c       if (PPB(j).gt.1.) then
182c         PHEAT(j) = PHEAT(j)*2.
183c       endif
184c--------------
185      enddo
186
187      return
188      end
189
Note: See TracBrowser for help on using the repository browser.