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

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

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

revision 69 by guez, Mon Feb 18 16:33:12 2013 UTC revision 72 by guez, Tue Jul 23 13:00:07 2013 UTC
# Line 4  module radlwsw_m Line 4  module radlwsw_m
4    
5  contains  contains
6    
7    SUBROUTINE radlwsw(dist, rmu0, fract, paprs, pplay, tsol, albedo, alblw, &    SUBROUTINE radlwsw(dist, rmu0, fract, paprs, play, tsol, albedo, alblw, &
8         t, q, wo, cldfra, cldemi, cldtaupd, heat, heat0, cool, cool0, radsol, &         t, q, wo, cldfra, cldemi, cldtaupd, heat, heat0, cool, cool0, radsol, &
9         albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, toplw0, solsw0, &         albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, toplw0, solsw0, &
10         sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, swup0, swup, ok_ade, &         sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, swup0, swup, ok_ade, &
# Line 35  contains Line 35  contains
35      ! aerosol indirect forcing is F_{AI} = topsw - topswai      ! aerosol indirect forcing is F_{AI} = topsw - topswai
36      ! aerosol direct forcing is F_{AD} = topswai - topswad      ! aerosol direct forcing is F_{AD} = topswai - topswad
37    
     USE dimphy, ONLY: klev, klon  
38      USE clesphys, ONLY: bug_ozone, solaire      USE clesphys, ONLY: bug_ozone, solaire
39      USE suphec_m, ONLY: rg      USE dimphy, ONLY: klev, klon
40        use lw_m, only: lw
41      USE raddim, ONLY: kdlon      USE raddim, ONLY: kdlon
42      USE yoethf_m, ONLY: rvtmp2      USE suphec_m, ONLY: rg
43      use sw_m, only: sw      use sw_m, only: sw
44        USE yoethf_m, ONLY: rvtmp2
45                    
46      ! Arguments:      ! Arguments:
47    
48      real rmu0(klon), fract(klon), dist      real dist, rmu0(klon), fract(klon)
49      ! dist-----input-R- distance astronomique terre-soleil      ! dist-----input-R- distance astronomique terre-soleil
50      ! rmu0-----input-R- cosinus de l'angle zenithal      ! rmu0-----input-R- cosinus de l'angle zenithal
51      ! fract----input-R- duree d'ensoleillement normalisee      ! fract----input-R- duree d'ensoleillement normalisee
52    
53      real, intent(in):: paprs(klon, klev+1)      real, intent(in):: paprs(klon, klev+1)
54      ! paprs----input-R- pression a inter-couche (Pa)      ! paprs----input-R- pression a inter-couche (Pa)
55      real, intent(in):: pplay(klon, klev)      real, intent(in):: play(klon, klev)
56      ! pplay----input-R- pression au milieu de couche (Pa)      ! play----input-R- pression au milieu de couche (Pa)
57      real albedo(klon), alblw(klon), tsol(klon)      real tsol(klon), albedo(klon), alblw(klon)
58      ! albedo---input-R- albedo du sol (entre 0 et 1)      ! albedo---input-R- albedo du sol (entre 0 et 1)
59      ! tsol-----input-R- temperature du sol (en K)      ! tsol-----input-R- temperature du sol (en K)
60      real, intent(in):: t(klon, klev)      real, intent(in):: t(klon, klev)
# Line 72  contains Line 73  contains
73      real, intent(out):: heat(klon, klev)      real, intent(out):: heat(klon, klev)
74      ! échauffement atmosphérique (visible) (K/jour)      ! échauffement atmosphérique (visible) (K/jour)
75    
76        real heat0(klon, klev)
77      real cool(klon, klev)      real cool(klon, klev)
78      ! cool-----output-R- refroidissement dans l'IR (K/jour)      ! cool-----output-R- refroidissement dans l'IR (K/jour)
79      real heat0(klon, klev), cool0(klon, klev)      real cool0(klon, klev)
80      real radsol(klon), topsw(klon)      real radsol(klon)
81      ! radsol---output-R- bilan radiatif net au sol (W/m**2) (+ vers le bas)      ! radsol---output-R- bilan radiatif net au sol (W/m**2) (+ vers le bas)
82        real albpla(klon)
83        ! albpla---output-R- albedo planetaire (entre 0 et 1)
84        real topsw(klon)
85      ! topsw----output-R- flux solaire net au sommet de l'atm.      ! topsw----output-R- flux solaire net au sommet de l'atm.
86    
87      real, intent(out):: toplw(klon)      real, intent(out):: toplw(klon)
88      ! rayonnement infrarouge montant au sommet de l'atmosphère      ! rayonnement infrarouge montant au sommet de l'atmosphère
89    
90      real solsw(klon), sollw(klon), albpla(klon)      real, intent(out):: solsw(klon) ! flux solaire net à la surface
91      ! solsw----output-R- flux solaire net a la surface  
92      ! sollw----output-R- ray. IR montant a la surface      real, intent(out):: sollw(klon)
93      ! albpla---output-R- albedo planetaire (entre 0 et 1)      ! rayonnement infrarouge montant à la surface
94      real topsw0(klon), solsw0(klon), sollw0(klon)  
95        real, intent(out):: sollwdown(klon)
96        real topsw0(klon)
97      real, intent(out):: toplw0(klon)      real, intent(out):: toplw0(klon)
98      real sollwdown(klon)      real solsw0(klon), sollw0(klon)
99        !IM output 3D: SWup, SWdn, LWup, LWdn
100        REAL lwdn0(klon, klev+1), lwdn(klon, klev+1)
101        REAL lwup0(klon, klev+1), lwup(klon, klev+1)
102        REAL swdn0(klon, klev+1), swdn(klon, klev+1)
103        REAL swup0(klon, klev+1), swup(klon, klev+1)
104    
105        logical ok_ade, ok_aie
106        ! switches whether to use aerosol direct (indirect) effects or not
107        ! ok_ade---input-L- apply the Aerosol Direct Effect or not?
108        ! ok_aie---input-L- apply the Aerosol Indirect Effect or not?
109    
110        real tau_ae(klon, klev, 2), piz_ae(klon, klev, 2), cg_ae(klon, klev, 2)
111        ! input-R- aerosol optical properties (calculated in aeropt.F)
112    
113        real topswad(klon), solswad(klon)
114        ! output: aerosol direct forcing at TOA and surface
115        ! topswad---output-R- ray. solaire absorbe au sommet de l'atm. (aerosol dir)
116        ! solswad---output-R- ray. solaire net absorbe a la surface (aerosol dir)
117    
118        real cldtaupi(klon, klev)
119        ! cloud optical thickness for pre-industrial aerosol concentrations
120        ! (i.e. with a smaller droplet concentration and thus larger droplet radii)
121        ! -input-R- epaisseur optique des nuages dans le visible
122        ! calculated for pre-industrial (pi) aerosol concentrations,
123        ! i.e. with smaller droplet concentration, thus larger droplets,
124        ! thus generally cdltaupi cldtaupd it is needed for the
125        ! diagnostics of the aerosol indirect radiative forcing
126    
127        real topswai(klon), solswai(klon)
128        ! output: aerosol indirect forcing atTOA and surface
129        ! topswai---output-R- ray. solaire absorbe au sommet de l'atm. (aerosol ind)
130        ! solswai---output-R- ray. solaire net absorbe a la surface (aerosol ind)
131    
132        ! Local:
133    
134        double precision tauae(kdlon, klev, 2) ! aer opt properties
135        double precision pizae(kdlon, klev, 2)
136        double precision cgae(kdlon, klev, 2)
137    
138      !IM output 3D      !IM output 3D
139      DOUBLE PRECISION ZFSUP(KDLON, KLEV+1)      DOUBLE PRECISION ZFSUP(KDLON, KLEV+1)
140      DOUBLE PRECISION ZFSDN(KDLON, KLEV+1)      DOUBLE PRECISION ZFSDN(KDLON, KLEV+1)
# Line 101  contains Line 147  contains
147      DOUBLE PRECISION ZFLDN0(KDLON, KLEV+1)      DOUBLE PRECISION ZFLDN0(KDLON, KLEV+1)
148    
149      DOUBLE PRECISION zx_alpha1, zx_alpha2      DOUBLE PRECISION zx_alpha1, zx_alpha2
   
150      INTEGER k, kk, i, iof, nb_gr      INTEGER k, kk, i, iof, nb_gr
     EXTERNAL lw  
   
151      DOUBLE PRECISION PSCT      DOUBLE PRECISION PSCT
152    
153      DOUBLE PRECISION PALBD(kdlon, 2), PALBP(kdlon, 2)      DOUBLE PRECISION PALBD(kdlon, 2), PALBP(kdlon, 2)
# Line 132  contains Line 175  contains
175      DOUBLE PRECISION ztopsw0(kdlon), ztoplw0(kdlon)      DOUBLE PRECISION ztopsw0(kdlon), ztoplw0(kdlon)
176      DOUBLE PRECISION zsolsw0(kdlon), zsollw0(kdlon)      DOUBLE PRECISION zsolsw0(kdlon), zsollw0(kdlon)
177      DOUBLE PRECISION zznormcp      DOUBLE PRECISION zznormcp
     !IM output 3D: SWup, SWdn, LWup, LWdn  
     REAL swdn(klon, klev+1), swdn0(klon, klev+1)  
     REAL swup(klon, klev+1), swup0(klon, klev+1)  
     REAL lwdn(klon, klev+1), lwdn0(klon, klev+1)  
     REAL lwup(klon, klev+1), lwup0(klon, klev+1)  
178    
179      !jq the following quantities are needed for the aerosol radiative forcings      !jq the following quantities are needed for the aerosol radiative forcings
180    
     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 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)  
   
     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 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  
   
     logical ok_ade, ok_aie  
     ! switches whether to use aerosol direct (indirect) effects or not  
     ! ok_ade---input-L- apply the Aerosol Direct Effect or not?  
     ! ok_aie---input-L- apply the Aerosol Indirect Effect or not?  
   
     double precision tauae(kdlon, klev, 2) ! aer opt properties  
     double precision pizae(kdlon, klev, 2)  
     double precision cgae(kdlon, klev, 2)  
   
181      DOUBLE PRECISION PTAUA(kdlon, 2, klev)      DOUBLE PRECISION PTAUA(kdlon, 2, klev)
182      ! present-day value of cloud opt thickness (PTAU is pre-industrial      ! present-day value of cloud opt thickness (PTAU is pre-industrial
183      ! value), local use      ! value), local use
# Line 214  contains Line 221  contains
221            PEMIS(i) = 1.0            PEMIS(i) = 1.0
222            PVIEW(i) = 1.66            PVIEW(i) = 1.66
223            PPSOL(i) = paprs(iof+i, 1)            PPSOL(i) = paprs(iof+i, 1)
224            zx_alpha1 = (paprs(iof+i, 1)-pplay(iof+i, 2))  &            zx_alpha1 = (paprs(iof+i, 1)-play(iof+i, 2))  &
225                 / (pplay(iof+i, 1)-pplay(iof+i, 2))                 / (play(iof+i, 1)-play(iof+i, 2))
226            zx_alpha2 = 1.0 - zx_alpha1            zx_alpha2 = 1.0 - zx_alpha1
227            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
228            PTL(i, klev+1) = t(iof+i, klev)            PTL(i, klev+1) = t(iof+i, klev)

Legend:
Removed from v.69  
changed lines
  Added in v.72

  ViewVC Help
Powered by ViewVC 1.1.21