/[lmdze]/trunk/Sources/phylmd/Radlwsw/radlwsw.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/Radlwsw/radlwsw.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/phylmd/Radlwsw/radlwsw.f90 revision 76 by guez, Fri Nov 15 18:45:49 2013 UTC trunk/Sources/phylmd/Radlwsw/radlwsw.f revision 220 by guez, Tue Apr 4 14:52:21 2017 UTC
# Line 4  module radlwsw_m Line 4  module radlwsw_m
4    
5  contains  contains
6    
7    SUBROUTINE radlwsw(dist, rmu0, fract, paprs, play, tsol, albedo, alblw, &    SUBROUTINE radlwsw(dist, mu0, fract, paprs, play, tsol, albedo, t, q, wo, &
8         t, q, wo, cldfra, cldemi, cldtaupd, heat, heat0, cool, cool0, radsol, &         cldfra, cldemi, cldtaupd, heat, heat0, cool, cool0, radsol, albpla, &
9         albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, toplw0, solsw0, &         topsw, toplw, solsw, sollw, sollwdown, topsw0, toplw0, solsw0, sollw0, &
10         sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, swup0, swup, ok_ade, &         lwdn0, lwdn, lwup0, lwup, swdn0, swdn, swup0, swup, ok_ade, topswad, &
11         ok_aie, tau_ae, piz_ae, cg_ae, topswad, solswad, cldtaupi, topswai, &         solswad)
        solswai)  
12    
13      ! From LMDZ4/libf/phylmd/radlwsw.F, version 1.4 2005/06/06 13:16:33      ! From LMDZ4/libf/phylmd/radlwsw.F, version 1.4, 2005/06/06 13:16:33
14      ! Author: Z. X. Li (LMD/CNRS)      ! Author: Z. X. Li (LMD/CNRS)
15      ! Date: 1996/07/19      ! Date: 1996/07/19
16    
17      ! Objet : interface entre le modèle et les rayonnements solaire et      ! Objet : interface entre le modèle et les rayonnements solaire et
18      ! infrarouge      ! infrarouge
19    
20      ! ATTENTION: swai and swad have to be interpreted in the following manner:      ! ATTENTION: swad has to be interpreted in the following manner:
21        ! not ok_ade zero
22        ! ok_ade aerosol direct forcing is F_{AD} = topsw - topswad
23    
24      ! not ok_ade and not ok_aie      USE clesphys, ONLY: solaire
     ! both are zero  
   
     ! ok_ade and not ok_aie  
     ! aerosol direct forcing is F_{AD} = topsw - topswad  
     ! indirect is zero  
   
     ! not ok_ade and ok_aie  
     ! aerosol indirect forcing is F_{AI} = topsw - topswai  
     ! direct is zero  
   
     ! ok_ade and ok_aie  
     ! aerosol indirect forcing is F_{AI} = topsw - topswai  
     ! aerosol direct forcing is F_{AD} = topswai - topswad  
   
     USE clesphys, ONLY: bug_ozone, solaire  
25      USE dimphy, ONLY: klev, klon      USE dimphy, ONLY: klev, klon
26      use lw_m, only: lw      use lw_m, only: lw
27      USE raddim, ONLY: kdlon      USE raddim, ONLY: kdlon
28      USE suphec_m, ONLY: rg      USE suphec_m, ONLY: rg
29      use sw_m, only: sw      use sw_m, only: sw
30      USE yoethf_m, ONLY: rvtmp2      USE yoethf_m, ONLY: rvtmp2
           
     ! Arguments:  
31    
32      real dist, rmu0(klon), fract(klon)      real, intent(in):: dist ! distance astronomique terre-soleil
33      ! dist-----input-R- distance astronomique terre-soleil      real, intent(in):: mu0(klon) ! cosinus de l'angle zenithal
34      ! rmu0-----input-R- cosinus de l'angle zenithal      real, intent(in):: fract(klon) ! duree d'ensoleillement normalisee
35      ! fract----input-R- duree d'ensoleillement normalisee      real, intent(in):: paprs(klon, klev+1) ! pression a inter-couche (Pa)
36        real, intent(in):: play(klon, klev) ! pression au milieu de couche (Pa)
37      real, intent(in):: paprs(klon, klev+1)      real, intent(in):: tsol(klon) ! temperature du sol (en K)
38      ! paprs----input-R- pression a inter-couche (Pa)      real, intent(in):: albedo(klon) ! albedo du sol (entre 0 et 1)
39      real, intent(in):: play(klon, klev)      real, intent(in):: t(klon, klev) ! temperature (K)
40      ! play----input-R- pression au milieu de couche (Pa)      real, intent(in):: q(klon, klev) ! vapeur d'eau (en kg/kg)
41      real tsol(klon), albedo(klon), alblw(klon)  
     ! albedo---input-R- albedo du sol (entre 0 et 1)  
     ! tsol-----input-R- temperature du sol (en K)  
     real, intent(in):: t(klon, klev)  
     ! t--------input-R- temperature (K)  
     real q(klon, klev)  
     ! q--------input-R- vapeur d'eau (en kg/kg)  
42      real, intent(in):: wo(klon, klev)      real, intent(in):: wo(klon, klev)
43      ! wo-------input-R- contenu en ozone (en kg/kg) correction MPL 100505      ! column-density of ozone in a layer, in kilo-Dobsons
44      real cldfra(klon, klev), cldemi(klon, klev)  
45      ! cldfra---input-R- fraction nuageuse (entre 0 et 1)      real, intent(in):: cldfra(klon, klev) ! fraction nuageuse (entre 0 et 1)
     ! cldemi---input-R- emissivite des nuages dans l'IR (entre 0 et 1)  
46    
47      real cldtaupd(klon, klev)      real, intent(in):: cldemi(klon, klev)
48      ! input-R- epaisseur optique des nuages dans le visible (present-day value)      ! emissivite des nuages dans l'IR (entre 0 et 1)
49    
50        real, intent(in):: cldtaupd(klon, klev)
51        ! epaisseur optique des nuages dans le visible (present-day value)
52    
53      real, intent(out):: heat(klon, klev)      real, intent(out):: heat(klon, klev)
54      ! échauffement atmosphérique (visible) (K/jour)      ! échauffement atmosphérique (visible) (K/jour)
55    
56      real heat0(klon, klev)      real, intent(out):: heat0(klon, klev) ! chauffage solaire ciel clair
57      real cool(klon, klev)      real, intent(out):: cool(klon, klev) ! refroidissement dans l'IR (K/jour)
58      ! cool-----output-R- refroidissement dans l'IR (K/jour)  
59      real cool0(klon, klev)      real, intent(out):: cool0(klon, klev)
60      real radsol(klon)      ! refroidissement infrarouge ciel clair
61      ! radsol---output-R- bilan radiatif net au sol (W/m**2) (+ vers le bas)  
62      real albpla(klon)      real, intent(out):: radsol(klon)
63      ! albpla---output-R- albedo planetaire (entre 0 et 1)      ! bilan radiatif net au sol (W/m**2) (+ vers le bas)
64      real topsw(klon)  
65      ! topsw----output-R- flux solaire net au sommet de l'atm.      real, intent(out):: albpla(klon) ! albedo planetaire (entre 0 et 1)
66        real, intent(out):: topsw(klon) ! flux solaire net au sommet de l'atm.
67    
68      real, intent(out):: toplw(klon)      real, intent(out):: toplw(klon)
69      ! rayonnement infrarouge montant au sommet de l'atmosphère      ! rayonnement infrarouge montant au sommet de l'atmosphère
# Line 93  contains Line 74  contains
74      ! rayonnement infrarouge montant à la surface      ! rayonnement infrarouge montant à la surface
75    
76      real, intent(out):: sollwdown(klon)      real, intent(out):: sollwdown(klon)
77      real topsw0(klon)      real, intent(out):: topsw0(klon)
78      real, intent(out):: toplw0(klon)      real, intent(out):: toplw0(klon)
79      real solsw0(klon), sollw0(klon)      real, intent(out):: solsw0(klon), sollw0(klon)
80      !IM output 3D: SWup, SWdn, LWup, LWdn      REAL, intent(out):: lwdn0(klon, klev+1), lwdn(klon, klev+1)
81      REAL lwdn0(klon, klev+1), lwdn(klon, klev+1)      REAL, intent(out):: lwup0(klon, klev+1), lwup(klon, klev+1)
82      REAL lwup0(klon, klev+1), lwup(klon, klev+1)      REAL, intent(out):: swdn0(klon, klev+1), swdn(klon, klev+1)
83      REAL swdn0(klon, klev+1), swdn(klon, klev+1)      REAL, intent(out):: swup0(klon, klev+1), swup(klon, klev+1)
84      REAL swup0(klon, klev+1), swup(klon, klev+1)  
85        logical, intent(in):: ok_ade ! apply the Aerosol Direct Effect
86      logical ok_ade, ok_aie  
87      ! switches whether to use aerosol direct (indirect) effects or not      real, intent(out):: topswad(klon), solswad(klon)
88      ! ok_ade---input-L- apply the Aerosol Direct Effect or not?      ! aerosol direct forcing at TOA and surface
89      ! ok_aie---input-L- apply the Aerosol Indirect Effect or not?      ! rayonnement solaire net absorb\'e
   
     real tau_ae(klon, klev, 2), piz_ae(klon, klev, 2), cg_ae(klon, klev, 2)  
     ! input-R- aerosol optical properties (calculated in aeropt.F)  
   
     real topswad(klon), solswad(klon)  
     ! output: aerosol direct forcing at TOA and surface  
     ! topswad---output-R- ray. solaire absorbe au sommet de l'atm. (aerosol dir)  
     ! solswad---output-R- ray. solaire net absorbe a la surface (aerosol dir)  
   
     real cldtaupi(klon, klev)  
     ! cloud optical thickness for pre-industrial aerosol concentrations  
     ! (i.e. with a smaller droplet concentration and thus larger droplet radii)  
     ! -input-R- epaisseur optique des nuages dans le visible  
     ! calculated for pre-industrial (pi) aerosol concentrations,  
     ! i.e. with smaller droplet concentration, thus larger droplets,  
     ! thus generally cdltaupi cldtaupd it is needed for the  
     ! diagnostics of the aerosol indirect radiative forcing  
   
     real topswai(klon), solswai(klon)  
     ! output: aerosol indirect forcing atTOA and surface  
     ! topswai---output-R- ray. solaire absorbe au sommet de l'atm. (aerosol ind)  
     ! solswai---output-R- ray. solaire net absorbe a la surface (aerosol ind)  
90    
91      ! Local:      ! Local:
92    
     double precision tauae(kdlon, klev, 2) ! aer opt properties  
     double precision pizae(kdlon, klev, 2)  
     double precision cgae(kdlon, klev, 2)  
   
     !IM output 3D  
93      DOUBLE PRECISION ZFSUP(KDLON, KLEV+1)      DOUBLE PRECISION ZFSUP(KDLON, KLEV+1)
94      DOUBLE PRECISION ZFSDN(KDLON, KLEV+1)      DOUBLE PRECISION ZFSDN(KDLON, KLEV+1)
95      DOUBLE PRECISION ZFSUP0(KDLON, KLEV+1)      DOUBLE PRECISION ZFSUP0(KDLON, KLEV+1)
# Line 155  contains Line 109  contains
109      DOUBLE PRECISION PPSOL(kdlon), PDP(kdlon, klev)      DOUBLE PRECISION PPSOL(kdlon), PDP(kdlon, klev)
110      DOUBLE PRECISION PTL(kdlon, klev+1), PPMB(kdlon, klev+1)      DOUBLE PRECISION PTL(kdlon, klev+1), PPMB(kdlon, klev+1)
111      DOUBLE PRECISION PTAVE(kdlon, klev)      DOUBLE PRECISION PTAVE(kdlon, klev)
112      DOUBLE PRECISION PWV(kdlon, klev), PQS(kdlon, klev), POZON(kdlon, klev)      DOUBLE PRECISION PWV(kdlon, klev), PQS(kdlon, klev)
113      DOUBLE PRECISION PAER(kdlon, klev, 5)      DOUBLE PRECISION POZON(kdlon, klev) ! mass fraction of ozone
114        DOUBLE PRECISION PAER(kdlon, klev, 5) ! AEROSOLS' OPTICAL THICKNESS
115      DOUBLE PRECISION PCLDLD(kdlon, klev)      DOUBLE PRECISION PCLDLD(kdlon, klev)
116      DOUBLE PRECISION PCLDLU(kdlon, klev)      DOUBLE PRECISION PCLDLU(kdlon, klev)
117      DOUBLE PRECISION PCLDSW(kdlon, klev)      DOUBLE PRECISION PCLDSW(kdlon, klev)
# Line 164  contains Line 119  contains
119      DOUBLE PRECISION POMEGA(kdlon, 2, klev)      DOUBLE PRECISION POMEGA(kdlon, 2, klev)
120      DOUBLE PRECISION PCG(kdlon, 2, klev)      DOUBLE PRECISION PCG(kdlon, 2, klev)
121    
122      DOUBLE PRECISION zfract(kdlon), zrmu0(kdlon), zdist      DOUBLE PRECISION zfract(kdlon), zrmu0(kdlon)
123    
124      DOUBLE PRECISION zheat(kdlon, klev), zcool(kdlon, klev)      DOUBLE PRECISION zheat(kdlon, klev), zcool(kdlon, klev)
125      DOUBLE PRECISION zheat0(kdlon, klev), zcool0(kdlon, klev)      DOUBLE PRECISION zheat0(kdlon, klev), zcool0(kdlon, klev)
# Line 177  contains Line 132  contains
132      DOUBLE PRECISION zznormcp      DOUBLE PRECISION zznormcp
133    
134      !jq the following quantities are needed for the aerosol radiative forcings      !jq the following quantities are needed for the aerosol radiative forcings
   
     DOUBLE PRECISION PTAUA(kdlon, 2, klev)  
     ! present-day value of cloud opt thickness (PTAU is pre-industrial  
     ! value), local use  
   
     DOUBLE PRECISION POMEGAA(kdlon, 2, klev) ! dito for single scatt albedo  
   
135      DOUBLE PRECISION ztopswad(kdlon), zsolswad(kdlon)      DOUBLE PRECISION ztopswad(kdlon), zsolswad(kdlon)
136      ! Aerosol direct forcing at TOAand surface      ! Aerosol direct forcing at TOA and surface
137    
138      DOUBLE PRECISION ztopswai(kdlon), zsolswai(kdlon) ! dito, indirect      real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
139    
140      !----------------------------------------------------------------------      !----------------------------------------------------------------------
141    
     tauae = 0.  
     pizae = 0.  
     cgae = 0.  
   
142      nb_gr = klon / kdlon      nb_gr = klon / kdlon
143      IF (nb_gr * kdlon /= klon) THEN      IF (nb_gr * kdlon /= klon) THEN
144         PRINT *, "kdlon mauvais :", klon, kdlon, nb_gr         PRINT *, "kdlon mauvais :", klon, kdlon, nb_gr
145         stop 1         stop 1
146      ENDIF      ENDIF
147        
148      heat = 0.      heat = 0.
149      cool = 0.      cool = 0.
150      heat0 = 0.      heat0 = 0.
151      cool0 = 0.      cool0 = 0.
152      zdist = dist      PSCT = solaire / dist**2
     PSCT = solaire / zdist / zdist  
153    
154      loop_iof: DO iof = 0, klon - kdlon, kdlon      loop_iof: DO iof = 0, klon - kdlon, kdlon
155         DO i = 1, kdlon         DO i = 1, kdlon
156            zfract(i) = fract(iof+i)            zfract(i) = fract(iof+i)
157            zrmu0(i) = rmu0(iof+i)            zrmu0(i) = mu0(iof+i)
158            PALBD(i, 1) = albedo(iof+i)            PALBD(i, 1) = albedo(iof+i)
159            PALBD(i, 2) = alblw(iof+i)            PALBD(i, 2) = albedo(iof+i)
160            PALBP(i, 1) = albedo(iof+i)            PALBP(i, 1) = albedo(iof+i)
161            PALBP(i, 2) = alblw(iof+i)            PALBP(i, 2) = albedo(iof+i)
162            ! cf. JLD pour etre en accord avec ORCHIDEE il faut mettre            ! cf. JLD pour etre en accord avec ORCHIDEE il faut mettre
163            ! PEMIS(i) = 0.96            ! PEMIS(i) = 0.96
164            PEMIS(i) = 1.0            PEMIS(i) = 1.
165            PVIEW(i) = 1.66            PVIEW(i) = 1.66
166            PPSOL(i) = paprs(iof+i, 1)            PPSOL(i) = paprs(iof+i, 1)
167            zx_alpha1 = (paprs(iof+i, 1)-play(iof+i, 2))  &            zx_alpha1 = (paprs(iof+i, 1)-play(iof+i, 2))  &
168                 / (play(iof+i, 1)-play(iof+i, 2))                 / (play(iof+i, 1)-play(iof+i, 2))
169            zx_alpha2 = 1.0 - zx_alpha1            zx_alpha2 = 1. - zx_alpha1
170            PTL(i, 1) = t(iof+i, 1) * zx_alpha1 + t(iof+i, 2) * zx_alpha2            PTL(i, 1) = t(iof+i, 1) * zx_alpha1 + t(iof+i, 2) * zx_alpha2
171            PTL(i, klev+1) = t(iof+i, klev)            PTL(i, klev+1) = t(iof+i, klev)
172            PDT0(i) = tsol(iof+i) - PTL(i, 1)            PDT0(i) = tsol(iof+i) - PTL(i, 1)
# Line 237  contains Line 180  contains
180            DO i = 1, kdlon            DO i = 1, kdlon
181               PDP(i, k) = paprs(iof+i, k)-paprs(iof+i, k+1)               PDP(i, k) = paprs(iof+i, k)-paprs(iof+i, k+1)
182               PTAVE(i, k) = t(iof+i, k)               PTAVE(i, k) = t(iof+i, k)
183               PWV(i, k) = MAX (q(iof+i, k), 1.0e-12)               PWV(i, k) = MAX (q(iof+i, k), 1e-12)
184               PQS(i, k) = PWV(i, k)               PQS(i, k) = PWV(i, k)
185               ! wo:    cm.atm (epaisseur en cm dans la situation standard)               POZON(i, k) = wo(iof+i, k) * RG * dobson_u * 1e3 &
186               ! POZON: kg/kg                    / (paprs(iof+i, k) - paprs(iof+i, k+1))
              IF (bug_ozone) then  
                 POZON(i, k) = MAX(wo(iof+i, k), 1.0e-12)*RG/46.6968 &  
                      /(paprs(iof+i, k)-paprs(iof+i, k+1)) &  
                      *(paprs(iof+i, 1)/101325.0)  
              ELSE  
                 ! le calcul qui suit est maintenant fait dans ozonecm (MPL)  
                 POZON(i, k) = wo(i, k)  
              ENDIF  
187               PCLDLD(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k)               PCLDLD(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k)
188               PCLDLU(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k)               PCLDLU(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k)
189               PCLDSW(i, k) = cldfra(iof+i, k)               PCLDSW(i, k) = cldfra(iof+i, k)
190               PTAU(i, 1, k) = MAX(cldtaupi(iof+i, k), 1.0e-05)               PTAU(i, 1, k) = MAX(cldtaupd(iof+i, k), 1e-05)
191               ! (1e-12 serait instable)               ! (1e-12 serait instable)
192               PTAU(i, 2, k) = MAX(cldtaupi(iof+i, k), 1.0e-05)               PTAU(i, 2, k) = MAX(cldtaupd(iof+i, k), 1e-05)
193               ! (pour 32-bit machines)               ! (pour 32-bit machines)
194               POMEGA(i, 1, k) = 0.9999 - 5.0e-04 * EXP(-0.5 * PTAU(i, 1, k))               POMEGA(i, 1, k) = 0.9999 - 5e-04 * EXP(-0.5 * PTAU(i, 1, k))
195               POMEGA(i, 2, k) = 0.9988 - 2.5e-03 * EXP(-0.05 * PTAU(i, 2, k))               POMEGA(i, 2, k) = 0.9988 - 2.5e-03 * EXP(-0.05 * PTAU(i, 2, k))
196               PCG(i, 1, k) = 0.865               PCG(i, 1, k) = 0.865
197               PCG(i, 2, k) = 0.910               PCG(i, 2, k) = 0.910
   
              ! Introduced for aerosol indirect forcings.  The  
              ! following values use the cloud optical thickness  
              ! calculated from present-day aerosol concentrations  
              ! whereas the quantities without the "A" at the end are  
              ! for pre-industial (natural-only) aerosol concentrations  
              PTAUA(i, 1, k) = MAX(cldtaupd(iof+i, k), 1.0e-05)  
              ! (1e-12 serait instable)  
              PTAUA(i, 2, k) = MAX(cldtaupd(iof+i, k), 1.0e-05)  
              ! (pour 32-bit machines)  
              POMEGAA(i, 1, k) = 0.9999 - 5.0e-04 * EXP(-0.5 * PTAUA(i, 1, k))  
              POMEGAA(i, 2, k) = 0.9988 - 2.5e-03 * EXP(-0.05 * PTAUA(i, 2, k))  
              !jq-end  
198            ENDDO            ENDDO
199         ENDDO         ENDDO
200    
201         DO k = 1, klev+1         DO k = 1, klev+1
202            DO i = 1, kdlon            DO i = 1, kdlon
203               PPMB(i, k) = paprs(iof+i, k)/100.0               PPMB(i, k) = paprs(iof+i, k)/100.
204            ENDDO            ENDDO
205         ENDDO         ENDDO
206    
207         DO kk = 1, 5         DO kk = 1, 5
208            DO k = 1, klev            DO k = 1, klev
209               DO i = 1, kdlon               DO i = 1, kdlon
210                  PAER(i, k, kk) = 1.0E-15                  PAER(i, k, kk) = 1E-15
211               ENDDO               ENDDO
212            ENDDO            ENDDO
213         ENDDO         ENDDO
214    
215         DO k = 1, klev         CALL LW(PPMB, PDP, PDT0, PEMIS, PTL, PTAVE, PWV, POZON, PAER, PCLDLD, &
216            DO i = 1, kdlon              PCLDLU, PVIEW, zcool, zcool0, ztoplw, zsollw, ztoplw0, zsollw0, &
217               tauae(i, k, 1) = tau_ae(iof+i, k, 1)              zsollwdown, ZFLUP, ZFLDN, ZFLUP0, ZFLDN0)
              pizae(i, k, 1) = piz_ae(iof+i, k, 1)  
              cgae(i, k, 1) =cg_ae(iof+i, k, 1)  
              tauae(i, k, 2) = tau_ae(iof+i, k, 2)  
              pizae(i, k, 2) = piz_ae(iof+i, k, 2)  
              cgae(i, k, 2) =cg_ae(iof+i, k, 2)  
           ENDDO  
        ENDDO  
   
        CALL LW(PPMB, PDP, PPSOL, PDT0, PEMIS, PTL, PTAVE, PWV, POZON, PAER, &  
             PCLDLD, PCLDLU, PVIEW, zcool, zcool0, ztoplw, zsollw, ztoplw0, &  
             zsollw0, zsollwdown, ZFLUP, ZFLDN, ZFLUP0, ZFLDN0)  
218         CALL SW(PSCT, zrmu0, zfract, PPMB, PDP, PPSOL, PALBD, PALBP, PTAVE, &         CALL SW(PSCT, zrmu0, zfract, PPMB, PDP, PPSOL, PALBD, PALBP, PTAVE, &
219              PWV, PQS, POZON, PAER, PCLDSW, PTAU, POMEGA, PCG, zheat, zheat0, &              PWV, PQS, POZON, PCLDSW, PTAU, POMEGA, PCG, zheat, zheat0, &
220              zalbpla, ztopsw, zsolsw, ztopsw0, zsolsw0, ZFSUP, ZFSDN, ZFSUP0, &              zalbpla, ztopsw, zsolsw, ztopsw0, zsolsw0, ZFSUP, ZFSDN, ZFSUP0, &
221              ZFSDN0, tauae, pizae, cgae, PTAUA, POMEGAA, ztopswad, zsolswad, &              ZFSDN0, ztopswad, zsolswad, ok_ade)
             ztopswai, zsolswai, ok_ade, ok_aie)  
222    
223         DO i = 1, kdlon         DO i = 1, kdlon
224            radsol(iof+i) = zsolsw(i) + zsollw(i)            radsol(iof+i) = zsolsw(i) + zsollw(i)
# Line 346  contains Line 256  contains
256            ENDDO            ENDDO
257         ELSE         ELSE
258            DO i = 1, kdlon            DO i = 1, kdlon
259               topswad(iof+i) = 0.0               topswad(iof+i) = 0.
260               solswad(iof+i) = 0.0               solswad(iof+i) = 0.
           ENDDO  
        ENDIF  
        IF (ok_aie) THEN  
           DO i = 1, kdlon  
              topswai(iof+i) = ztopswai(i)  
              solswai(iof+i) = zsolswai(i)  
           ENDDO  
        ELSE  
           DO i = 1, kdlon  
              topswai(iof+i) = 0.0  
              solswai(iof+i) = 0.0  
261            ENDDO            ENDDO
262         ENDIF         ENDIF
263    

Legend:
Removed from v.76  
changed lines
  Added in v.220

  ViewVC Help
Powered by ViewVC 1.1.21