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

Last change on this file since 190 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

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