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

Last change on this file since 1543 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

File size: 5.4 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 "YOMCST.h"
11C
12C     ------------------------------------------------------------------
13C
14C     PURPOSE.
15C     --------
16C
17c      this routine loads and interpolates the shortwave radiation
18c     fluxes taken from Dave Crisp calculations for Venus.
19c     Ref: Crisp 1986.
20C
21C     AUTHOR.
22C     -------
23C        Sebastien Lebonnois
24C
25C     MODIFICATIONS.
26C     --------------
27C        ORIGINAL : 27/07/2005
28c        L.Salmi  : june 2013 astuce to reduce the excess of  NIR
29c                   in the transition region LTE/LTE
30c
31c        G.Gilli  : feb  2014         
32C     ------------------------------------------------------------------
33C
34C* ARGUMENTS:
35C
36c inputs
37
38      REAL   PRMU0  ! COSINE OF ZENITHAL ANGLE
39      REAL   PFRAC  ! fraction de la journee
40      REAL   PPB(klev+1)  ! inter-couches PRESSURE (bar)
41      REAL   pt(klev)     ! mid-layer temperature
42C
43c output
44
45      REAL   PHEAT(klev)  ! SHORTWAVE HEATING (K/s) within each layer
46      REAL   PTOPSW       ! SHORTWAVE FLUX AT T.O.A. (net)
47      REAL   PSOLSW       ! SHORTWAVE FLUX AT SURFACE (net)
48      REAL   ZFSNET(klev+1) ! net solar flux at ppb levels
49
50C
51C* LOCAL VARIABLES:
52C
53      integer nldc,nszadc
54      parameter (nldc=49)  ! fichiers Crisp
55      parameter (nszadc=8) ! fichiers Crisp
56     
57      integer i,j,nsza,nsza0,nl0
58      real   solarrate               ! solar heating rate (K/earthday)
59      real   zsnet(nldc+1,nszadc)    ! net solar flux (W/m**2) (+ vers bas)
60      real   zsdn,zsup               ! downward/upward solar flux (W/m**2)
61      real   solza(nszadc)           ! solar zenith angles in table
62      real   presdc(nldc+1)          ! pressure levels in table (bar)
63      real   tempdc(nldc+1)          ! temperature in table (K)
64      real   altdc(nldc+1)           ! altitude in table (km)
65      real   coolrate                ! IR heating rate (K/earthday) ?
66      real   totalrate               ! total rate (K/earthday)
67      real   zldn                    ! downward IR flux (W/m**2) ?
68      real   zlup                    !   upward IR flux (W/m**2) ?
69      real   zsolnet(nldc+1)         ! for testing mean net solar flux in DC
70      character*22 nullchar
71      real   deltasza
72      real   sza0,factflux
73      logical firstcall
74      data    firstcall/.true./
75      save   solza,zsnet,presdc,tempdc,altdc,zsolnet
76      save   firstcall
77     
78c ------------------------
79c Loading the file
80c ------------------------
81
82      if (firstcall) then
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      Moyenne planetaire
113c -----------------------------
114     
115      deltasza=(solza(2)-solza(1))*RPI/180.
116
117      do j=1,nldc+1
118        zsolnet(j) = zsnet(j,1)*deltasza*deltasza/16.
119        do nsza=2,nszadc
120        zsolnet(j) = zsolnet(j)+zsnet(j,nsza)*0.5*deltasza*
121     .             sin(solza(nsza)*RPI/180.)
122        enddo
123c overestimation:
124        zsolnet(j) = zsolnet(j)*0.84 
125c        print*,j,altdc(j),zsolnet(j)
126      enddo
127c      stop
128c -----------------------------
129c --------  FIN TEST ----------
130
131       firstcall=.false.
132      endif
133
134c --------------------------------------
135c Interpolation in the GCM vertical grid
136c --------------------------------------
137
138c Pressure levels
139c ---------------
140
141      do j=1,klev+1
142        nl0 = 2
143        do i=1,nldc
144           if (presdc(i).ge.PPB(j)) then
145                nl0 = i+1
146           endif
147        enddo
148       
149        factflux = (log10(max(PPB(j),presdc(nldc+1)))
150     .                          -log10(presdc(nl0-1)))
151     .            /(log10(presdc(nl0))-log10(presdc(nl0-1)))
152        ZFSNET(j) =  factflux     *zsolnet(nl0)
153     .             + (1.-factflux)*zsolnet(nl0-1)
154       
155      enddo
156
157      PTOPSW = ZFSNET(klev+1)
158      PSOLSW = ZFSNET(1)
159     
160c Heating rates
161c -------------
162c On utilise le gradient du flux pour calculer le taux de chauffage:
163c   heat(K/s) = d(fluxnet)  (W/m2)
164c              *g           (m/s2)
165c              /(-dp)  (epaisseur couche, en Pa=kg/m/s2)
166c              /cp  (J/kg/K)
167
168      do j=1,klev
169! ADAPTATION GCM POUR CP(T)
170        PHEAT(j) = (ZFSNET(j+1)-ZFSNET(j))
171     .            *RG/cpdet(pt(j)) / ((PPB(j)-PPB(j+1))*1.e5)
172c--------------
173c BIDOUILLE POUR AJUSTEMENT ET TEST
174c       if (PPB(j).lt.1.e-2) then
175c         PHEAT(j) = PHEAT(j)*0.3
176c       endif
177c       if ((PPB(j).gt.1.e-2).and.(PPB(j).lt.2.e-1)) then
178c         PHEAT(j) = PHEAT(j)*0.7
179c       endif
180c       if (PPB(j).gt.1.) then
181c         PHEAT(j) = PHEAT(j)*2.
182c       endif
183c--------------
184      enddo
185
186      return
187      end
188
Note: See TracBrowser for help on using the repository browser.