/[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

revision 155 by guez, Wed Jul 8 17:03:45 2015 UTC revision 217 by guez, Thu Mar 30 14:25:18 2017 UTC
# Line 4  module radlwsw_m Line 4  module radlwsw_m
4    
5  contains  contains
6    
7    SUBROUTINE radlwsw(dist, mu0, fract, paprs, play, tsol, albedo, &    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    
# Line 20  contains Line 19  contains
19    
20      ! ATTENTION: swai and swad have to be interpreted in the following manner:      ! ATTENTION: swai and swad have to be interpreted in the following manner:
21    
22      ! not ok_ade and not ok_aie      ! not ok_ade
23      ! both are zero      ! both are zero
24    
25      ! ok_ade and not ok_aie      ! ok_ade
26      ! aerosol direct forcing is F_{AD} = topsw - topswad      ! aerosol direct forcing is F_{AD} = topsw - topswad
27      ! indirect is zero      ! indirect is zero
28    
     ! 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  
   
29      USE clesphys, ONLY: solaire      USE clesphys, ONLY: solaire
30      USE dimphy, ONLY: klev, klon      USE dimphy, ONLY: klev, klon
31      use lw_m, only: lw      use lw_m, only: lw
# Line 42  contains Line 33  contains
33      USE suphec_m, ONLY: rg      USE suphec_m, ONLY: rg
34      use sw_m, only: sw      use sw_m, only: sw
35      USE yoethf_m, ONLY: rvtmp2      USE yoethf_m, ONLY: rvtmp2
           
     ! Arguments:  
36    
37      real, intent(in):: dist ! distance astronomique terre-soleil      real, intent(in):: dist ! distance astronomique terre-soleil
38      real, intent(in):: mu0(klon) ! cosinus de l'angle zenithal      real, intent(in):: mu0(klon) ! cosinus de l'angle zenithal
# Line 53  contains Line 42  contains
42      real, intent(in):: tsol(klon) ! temperature du sol (en K)      real, intent(in):: tsol(klon) ! temperature du sol (en K)
43      real, intent(in):: albedo(klon) ! albedo du sol (entre 0 et 1)      real, intent(in):: albedo(klon) ! albedo du sol (entre 0 et 1)
44      real, intent(in):: t(klon, klev) ! temperature (K)      real, intent(in):: t(klon, klev) ! temperature (K)
45      real q(klon, klev)      real, intent(in):: q(klon, klev) ! vapeur d'eau (en kg/kg)
     ! q--------input-R- vapeur d'eau (en kg/kg)  
46    
47      real, intent(in):: wo(klon, klev)      real, intent(in):: wo(klon, klev)
48      ! column-density of ozone in a layer, in kilo-Dobsons      ! column-density of ozone in a layer, in kilo-Dobsons
49    
50      real cldfra(klon, klev), cldemi(klon, klev)      real, intent(in):: cldfra(klon, klev) ! fraction nuageuse (entre 0 et 1)
51      ! cldfra---input-R- fraction nuageuse (entre 0 et 1)  
52      ! cldemi---input-R- emissivite des nuages dans l'IR (entre 0 et 1)      real, intent(in):: cldemi(klon, klev)
53        ! emissivite des nuages dans l'IR (entre 0 et 1)
54    
55      real cldtaupd(klon, klev)      real, intent(in):: cldtaupd(klon, klev)
56      ! input-R- epaisseur optique des nuages dans le visible (present-day value)      ! epaisseur optique des nuages dans le visible (present-day value)
57    
58      real, intent(out):: heat(klon, klev)      real, intent(out):: heat(klon, klev)
59      ! échauffement atmosphérique (visible) (K/jour)      ! échauffement atmosphérique (visible) (K/jour)
60    
61      real heat0(klon, klev)      real, intent(out):: heat0(klon, klev) ! chauffage solaire ciel clair
62      real cool(klon, klev)      real, intent(out):: cool(klon, klev) ! refroidissement dans l'IR (K/jour)
63      ! cool-----output-R- refroidissement dans l'IR (K/jour)  
64      real cool0(klon, klev)      real, intent(out):: cool0(klon, klev)
65      real radsol(klon)      ! refroidissement infrarouge ciel clair
66      ! radsol---output-R- bilan radiatif net au sol (W/m**2) (+ vers le bas)  
67        real, intent(out):: radsol(klon)
68        ! bilan radiatif net au sol (W/m**2) (+ vers le bas)
69    
70      real, intent(out):: albpla(klon) ! albedo planetaire (entre 0 et 1)      real, intent(out):: albpla(klon) ! albedo planetaire (entre 0 et 1)
71      real topsw(klon)      real, intent(out):: topsw(klon) ! flux solaire net au sommet de l'atm.
     ! topsw----output-R- flux solaire net au sommet de l'atm.  
72    
73      real, intent(out):: toplw(klon)      real, intent(out):: toplw(klon)
74      ! rayonnement infrarouge montant au sommet de l'atmosphère      ! rayonnement infrarouge montant au sommet de l'atmosphère
# Line 88  contains Line 79  contains
79      ! rayonnement infrarouge montant à la surface      ! rayonnement infrarouge montant à la surface
80    
81      real, intent(out):: sollwdown(klon)      real, intent(out):: sollwdown(klon)
82      real topsw0(klon)      real, intent(out):: topsw0(klon)
83      real, intent(out):: toplw0(klon)      real, intent(out):: toplw0(klon)
84      real solsw0(klon), sollw0(klon)      real, intent(out):: solsw0(klon), sollw0(klon)
85      !IM output 3D: SWup, SWdn, LWup, LWdn      REAL, intent(out):: lwdn0(klon, klev+1), lwdn(klon, klev+1)
86      REAL lwdn0(klon, klev+1), lwdn(klon, klev+1)      REAL, intent(out):: lwup0(klon, klev+1), lwup(klon, klev+1)
87      REAL lwup0(klon, klev+1), lwup(klon, klev+1)      REAL, intent(out):: swdn0(klon, klev+1), swdn(klon, klev+1)
88      REAL swdn0(klon, klev+1), swdn(klon, klev+1)      REAL, intent(out):: swup0(klon, klev+1), swup(klon, klev+1)
89      REAL swup0(klon, klev+1), swup(klon, klev+1)  
90        logical, intent(in):: ok_ade ! apply the Aerosol Direct Effect
91      logical ok_ade, ok_aie  
92      ! switches whether to use aerosol direct (indirect) effects or not      real, intent(out):: topswad(klon), solswad(klon)
93      ! ok_ade---input-L- apply the Aerosol Direct Effect or not?      ! aerosol direct forcing at TOA and surface
94      ! 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)  
95    
96      ! Local:      ! Local:
97    
     double precision tauae(kdlon, klev, 2) ! aer opt properties  
     double precision pizae(kdlon, klev, 2)  
     double precision cgae(kdlon, klev, 2)  
   
     !IM output 3D  
98      DOUBLE PRECISION ZFSUP(KDLON, KLEV+1)      DOUBLE PRECISION ZFSUP(KDLON, KLEV+1)
99      DOUBLE PRECISION ZFSDN(KDLON, KLEV+1)      DOUBLE PRECISION ZFSDN(KDLON, KLEV+1)
100      DOUBLE PRECISION ZFSUP0(KDLON, KLEV+1)      DOUBLE PRECISION ZFSUP0(KDLON, KLEV+1)
# Line 152  contains Line 116  contains
116      DOUBLE PRECISION PTAVE(kdlon, klev)      DOUBLE PRECISION PTAVE(kdlon, klev)
117      DOUBLE PRECISION PWV(kdlon, klev), PQS(kdlon, klev)      DOUBLE PRECISION PWV(kdlon, klev), PQS(kdlon, klev)
118      DOUBLE PRECISION POZON(kdlon, klev) ! mass fraction of ozone      DOUBLE PRECISION POZON(kdlon, klev) ! mass fraction of ozone
119      DOUBLE PRECISION PAER(kdlon, klev, 5)      DOUBLE PRECISION PAER(kdlon, klev, 5) ! AEROSOLS' OPTICAL THICKNESS
120      DOUBLE PRECISION PCLDLD(kdlon, klev)      DOUBLE PRECISION PCLDLD(kdlon, klev)
121      DOUBLE PRECISION PCLDLU(kdlon, klev)      DOUBLE PRECISION PCLDLU(kdlon, klev)
122      DOUBLE PRECISION PCLDSW(kdlon, klev)      DOUBLE PRECISION PCLDSW(kdlon, klev)
# Line 188  contains Line 152  contains
152    
153      !----------------------------------------------------------------------      !----------------------------------------------------------------------
154    
     tauae = 0.  
     pizae = 0.  
     cgae = 0.  
   
155      nb_gr = klon / kdlon      nb_gr = klon / kdlon
156      IF (nb_gr * kdlon /= klon) THEN      IF (nb_gr * kdlon /= klon) THEN
157         PRINT *, "kdlon mauvais :", klon, kdlon, nb_gr         PRINT *, "kdlon mauvais :", klon, kdlon, nb_gr
158         stop 1         stop 1
159      ENDIF      ENDIF
160        
161      heat = 0.      heat = 0.
162      cool = 0.      cool = 0.
163      heat0 = 0.      heat0 = 0.
# Line 214  contains Line 174  contains
174            PALBP(i, 2) = albedo(iof+i)            PALBP(i, 2) = albedo(iof+i)
175            ! cf. JLD pour etre en accord avec ORCHIDEE il faut mettre            ! cf. JLD pour etre en accord avec ORCHIDEE il faut mettre
176            ! PEMIS(i) = 0.96            ! PEMIS(i) = 0.96
177            PEMIS(i) = 1.0            PEMIS(i) = 1.
178            PVIEW(i) = 1.66            PVIEW(i) = 1.66
179            PPSOL(i) = paprs(iof+i, 1)            PPSOL(i) = paprs(iof+i, 1)
180            zx_alpha1 = (paprs(iof+i, 1)-play(iof+i, 2))  &            zx_alpha1 = (paprs(iof+i, 1)-play(iof+i, 2))  &
181                 / (play(iof+i, 1)-play(iof+i, 2))                 / (play(iof+i, 1)-play(iof+i, 2))
182            zx_alpha2 = 1.0 - zx_alpha1            zx_alpha2 = 1. - zx_alpha1
183            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
184            PTL(i, klev+1) = t(iof+i, klev)            PTL(i, klev+1) = t(iof+i, klev)
185            PDT0(i) = tsol(iof+i) - PTL(i, 1)            PDT0(i) = tsol(iof+i) - PTL(i, 1)
# Line 233  contains Line 193  contains
193            DO i = 1, kdlon            DO i = 1, kdlon
194               PDP(i, k) = paprs(iof+i, k)-paprs(iof+i, k+1)               PDP(i, k) = paprs(iof+i, k)-paprs(iof+i, k+1)
195               PTAVE(i, k) = t(iof+i, k)               PTAVE(i, k) = t(iof+i, k)
196               PWV(i, k) = MAX (q(iof+i, k), 1.0e-12)               PWV(i, k) = MAX (q(iof+i, k), 1e-12)
197               PQS(i, k) = PWV(i, k)               PQS(i, k) = PWV(i, k)
198               POZON(i, k) = wo(iof+i, k) * RG * dobson_u * 1e3 &               POZON(i, k) = wo(iof+i, k) * RG * dobson_u * 1e3 &
199                    / (paprs(iof+i, k) - paprs(iof+i, k+1))                    / (paprs(iof+i, k) - paprs(iof+i, k+1))
200               PCLDLD(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k)               PCLDLD(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k)
201               PCLDLU(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k)               PCLDLU(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k)
202               PCLDSW(i, k) = cldfra(iof+i, k)               PCLDSW(i, k) = cldfra(iof+i, k)
203               PTAU(i, 1, k) = MAX(cldtaupi(iof+i, k), 1.0e-05)               PTAU(i, 1, k) = MAX(cldtaupd(iof+i, k), 1e-05)
204               ! (1e-12 serait instable)               ! (1e-12 serait instable)
205               PTAU(i, 2, k) = MAX(cldtaupi(iof+i, k), 1.0e-05)               PTAU(i, 2, k) = MAX(cldtaupd(iof+i, k), 1e-05)
206               ! (pour 32-bit machines)               ! (pour 32-bit machines)
207               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))
208               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))
209               PCG(i, 1, k) = 0.865               PCG(i, 1, k) = 0.865
210               PCG(i, 2, k) = 0.910               PCG(i, 2, k) = 0.910
# Line 254  contains Line 214  contains
214               ! calculated from present-day aerosol concentrations               ! calculated from present-day aerosol concentrations
215               ! whereas the quantities without the "A" at the end are               ! whereas the quantities without the "A" at the end are
216               ! for pre-industial (natural-only) aerosol concentrations               ! for pre-industial (natural-only) aerosol concentrations
217               PTAUA(i, 1, k) = MAX(cldtaupd(iof+i, k), 1.0e-05)               PTAUA(i, 1, k) = MAX(cldtaupd(iof+i, k), 1e-05)
218               ! (1e-12 serait instable)               ! (1e-12 serait instable)
219               PTAUA(i, 2, k) = MAX(cldtaupd(iof+i, k), 1.0e-05)               PTAUA(i, 2, k) = MAX(cldtaupd(iof+i, k), 1e-05)
220               ! (pour 32-bit machines)               ! (pour 32-bit machines)
221               POMEGAA(i, 1, k) = 0.9999 - 5.0e-04 * EXP(-0.5 * PTAUA(i, 1, k))               POMEGAA(i, 1, k) = 0.9999 - 5e-04 * EXP(-0.5 * PTAUA(i, 1, k))
222               POMEGAA(i, 2, k) = 0.9988 - 2.5e-03 * EXP(-0.05 * PTAUA(i, 2, k))               POMEGAA(i, 2, k) = 0.9988 - 2.5e-03 * EXP(-0.05 * PTAUA(i, 2, k))
223               !jq-end               !jq-end
224            ENDDO            ENDDO
# Line 266  contains Line 226  contains
226    
227         DO k = 1, klev+1         DO k = 1, klev+1
228            DO i = 1, kdlon            DO i = 1, kdlon
229               PPMB(i, k) = paprs(iof+i, k)/100.0               PPMB(i, k) = paprs(iof+i, k)/100.
230            ENDDO            ENDDO
231         ENDDO         ENDDO
232    
233         DO kk = 1, 5         DO kk = 1, 5
234            DO k = 1, klev            DO k = 1, klev
235               DO i = 1, kdlon               DO i = 1, kdlon
236                  PAER(i, k, kk) = 1.0E-15                  PAER(i, k, kk) = 1E-15
237               ENDDO               ENDDO
238            ENDDO            ENDDO
239         ENDDO         ENDDO
240    
        DO k = 1, klev  
           DO i = 1, kdlon  
              tauae(i, k, 1) = tau_ae(iof+i, k, 1)  
              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  
   
241         CALL LW(PPMB, PDP, PDT0, PEMIS, PTL, PTAVE, PWV, POZON, PAER, PCLDLD, &         CALL LW(PPMB, PDP, PDT0, PEMIS, PTL, PTAVE, PWV, POZON, PAER, PCLDLD, &
242              PCLDLU, PVIEW, zcool, zcool0, ztoplw, zsollw, ztoplw0, zsollw0, &              PCLDLU, PVIEW, zcool, zcool0, ztoplw, zsollw, ztoplw0, zsollw0, &
243              zsollwdown, ZFLUP, ZFLDN, ZFLUP0, ZFLDN0)              zsollwdown, ZFLUP, ZFLDN, ZFLUP0, ZFLDN0)
244         CALL SW(PSCT, zrmu0, zfract, PPMB, PDP, PPSOL, PALBD, PALBP, PTAVE, &         CALL SW(PSCT, zrmu0, zfract, PPMB, PDP, PPSOL, PALBD, PALBP, PTAVE, &
245              PWV, PQS, POZON, PAER, PCLDSW, PTAU, POMEGA, PCG, zheat, zheat0, &              PWV, PQS, POZON, PCLDSW, PTAU, POMEGA, PCG, zheat, zheat0, &
246              zalbpla, ztopsw, zsolsw, ztopsw0, zsolsw0, ZFSUP, ZFSDN, ZFSUP0, &              zalbpla, ztopsw, zsolsw, ztopsw0, zsolsw0, ZFSUP, ZFSDN, ZFSUP0, &
247              ZFSDN0, tauae, pizae, cgae, PTAUA, POMEGAA, ztopswad, zsolswad, &              ZFSDN0, ztopswad, zsolswad, ztopswai, zsolswai, ok_ade)
             ztopswai, zsolswai, ok_ade, ok_aie)  
248    
249         DO i = 1, kdlon         DO i = 1, kdlon
250            radsol(iof+i) = zsolsw(i) + zsollw(i)            radsol(iof+i) = zsolsw(i) + zsollw(i)
# Line 334  contains Line 282  contains
282            ENDDO            ENDDO
283         ELSE         ELSE
284            DO i = 1, kdlon            DO i = 1, kdlon
285               topswad(iof+i) = 0.0               topswad(iof+i) = 0.
286               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  
287            ENDDO            ENDDO
288         ENDIF         ENDIF
289    

Legend:
Removed from v.155  
changed lines
  Added in v.217

  ViewVC Help
Powered by ViewVC 1.1.21