/[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 134 by guez, Wed Apr 29 15:47:56 2015 UTC revision 213 by guez, Mon Feb 27 15:44:55 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, 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, ok_aie, &
11         ok_aie, tau_ae, piz_ae, cg_ae, topswad, solswad, cldtaupi, topswai, &         tau_ae, piz_ae, cg_ae, topswad, solswad, cldtaupi, topswai, solswai)
        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)
# Line 43  contains Line 42  contains
42      use sw_m, only: sw      use sw_m, only: sw
43      USE yoethf_m, ONLY: rvtmp2      USE yoethf_m, ONLY: rvtmp2
44                    
     ! Arguments:  
   
45      real, intent(in):: dist ! distance astronomique terre-soleil      real, intent(in):: dist ! distance astronomique terre-soleil
46      real, intent(in):: mu0(klon) ! cosinus de l'angle zenithal      real, intent(in):: mu0(klon) ! cosinus de l'angle zenithal
47      real, intent(in):: fract(klon) ! duree d'ensoleillement normalisee      real, intent(in):: fract(klon) ! duree d'ensoleillement normalisee
48      real, intent(in):: paprs(klon, klev+1) ! pression a inter-couche (Pa)      real, intent(in):: paprs(klon, klev+1) ! pression a inter-couche (Pa)
49      real, intent(in):: play(klon, klev) ! pression au milieu de couche (Pa)      real, intent(in):: play(klon, klev) ! pression au milieu de couche (Pa)
50        real, intent(in):: tsol(klon) ! temperature du sol (en K)
51      real tsol(klon), albedo(klon), alblw(klon)      real, intent(in):: albedo(klon) ! albedo du sol (entre 0 et 1)
52      ! albedo---input-R- albedo du sol (entre 0 et 1)      real, intent(in):: t(klon, klev) ! temperature (K)
53      ! tsol-----input-R- temperature du sol (en K)      real, intent(in):: q(klon, klev) ! vapeur d'eau (en kg/kg)
     real, intent(in):: t(klon, klev)  
     ! t--------input-R- temperature (K)  
     real q(klon, klev)  
     ! q--------input-R- vapeur d'eau (en kg/kg)  
54    
55      real, intent(in):: wo(klon, klev)      real, intent(in):: wo(klon, klev)
56      ! column-density of ozone in a layer, in kilo-Dobsons      ! column-density of ozone in a layer, in kilo-Dobsons
57    
58      real cldfra(klon, klev), cldemi(klon, klev)      real, intent(in):: cldfra(klon, klev) ! fraction nuageuse (entre 0 et 1)
     ! cldfra---input-R- fraction nuageuse (entre 0 et 1)  
     ! cldemi---input-R- emissivite des nuages dans l'IR (entre 0 et 1)  
59    
60      real cldtaupd(klon, klev)      real, intent(in):: cldemi(klon, klev)
61      ! input-R- epaisseur optique des nuages dans le visible (present-day value)      ! emissivite des nuages dans l'IR (entre 0 et 1)
62    
63        real, intent(in):: cldtaupd(klon, klev)
64        ! epaisseur optique des nuages dans le visible (present-day value)
65    
66      real, intent(out):: heat(klon, klev)      real, intent(out):: heat(klon, klev)
67      ! échauffement atmosphérique (visible) (K/jour)      ! échauffement atmosphérique (visible) (K/jour)
68    
69      real heat0(klon, klev)      real, intent(out):: heat0(klon, klev) ! chauffage solaire ciel clair
70      real cool(klon, klev)      real, intent(out):: cool(klon, klev) ! refroidissement dans l'IR (K/jour)
71      ! cool-----output-R- refroidissement dans l'IR (K/jour)  
72      real cool0(klon, klev)      real, intent(out):: cool0(klon, klev)
73      real radsol(klon)      ! refroidissement infrarouge ciel clair
74      ! radsol---output-R- bilan radiatif net au sol (W/m**2) (+ vers le bas)  
75      real albpla(klon)      real, intent(out):: radsol(klon)
76      ! albpla---output-R- albedo planetaire (entre 0 et 1)      ! bilan radiatif net au sol (W/m**2) (+ vers le bas)
77      real topsw(klon)  
78      ! topsw----output-R- flux solaire net au sommet de l'atm.      real, intent(out):: albpla(klon) ! albedo planetaire (entre 0 et 1)
79        real, intent(out):: topsw(klon) ! flux solaire net au sommet de l'atm.
80    
81      real, intent(out):: toplw(klon)      real, intent(out):: toplw(klon)
82      ! rayonnement infrarouge montant au sommet de l'atmosphère      ! rayonnement infrarouge montant au sommet de l'atmosphère
# Line 92  contains Line 87  contains
87      ! rayonnement infrarouge montant à la surface      ! rayonnement infrarouge montant à la surface
88    
89      real, intent(out):: sollwdown(klon)      real, intent(out):: sollwdown(klon)
90      real topsw0(klon)      real, intent(out):: topsw0(klon)
91      real, intent(out):: toplw0(klon)      real, intent(out):: toplw0(klon)
92      real solsw0(klon), sollw0(klon)      real, intent(out):: solsw0(klon), sollw0(klon)
93      !IM output 3D: SWup, SWdn, LWup, LWdn      REAL, intent(out):: lwdn0(klon, klev+1), lwdn(klon, klev+1)
94      REAL lwdn0(klon, klev+1), lwdn(klon, klev+1)      REAL, intent(out):: lwup0(klon, klev+1), lwup(klon, klev+1)
95      REAL lwup0(klon, klev+1), lwup(klon, klev+1)      REAL, intent(out):: swdn0(klon, klev+1), swdn(klon, klev+1)
96      REAL swdn0(klon, klev+1), swdn(klon, klev+1)      REAL, intent(out):: swup0(klon, klev+1), swup(klon, klev+1)
97      REAL swup0(klon, klev+1), swup(klon, klev+1)  
98        logical, intent(in):: ok_ade ! apply the Aerosol Direct Effect
99      logical ok_ade, ok_aie      logical, intent(in):: ok_aie ! apply the Aerosol Indirect Effect
100      ! switches whether to use aerosol direct (indirect) effects or not  
101      ! ok_ade---input-L- apply the Aerosol Direct Effect or not?      ! aerosol optical properties (calculated in aeropt.F):
102      ! ok_aie---input-L- apply the Aerosol Indirect Effect or not?      real, intent(in):: tau_ae(klon, klev, 2), piz_ae(klon, klev, 2)
103        real, intent(in):: cg_ae(klon, klev, 2)
104      real tau_ae(klon, klev, 2), piz_ae(klon, klev, 2), cg_ae(klon, klev, 2)  
105      ! input-R- aerosol optical properties (calculated in aeropt.F)      real, intent(out):: topswad(klon), solswad(klon)
106        ! aerosol direct forcing at TOA and surface
107      real topswad(klon), solswad(klon)      ! ray. solaire net absorbe
108      ! output: aerosol direct forcing at TOA and surface      
109      ! topswad---output-R- ray. solaire absorbe au sommet de l'atm. (aerosol dir)      real, intent(in):: cldtaupi(klon, klev)
110      ! solswad---output-R- ray. solaire net absorbe a la surface (aerosol dir)      ! cloud visible optical thickness for pre-industrial aerosol concentrations
   
     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,  
111      ! i.e. with smaller droplet concentration, thus larger droplets,      ! i.e. with smaller droplet concentration, thus larger droplets,
112      ! thus generally cdltaupi cldtaupd it is needed for the      ! thus generally cdltaupi cldtaupd it is needed for the
113      ! diagnostics of the aerosol indirect radiative forcing      ! diagnostics of the aerosol indirect radiative forcing
114    
115      real topswai(klon), solswai(klon)      real, intent(out):: topswai(klon), solswai(klon)
116      ! output: aerosol indirect forcing atTOA and surface      ! aerosol indirect forcing at TOA and surface
117      ! topswai---output-R- ray. solaire absorbe au sommet de l'atm. (aerosol ind)      ! ray. solaire net absorbe
     ! solswai---output-R- ray. solaire net absorbe a la surface (aerosol ind)  
118    
119      ! Local:      ! Local:
120    
# Line 134  contains Line 122  contains
122      double precision pizae(kdlon, klev, 2)      double precision pizae(kdlon, klev, 2)
123      double precision cgae(kdlon, klev, 2)      double precision cgae(kdlon, klev, 2)
124    
     !IM output 3D  
125      DOUBLE PRECISION ZFSUP(KDLON, KLEV+1)      DOUBLE PRECISION ZFSUP(KDLON, KLEV+1)
126      DOUBLE PRECISION ZFSDN(KDLON, KLEV+1)      DOUBLE PRECISION ZFSDN(KDLON, KLEV+1)
127      DOUBLE PRECISION ZFSUP0(KDLON, KLEV+1)      DOUBLE PRECISION ZFSUP0(KDLON, KLEV+1)
# Line 156  contains Line 143  contains
143      DOUBLE PRECISION PTAVE(kdlon, klev)      DOUBLE PRECISION PTAVE(kdlon, klev)
144      DOUBLE PRECISION PWV(kdlon, klev), PQS(kdlon, klev)      DOUBLE PRECISION PWV(kdlon, klev), PQS(kdlon, klev)
145      DOUBLE PRECISION POZON(kdlon, klev) ! mass fraction of ozone      DOUBLE PRECISION POZON(kdlon, klev) ! mass fraction of ozone
146      DOUBLE PRECISION PAER(kdlon, klev, 5)      DOUBLE PRECISION PAER(kdlon, klev, 5) ! AEROSOLS' OPTICAL THICKNESS
147      DOUBLE PRECISION PCLDLD(kdlon, klev)      DOUBLE PRECISION PCLDLD(kdlon, klev)
148      DOUBLE PRECISION PCLDLU(kdlon, klev)      DOUBLE PRECISION PCLDLU(kdlon, klev)
149      DOUBLE PRECISION PCLDSW(kdlon, klev)      DOUBLE PRECISION PCLDSW(kdlon, klev)
# Line 213  contains Line 200  contains
200            zfract(i) = fract(iof+i)            zfract(i) = fract(iof+i)
201            zrmu0(i) = mu0(iof+i)            zrmu0(i) = mu0(iof+i)
202            PALBD(i, 1) = albedo(iof+i)            PALBD(i, 1) = albedo(iof+i)
203            PALBD(i, 2) = alblw(iof+i)            PALBD(i, 2) = albedo(iof+i)
204            PALBP(i, 1) = albedo(iof+i)            PALBP(i, 1) = albedo(iof+i)
205            PALBP(i, 2) = alblw(iof+i)            PALBP(i, 2) = albedo(iof+i)
206            ! cf. JLD pour etre en accord avec ORCHIDEE il faut mettre            ! cf. JLD pour etre en accord avec ORCHIDEE il faut mettre
207            ! PEMIS(i) = 0.96            ! PEMIS(i) = 0.96
208            PEMIS(i) = 1.0            PEMIS(i) = 1.0
# Line 293  contains Line 280  contains
280            ENDDO            ENDDO
281         ENDDO         ENDDO
282    
283         CALL LW(PPMB, PDP, PPSOL, PDT0, PEMIS, PTL, PTAVE, PWV, POZON, PAER, &         CALL LW(PPMB, PDP, PDT0, PEMIS, PTL, PTAVE, PWV, POZON, PAER, PCLDLD, &
284              PCLDLD, PCLDLU, PVIEW, zcool, zcool0, ztoplw, zsollw, ztoplw0, &              PCLDLU, PVIEW, zcool, zcool0, ztoplw, zsollw, ztoplw0, zsollw0, &
285              zsollw0, zsollwdown, ZFLUP, ZFLDN, ZFLUP0, ZFLDN0)              zsollwdown, ZFLUP, ZFLDN, ZFLUP0, ZFLDN0)
286         CALL SW(PSCT, zrmu0, zfract, PPMB, PDP, PPSOL, PALBD, PALBP, PTAVE, &         CALL SW(PSCT, zrmu0, zfract, PPMB, PDP, PPSOL, PALBD, PALBP, PTAVE, &
287              PWV, PQS, POZON, PAER, PCLDSW, PTAU, POMEGA, PCG, zheat, zheat0, &              PWV, PQS, POZON, PCLDSW, PTAU, POMEGA, PCG, zheat, zheat0, &
288              zalbpla, ztopsw, zsolsw, ztopsw0, zsolsw0, ZFSUP, ZFSDN, ZFSUP0, &              zalbpla, ztopsw, zsolsw, ztopsw0, zsolsw0, ZFSUP, ZFSDN, ZFSUP0, &
289              ZFSDN0, tauae, pizae, cgae, PTAUA, POMEGAA, ztopswad, zsolswad, &              ZFSDN0, tauae, pizae, cgae, PTAUA, POMEGAA, ztopswad, zsolswad, &
290              ztopswai, zsolswai, ok_ade, ok_aie)              ztopswai, zsolswai, ok_ade, ok_aie)

Legend:
Removed from v.134  
changed lines
  Added in v.213

  ViewVC Help
Powered by ViewVC 1.1.21