source: trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_ve_1Dglobave.F @ 3461

Last change on this file since 3461 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: 5.4 KB
Line 
1      SUBROUTINE SW_venus_ve_1Dglobave( PRMU0, PFRAC,
2     S              PPB, pt, pz,
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 and heating rates computed from Vincent Eymet 3D MC code
19C
20C     AUTHOR.
21C     -------
22C        Sebastien Lebonnois
23C
24C     MODIFICATIONS.
25C     --------------
26C        ORIGINAL : 06/2014
27C     ------------------------------------------------------------------
28C
29C* ARGUMENTS:
30C
31c inputs
32
33      REAL   PRMU0  ! COSINE OF ZENITHAL ANGLE
34      REAL   PFRAC  ! fraction de la journee
35      REAL   PPB(klev+1)  ! inter-couches PRESSURE (bar)
36      REAL   pt(klev)     ! mid-layer temperature
37      REAL   pz(klev+1)   ! inter-couches altitude (m)
38C
39c output
40
41      REAL   PHEAT(klev) ! SHORTWAVE HEATING (K/VENUSDAY) 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 nlve,nszave
50      parameter (nlve=78)   ! fichiers planet_EMC
51      parameter (nszave=20) ! fichiers planet_EMC
52     
53      integer i,j,nsza,nsza0,nl0
54      real   solarrate               ! solar heating rate (K/earthday)
55      real   zsnet(nlve,nszave)      ! net solar flux (W/m**2) (+ vers bas)
56      real   zheat(nlve-1,nszave)    ! rad budget (W/m**2)
57      real   zsdn,zsup               ! downward/upward solar flux (W/m**2)
58      real   solza(nszave)           ! solar zenith angles in table (rad)
59      real   altve(nlve)             ! altitude in table (m)
60      real   zheatave(nlve-1)        ! for testing mean net solar flux
61      real   zsolnet(nlve)           ! for testing mean net solar flux
62      character*22 nullchar
63      real   deltasza
64      real   sza0,factflux,alt
65      logical firstcall
66      data    firstcall/.true./
67      save   solza,zsnet,altve,zheat,zheatave,zsolnet
68      save   firstcall
69     
70c ------------------------
71c Loading the files
72c ------------------------
73
74      if (firstcall) then
75
76! FLUXES (W/m2)
77
78       open(11,file='solar_fluxes_GCM.dat')
79       read(11,*) nullchar
80       read(11,*) nullchar
81       read(11,*) nullchar
82       read(11,*) nullchar
83     
84       do nsza=1,nszave
85        read(11,*) nullchar
86        read(11,*) solza(nsza)
87        read(11,*) nullchar
88        read(11,*) nullchar
89        do j=1,nlve
90           read(11,'(4(2x,F12.5))')
91     .          altve(j),zsdn,zsup,zsnet(j,nsza)
92        enddo
93       enddo
94
95       close(11)
96
97! HEATING RATES (W/m2)
98
99       open(12,file='solar_budgets_GCM.dat')
100       read(12,*) nullchar
101       read(12,*) nullchar
102       read(12,*) nullchar
103       read(12,*) nullchar
104     
105       do nsza=1,nszave
106        read(12,*) nullchar
107        read(12,*) solza(nsza)
108        read(12,*) nullchar
109        read(12,*) nullchar
110        do j=1,nlve-1
111           read(12,'(2(2x,F12.5))')
112     .          alt,zheat(j,nsza)
113        enddo
114       enddo
115
116       close(12)
117
118       firstcall=.false.
119      endif
120
121c ----------- TEST ------------
122c      Moyenne planetaire
123c -----------------------------
124      zheatave(:)=0.
125      zsolnet(:)=0.
126     
127      do j=1,nlve-1
128        deltasza=solza(1)+(solza(2)-solza(1))/2.  ! deja en radian
129        zheatave(j) = zheat(j,1)*deltasza*deltasza/16.
130        do nsza=2,nszave-1
131         deltasza=(solza(nsza)-solza(nsza-1))/2.
132     .           +(solza(nsza+1)-solza(nsza))/2.  ! deja en radian
133         zheatave(j) = zheatave(j)+zheat(j,nsza)*0.5*deltasza*
134     .             sin(solza(nsza))
135        enddo
136      enddo
137      do j=1,nlve
138        deltasza=solza(1)+(solza(2)-solza(1))/2.  ! deja en radian
139        zsolnet(j) = zsnet(j,1)*deltasza*deltasza/16.
140        do nsza=2,nszave
141         deltasza=(solza(nsza)-solza(nsza-1))/2.
142     .           +(solza(nsza+1)-solza(nsza))/2.  ! deja en radian
143         zsolnet(j) = zsolnet(j)+zsnet(j,nsza)*0.5*deltasza*
144     .             sin(solza(nsza))
145        enddo
146      enddo
147c      stop
148c -----------------------------
149c --------  FIN TEST ----------
150
151c --------------------------------------
152c Interpolation in the GCM vertical grid
153c --------------------------------------
154
155c Pressure levels
156c ---------------
157
158      do j=1,klev+1
159        nl0 = 2
160        do i=1,nlve-1
161           if (altve(i).le.pz(j)) then
162                nl0 = i+1
163           endif
164        enddo
165       
166        factflux = (min(pz(j),altve(nlve))
167     .                          -altve(nl0-1))
168     .            /(altve(nl0)-altve(nl0-1))
169
170! FLUXES
171
172        ZFSNET(j) =  factflux   *zsolnet(nl0)
173     .           + (1.-factflux)*zsolnet(nl0-1)
174
175! HEATING RATES
176
177        if (j.ne.klev+1) then
178          PHEAT(j) =  factflux   *zheatave(nl0)
179     .            + (1.-factflux)*zheatave(nl0-1)
180        endif
181
182      enddo
183
184      PTOPSW = ZFSNET(klev+1)
185      PSOLSW = ZFSNET(1)
186     
187c Heating rates
188c -------------
189c Conversion from W/m2 to K/s:
190c   heat(K/s) = d(fluxnet)  (W/m2)
191c              *g           (m/s2)
192c              /(-dp)  (epaisseur couche, en Pa=kg/m/s2)
193c              /cp  (J/kg/K)
194
195      do j=1,klev
196! ADAPTATION GCM POUR CP(T)
197        PHEAT(j) = PHEAT(j)
198     .            *RG/cpdet(pt(j)) / ((PPB(j)-PPB(j+1))*1.e5)
199      enddo
200
201      return
202      end
203
Note: See TracBrowser for help on using the repository browser.