source: trunk/LMDZ.VENUS/libf/phyvenus/sw_venus_dc.F @ 2187

Last change on this file since 2187 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
RevLine 
[1310]1      SUBROUTINE SW_venus_dc(PRMU0, PFRAC,
[3]2     S              PPB, pt,
3     S              PHEAT,
4     S              PTOPSW,PSOLSW,ZFSNET)
5     
[101]6      use dimphy
[1621]7      use cpdet_phy_mod, only: cpdet
[3]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
[1310]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         
[3]32C     ------------------------------------------------------------------
33C
34C* ARGUMENTS:
35C
36c inputs
37
38      REAL   PRMU0  ! COSINE OF ZENITHAL ANGLE
39      REAL   PFRAC  ! fraction de la journee
[892]40      REAL   PPB(klev+1)  ! inter-couches PRESSURE (bar)
41      REAL   pt(klev)     ! mid-layer temperature
[3]42C
43c output
44
[1301]45      REAL   PHEAT(klev)  ! SHORTWAVE HEATING (K/s) within each layer
[3]46      REAL   PTOPSW       ! SHORTWAVE FLUX AT T.O.A. (net)
47      REAL   PSOLSW       ! SHORTWAVE FLUX AT SURFACE (net)
[892]48      REAL   ZFSNET(klev+1) ! net solar flux at ppb levels
[3]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      character*22 nullchar
70      real   sza0,factsza,factflux
71      logical firstcall
72      data    firstcall/.true./
[101]73      save   solza,zsnet,presdc,tempdc,altdc
[3]74      save   firstcall
75     
76c ------------------------
77c Loading the file
78c ------------------------
79
80      if (firstcall) then
[101]81
[3]82       open(11,file='dataDCrisp.dat')
83       read(11,*) nullchar
84     
85       do nsza=1,nszadc
86        read(11,*) nullchar
87        read(11,*) nullchar
88        read(11,*) nullchar
89        read(11,'(22x,F11.5)') solza(nsza)
90        read(11,*) nullchar
91        read(11,*) nullchar
92        read(11,*) nullchar
93        read(11,'(3(2x,F10.4),36x,4(2x,F11.5))')
94     .          presdc(nldc+1),tempdc(nldc+1), altdc(nldc+1),
95     .          zsdn,zsup,zldn,zlup
96        zsnet(nldc+1,nsza)=zsdn-zsup
97        do i=1,nldc
98           j = nldc+1-i        ! changing: vectors from surface to top
99           read(11,'(6(2x,F10.4),4(2x,F11.5))')
100     .          presdc(j),tempdc(j),altdc(j),
101     .          solarrate,coolrate,totalrate,
102     .          zsdn,zsup,zldn,zlup
103           zsnet(j,nsza)=zsdn-zsup
104        enddo
105       enddo
106
107       close(11)
108
109       firstcall=.false.
110      endif
111
112c --------------------------------------
113c Interpolation in the GCM vertical grid
114c --------------------------------------
115
116c Zenith angle
117c ------------
118     
119      sza0 = acos(PRMU0)/3.1416*180.
120c        print*,'Angle Zenithal =',sza0,' PFRAC=',PFRAC
121
122      do nsza=1,nszadc
123         if (solza(nsza).le.sza0) then
124              nsza0 = nsza+1
125         endif
126      enddo
127     
128      if (nsza0.ne.nszadc+1) then
129          factsza = (sza0-solza(nsza0-1))/(solza(nsza0)-solza(nsza0-1))
130      else
131          factsza = min((sza0-solza(nszadc))/(90.-solza(nszadc)), 1.)
132      endif
133
134c Pressure levels
135c ---------------
136
[892]137      do j=1,klev+1
[3]138        nl0 = 2
139        do i=1,nldc
140           if (presdc(i).ge.PPB(j)) then
141                nl0 = i+1
142           endif
143        enddo
144       
145        factflux = (log10(max(PPB(j),presdc(nldc+1)))
146     .                          -log10(presdc(nl0-1)))
147     .            /(log10(presdc(nl0))-log10(presdc(nl0-1)))
148c       factflux = (max(PPB(j),presdc(nldc+1))-presdc(nl0-1))
149c    .            /(presdc(nl0)-presdc(nl0-1))
150        if (nsza0.ne.nszadc+1) then
151          ZFSNET(j) =  factflux   *  factsza   *zsnet(nl0,nsza0)
152     .             +   factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
153     .             + (1.-factflux)*  factsza   *zsnet(nl0-1,nsza0)
154     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
155        else
156          ZFSNET(j) =  factflux   *(1.-factsza)*zsnet(nl0,nsza0-1)
157     .             + (1.-factflux)*(1.-factsza)*zsnet(nl0-1,nsza0-1)
158        endif
159       
160        ZFSNET(j) = ZFSNET(j)*PFRAC
161
162      enddo
163
[892]164      PTOPSW = ZFSNET(klev+1)
[3]165      PSOLSW = ZFSNET(1)
166     
167c Heating rates
168c -------------
169c On utilise le gradient du flux pour calculer le taux de chauffage:
170c   heat(K/s) = d(fluxnet)  (W/m2)
171c              *g           (m/s2)
172c              /(-dp)  (epaisseur couche, en Pa=kg/m/s2)
173c              /cp  (J/kg/K)
174
[892]175      do j=1,klev
[3]176! ADAPTATION GCM POUR CP(T)
177        PHEAT(j) = (ZFSNET(j+1)-ZFSNET(j))
178     .            *RG/cpdet(pt(j)) / ((PPB(j)-PPB(j+1))*1.e5)
179      enddo
180
181      return
182      end
183
Note: See TracBrowser for help on using the repository browser.