source: trunk/LMDZ.MARS/libf/phymars/swmain.F @ 1233

Last change on this file since 1233 was 1047, checked in by emillour, 11 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

File size: 6.4 KB
Line 
1      SUBROUTINE SWMAIN ( KDLON, KFLEV,
2     $                PCST, albedo,
3     $                PRMU0, PDP, PPLEV, aerosol,PFRACT,
4     $                PHEAT, PFLUXD,PFLUXU,
5     &                QVISsQREF3d,omegaVIS3d,gVIS3d)
6
7      use dimradmars_mod, only: ndlo2, ndlon, nflev, nsun
8      use yomlw_h, only: nlaylte, gcp
9      IMPLICIT NONE
10     
11!#include "dimensions.h"
12!#include "dimphys.h"
13!#include "dimradmars.h"
14
15!#include "yomaer.h"
16!#include "yomlw.h"
17! naerkind is set in scatterers.h (built when compiling with makegcm -s #)
18#include"scatterers.h"
19#include "callkeys.h"
20c     
21c     PURPOSE.
22c     --------
23c     
24c     This routine computes the shortwave (solar wavelength)
25c     radiation fluxes in two spectral intervals
26c     and heating rate on the first "nlaylte" layers.
27C     
28c     Francois Forget (2000), adapted from
29C     Fouquart and Bonnel's ECMWF program
30c
31C     IMPLICIT ARGUMENTS :
32C     --------------------
33C     
34C     ==== INPUTS ===
35c
36c    KDLON :  number of horizontal grid points
37c    PCST  :  Solar constant on Mars (W.m-2)
38c    albedo   hemispheric surface albedo
39c                         albedo (i,1) : mean albedo for solar band#1
40c                                        (see below)
41c                         albedo (i,2) : mean albedo for solar band#2
42c                                        (see below)
43c    PRMU0 :         cos of solar zenith angle (=1 when sun at zenith)
44c    PDP :           Layer thickness (Pa)
45c    PPLEV           pressure (Pa) at boundaries of each layer
46c   aerosol               aerosol extinction optical depth
47c                         at reference wavelength "longrefvis" set
48c                         in dimradmars_mod , in each layer, for one of
49c                         the "naerkind" kind of aerosol optical properties.
50c    Pfract :        day fraction of the time interval
51c                          =1 during the full day ; =0 during the night
52c    QVISsQREF3d,omegaVIS3d,gVIS3d Aerosol optical properties
53c
54C     ==== OUTPUTS ===
55c    PHEAT :         Heating rate (K/s)
56c    PFLUXD :        SW downward flux at boundaries of each layer (W.m-2)
57c    PFLUXU :        SW upward flux at boundaries of each layer (W.m-2)
58C     
59C     ----------
60C     
61C-----------------------------------------------------------------------
62C     
63C     
64C-----------------------------------------------------------------------
65C     
66C     ARGUMENTS
67C     ---------
68     
69      INTEGER KDLON, KFLEV
70      REAL ZPSOL(NDLO2), aerosol(NDLO2,KFLEV,naerkind),PRMU0(NDLO2)
71      real PCST
72      REAL albedo(NDLO2,2)
73      REAL PDP(NDLO2,KFLEV)
74      REAL PPLEV(NDLO2,KFLEV+1)
75      REAL PHEAT(NDLO2,KFLEV)
76      REAL PFRACT(NDLO2)
77      real PFLUXD(NDLON,NFLEV+1,2)
78      real PFLUXU(NDLON,NFLEV+1,2)
79      REAL :: QVISsQREF3d(NDLO2,KFLEV,nsun,naerkind)
80      REAL :: omegaVIS3d(NDLO2,KFLEV,nsun,naerkind)
81      REAL :: gVIS3d(NDLO2,KFLEV,nsun,naerkind)
82     
83C     LOCAL ARRAYS
84C     ------------
85     
86      REAL ZDSIG(NDLON,NFLEV), ZFACT(NDLON)
87     S     ,  ZFD(NDLON,NFLEV+1)
88     S     ,  ZFU(NDLON,NFLEV+1)
89     S     ,  ZRMU(NDLON), ZSEC(NDLON)
90     S     ,  ZUD(NDLON,3,NFLEV+1), ZUM(NDLON,NFLEV+1)
91      REAL ZSIGN(NDLON),  ZSIGO(NDLON)
92
93c following line has been changed, kflev--->nflev (to avoid error message
94c when compiling on NASA Ames Sun)
95      REAL ZFDOWN(NDLO2,NFLEV+1),ZFUP(NDLO2,NFLEV+1)
96
97      integer jl, jk, jkp1, jkl
98      integer INU
99      real  zdfnet
100
101C     ------------------------------------------------------------------
102C     Initializations :
103C     ------------------------------------------------------------------
104
105c     Incident Solar flux and corrected angle in the atmosphere
106c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
107      DO JL = 1 , KDLON
108c        Incident Flux at the top of the atmosphere
109         ZFACT(JL)= PRMU0(JL) * PCST * PFRACT(JL)
110
111c        Cos of solar zenith angle CORRECTED for high zenith angle
112       if (PRMU0(JL).GT.0) then
113         ZRMU(JL)=SQRT(1224.* PRMU0(JL) * PRMU0(JL) + 1.) / 35.
114       else
115         ZRMU(JL)= 1. / 35.
116       endif
117         ZSEC(JL)=1./ZRMU(JL)
118      END DO
119
120c     Calcul of ZDSIG  (thickness of layers in sigma coordinates)
121c     ~~~~~~~~~~~~~~~
122      DO JL = 1 , KDLON
123         ZSIGO(JL) = 1.0
124         ZPSOL(JL) = PPLEV(JL,1)
125      END DO
126      DO JK = 1 , nlaylte
127         JKP1 = JK + 1
128         JKL = nlaylte+1 - JK
129         DO  JL = 1 , KDLON
130            ZSIGN(JL) = PPLEV(JL,JKP1) / PPLEV(JL,1)
131            ZDSIG(JL,JK) = ZSIGO(JL) - ZSIGN(JL)
132            ZSIGO(JL) = ZSIGN(JL)
133         END DO
134      END DO
135
136C------------------------------------------------------------------
137C          LOOP ON SPECTRAL INTERVAL in solar spectrum
138C------------------------------------------------------------------
139c  2 spectral interval in solar spectrum :
140c  - INU=1: between wavelength "long1vis" and "long2vis" set in dimradmars_mod
141c  - INU=2: between wavelength "long2vis" and "long3vis" set in dimradmars_mod
142
143      DO INU = 1,2
144
145! NB: swrtype is set in callkeys.h
146        if (swrtype.eq.1) then ! Fouquart
147          CALL SWR_FOUQUART( KDLON, kflev, INU
148     &     ,  aerosol,QVISsQREF3d,omegaVIS3d,gVIS3d
149     &     ,  albedo,ZDSIG,ZPSOL,ZRMU,ZSEC
150     &     ,  ZFD,ZFU )
151        else
152          if (swrtype.eq.2) then ! Toon
153            CALL SWR_TOON( KDLON, kflev, INU
154     &       ,  aerosol,QVISsQREF3d,omegaVIS3d,gVIS3d
155     &       ,  albedo,ZDSIG,ZPSOL,ZRMU,ZSEC
156     &       ,  ZFD,ZFU )
157          else
158            write(*,*) "swmain: invalid swrtype value !!"
159            stop
160          endif ! of if (swrtype.eq.2)
161        endif ! of if (swrtype.eq.1)
162       
163         DO JK = 1 , nlaylte+1
164            DO  JL = 1 , KDLON
165              PFLUXD(JL,JK,INU)=ZFD(JL,JK)*ZFACT(JL)
166              PFLUXU(JL,JK,INU)=ZFU(JL,JK)*ZFACT(JL)
167            END DO
168         END DO
169      END DO ! of DO INU=1,2
170
171C     ------------------------------------------------------
172C     HEATING RATES
173C     ------------------------------------------------------
174
175      DO JK = 1 , nlaylte+1
176         DO  JL = 1 , KDLON
177c           wavelength integrated flux at every level:
178            ZFUP(JL,JK)= (PFLUXU(JL,JK,1)+ PFLUXU(JL,JK,2))
179            ZFDOWN(JL,JK)= (PFLUXD(JL,JK,1)+ PFLUXD(JL,JK,2))
180         END DO
181      END DO
182     
183      DO JK = 1 , nlaylte
184         DO  JL = 1 , KDLON
185            ZDFNET = ZFUP (JL,JK  ) - ZFDOWN(JL,JK  )
186     S              -ZFUP (JL,JK+1) + ZFDOWN(JL,JK+1)
187c           Heating rate
188            PHEAT(JL,JK) = gcp * ZDFNET / PDP(JL,JK)
189         END DO
190      END DO
191
192      RETURN
193      END
Note: See TracBrowser for help on using the repository browser.