source: trunk/LMDZ.MARS/libf/phymars/swmain_mod.F @ 3807

Last change on this file since 3807 was 3727, checked in by emillour, 2 months ago

Mars PCM:
Code tidying: put routines in modules, remove useless "return" statements and
remove obsolete and unused scopyi.F
EM

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