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

Last change on this file since 1661 was 1621, checked in by emillour, 8 years ago

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

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_phy_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 Chris Lee calculations for Venus.
19c     Ref: Lee and Richardson 2011
20C
21C     AUTHOR.
22C     -------
23C        Sebastien Lebonnois
24C
25C     MODIFICATIONS.
26C     --------------
27C        ORIGINAL : 11/2014
28C     ------------------------------------------------------------------
29C
30C* ARGUMENTS:
31C
32c inputs
33
34      REAL   PRMU0  ! COSINE OF ZENITHAL ANGLE
35      REAL   PFRAC  ! fraction de la journee
36      REAL   PPB(klev+1)  ! inter-couches PRESSURE (bar)
37      REAL   pt(klev)     ! mid-layer temperature
38C
39c output
40
41      REAL   PHEAT(klev)  ! SHORTWAVE HEATING (K/s) within each layer
42      REAL   PTOPSW       ! SHORTWAVE FLUX AT T.O.A. (net)
43      REAL   PSOLSW       ! SHORTWAVE FLUX AT SURFACE (net)
44      REAL   ZFSNET(klev+1) ! net solar flux at ppb levels
45
46C
47C* LOCAL VARIABLES:
48C
49      integer nlcl,nszacl
50      parameter (nlcl=80)  ! fichiers Crisp
51      parameter (nszacl=18) ! fichiers Crisp
52     
53      integer i,j,nsza,nsza0,nl0
54      real   solarrate               ! solar heating rate (K/earthday)
55      real   zsnet(nlcl+1,nszacl)    ! net solar flux (W/m**2) (+ vers bas)
56      real   zsdn,zsup               ! downward/upward solar flux (W/m**2)
57      real   solza(nszacl)           ! solar zenith angles in table
58      real   prescl(nlcl+1)          ! pressure levels in table (bar)
59      real   tempcl(nlcl+1)          ! temperature in table (K)
60      real   altcl(nlcl+1)           ! altitude in table (km)
61      real   coolrate                ! IR heating rate (K/earthday) ?
62      real   totalrate               ! total rate (K/earthday)
63      character*22 nullchar
64      real   sza0,factsza,factflux
65      real   zlnet,tmpzsnet(nszacl)
66      logical firstcall
67      data    firstcall/.true./
68      save   solza,zsnet,prescl,tempcl,altcl
69      save   firstcall
70     
71c ------------------------
72c Loading the file
73c ------------------------
74
75      if (firstcall) then
76
77       do nsza=1,nszacl
78          solza(nsza)=(nsza-1)*5.
79       enddo
80       
81       open(11,file='CLee-SW.dat')
82       read(11,*) nullchar
83       
84       do i=1,nlcl+1
85        read(11,'(4(F10.4,1x),18(F11.4,1x))')
86     .          altcl(i),prescl(i),tempcl(i),zlnet,tmpzsnet
87c change of sign convention:
88        zsnet(i,:)=tmpzsnet*(-1.)
89        prescl(i)=prescl(i)*1.e-5 ! conversion to bars...
90       enddo
91
92       close(11)
93
94       firstcall=.false.
95      endif
96
97c --------------------------------------
98c Interpolation in the GCM vertical grid
99c --------------------------------------
100
101c Zenith angle
102c ------------
103     
104      sza0 = acos(PRMU0)/3.1416*180.
105c        print*,'Angle Zenithal =',sza0,' PFRAC=',PFRAC
106
107      do nsza=1,nszacl
108         if (solza(nsza).le.sza0) then
109              nsza0 = nsza+1
110         endif
111      enddo
112     
113      if (nsza0.ne.nszacl+1) then
114          factsza = (sza0-solza(nsza0-1))/(solza(nsza0)-solza(nsza0-1))
115      else
116          factsza = min((sza0-solza(nszacl))/(90.-solza(nszacl)), 1.)
117      endif
118
119c Pressure levels
120c ---------------
121
122      do j=1,klev+1
123        nl0 = 2
124        do i=1,nlcl
125           if (prescl(i).ge.PPB(j)) then
126                nl0 = i+1
127           endif
128        enddo
129       
130        factflux = (log10(max(PPB(j),prescl(nlcl+1)))
131     .                          -log10(prescl(nl0-1)))
132     .            /(log10(prescl(nl0))-log10(prescl(nl0-1)))
133        if (nsza0.ne.nszacl+1) then
134          ZFSNET(j) =  factflux   *  factsza   *zsnet(nl0,nsza0)
135     .             +   factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
136     .             + (1.-factflux)*  factsza   *zsnet(nl0-1,nsza0)
137     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
138        else
139          ZFSNET(j) =  factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
140     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
141        endif
142       
143        ZFSNET(j) = ZFSNET(j)*PFRAC
144
145      enddo
146
147      PTOPSW = ZFSNET(klev+1)
148      PSOLSW = ZFSNET(1)
149     
150c Heating rates
151c -------------
152c On utilise le gradient du flux pour calculer le taux de chauffage:
153c   heat(K/s) = d(fluxnet)  (W/m2)
154c              *g           (m/s2)
155c              /(-dp)  (epaisseur couche, en Pa=kg/m/s2)
156c              /cp  (J/kg/K)
157
158      do j=1,klev
159! ADAPTATION GCM POUR CP(T)
160        PHEAT(j) = (ZFSNET(j+1)-ZFSNET(j))
161     .            *RG/cpdet(pt(j)) / ((PPB(j)-PPB(j+1))*1.e5)
162      enddo
163
164      return
165      end
166
Note: See TracBrowser for help on using the repository browser.