--- trunk/libf/phylmd/Radlwsw/radlwsw.f90 2011/10/07 13:11:58 53 +++ trunk/Sources/phylmd/Radlwsw/radlwsw.f 2015/07/08 17:03:45 155 @@ -4,7 +4,7 @@ contains - SUBROUTINE radlwsw(dist, rmu0, fract, paprs, pplay, tsol, albedo, alblw, & + SUBROUTINE radlwsw(dist, mu0, fract, paprs, play, tsol, albedo, & t, q, wo, cldfra, cldemi, cldtaupd, heat, heat0, cool, cool0, radsol, & albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, toplw0, solsw0, & sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, swup0, swup, ok_ade, & @@ -12,81 +12,124 @@ solswai) ! From LMDZ4/libf/phylmd/radlwsw.F, version 1.4 2005/06/06 13:16:33 - ! Author: Z. X. Li (LMD/CNRS) date: 1996/07/19 - ! Objet : interface entre le modèle et les rayonnements - ! Rayonnements solaire et infrarouge + ! Author: Z. X. Li (LMD/CNRS) + ! Date: 1996/07/19 + ! Objet : interface entre le modèle et les rayonnements solaire et + ! infrarouge + + ! ATTENTION: swai and swad have to be interpreted in the following manner: + + ! not ok_ade and not ok_aie + ! 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: solaire USE dimphy, ONLY: klev, klon - USE clesphys, ONLY: bug_ozone, solaire - USE suphec_m, ONLY: rg + use lw_m, only: lw USE raddim, ONLY: kdlon - USE yoethf_m, ONLY: rvtmp2 + USE suphec_m, ONLY: rg use sw_m, only: sw + USE yoethf_m, ONLY: rvtmp2 ! Arguments: - ! dist-----input-R- distance astronomique terre-soleil - ! rmu0-----input-R- cosinus de l'angle zenithal - ! fract----input-R- duree d'ensoleillement normalisee - ! co2_ppm--input-R- concentration du gaz carbonique (en ppm) - ! solaire--input-R- constante solaire (W/m**2) - ! paprs----input-R- pression a inter-couche (Pa) - ! pplay----input-R- pression au milieu de couche (Pa) - ! tsol-----input-R- temperature du sol (en K) - ! albedo---input-R- albedo du sol (entre 0 et 1) - ! t--------input-R- temperature (K) + + real, intent(in):: dist ! distance astronomique terre-soleil + real, intent(in):: mu0(klon) ! cosinus de l'angle zenithal + real, intent(in):: fract(klon) ! duree d'ensoleillement normalisee + real, intent(in):: paprs(klon, klev+1) ! pression a inter-couche (Pa) + real, intent(in):: play(klon, klev) ! pression au milieu de couche (Pa) + real, intent(in):: tsol(klon) ! temperature du sol (en K) + real, intent(in):: albedo(klon) ! albedo du sol (entre 0 et 1) + real, intent(in):: t(klon, klev) ! temperature (K) + real q(klon, klev) ! q--------input-R- vapeur d'eau (en kg/kg) - ! wo-------input-R- contenu en ozone (en kg/kg) correction MPL 100505 + + real, intent(in):: wo(klon, klev) + ! column-density of ozone in a layer, in kilo-Dobsons + + real cldfra(klon, klev), cldemi(klon, klev) ! cldfra---input-R- fraction nuageuse (entre 0 et 1) - ! cldtaupd---input-R- epaisseur optique des nuages dans le visible (present-day value) ! cldemi---input-R- emissivite des nuages dans l'IR (entre 0 et 1) - ! ok_ade---input-L- apply the Aerosol Direct Effect or not? - ! ok_aie---input-L- apply the Aerosol Indirect Effect or not? - ! tau_ae, piz_ae, cg_ae-input-R- aerosol optical properties (calculated in aeropt.F) - ! cldtaupi-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 cldtaupd(klon, klev) + ! input-R- epaisseur optique des nuages dans le visible (present-day value) + + real, intent(out):: heat(klon, klev) + ! échauffement atmosphérique (visible) (K/jour) + + real heat0(klon, klev) + real cool(klon, klev) ! cool-----output-R- refroidissement dans l'IR (K/jour) + real cool0(klon, klev) + real radsol(klon) ! radsol---output-R- bilan radiatif net au sol (W/m**2) (+ vers le bas) - ! albpla---output-R- albedo planetaire (entre 0 et 1) + real, intent(out):: albpla(klon) ! albedo planetaire (entre 0 et 1) + real topsw(klon) ! topsw----output-R- flux solaire net au sommet de l'atm. - ! toplw----output-R- ray. IR montant au sommet de l'atmosphere - ! solsw----output-R- flux solaire net a la surface - ! sollw----output-R- ray. IR montant a la surface - ! solswad---output-R- ray. solaire net absorbe a la surface (aerosol dir) + + real, intent(out):: toplw(klon) + ! rayonnement infrarouge montant au sommet de l'atmosphère + + real, intent(out):: solsw(klon) ! flux solaire net à la surface + + real, intent(out):: sollw(klon) + ! rayonnement infrarouge montant à la surface + + real, intent(out):: sollwdown(klon) + real topsw0(klon) + real, intent(out):: toplw0(klon) + real solsw0(klon), sollw0(klon) + !IM output 3D: SWup, SWdn, LWup, LWdn + REAL lwdn0(klon, klev+1), lwdn(klon, klev+1) + REAL lwup0(klon, klev+1), lwup(klon, klev+1) + REAL swdn0(klon, klev+1), swdn(klon, klev+1) + REAL swup0(klon, klev+1), swup(klon, klev+1) + + 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? + + 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) - ! solswai---output-R- ray. solaire net absorbe a la surface (aerosol ind) + ! 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) - ! ATTENTION: swai and swad have to be interpreted in the following manner: - ! ok_ade = F & ok_aie = F -both are zero - ! ok_ade = T & ok_aie = F -aerosol direct forcing is F_{AD} = topsw-topswad - ! indirect is zero - ! ok_ade = F & ok_aie = T -aerosol indirect forcing is F_{AI} = topsw-topswai - ! direct is zero - ! ok_ade = T & ok_aie = T -aerosol indirect forcing is F_{AI} = topsw-topswai - ! aerosol direct forcing is F_{AD} = topswai-topswad - - real rmu0(klon), fract(klon), dist - - real, intent(in):: paprs(klon, klev+1) - real, intent(in):: pplay(klon, klev) - real albedo(klon), alblw(klon), tsol(klon) - real, intent(in):: t(klon, klev) - real q(klon, klev) - real, intent(in):: wo(klon, klev) - real cldfra(klon, klev), cldemi(klon, klev), cldtaupd(klon, klev) + ! Local: - real, intent(out):: heat(klon, klev) - ! échauffement atmosphérique (visible) (K/jour) + double precision tauae(kdlon, klev, 2) ! aer opt properties + double precision pizae(kdlon, klev, 2) + double precision cgae(kdlon, klev, 2) - real cool(klon, klev) - real heat0(klon, klev), cool0(klon, klev) - real radsol(klon), topsw(klon), toplw(klon) - real solsw(klon), sollw(klon), albpla(klon) - real topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon) - real sollwdown(klon) !IM output 3D DOUBLE PRECISION ZFSUP(KDLON, KLEV+1) DOUBLE PRECISION ZFSDN(KDLON, KLEV+1) @@ -99,10 +142,7 @@ DOUBLE PRECISION ZFLDN0(KDLON, KLEV+1) DOUBLE PRECISION zx_alpha1, zx_alpha2 - - INTEGER k, kk, i, j, iof, nb_gr - EXTERNAL lw - + INTEGER k, kk, i, iof, nb_gr DOUBLE PRECISION PSCT DOUBLE PRECISION PALBD(kdlon, 2), PALBP(kdlon, 2) @@ -110,7 +150,8 @@ DOUBLE PRECISION PPSOL(kdlon), PDP(kdlon, klev) DOUBLE PRECISION PTL(kdlon, klev+1), PPMB(kdlon, klev+1) DOUBLE PRECISION PTAVE(kdlon, klev) - DOUBLE PRECISION PWV(kdlon, klev), PQS(kdlon, klev), POZON(kdlon, klev) + DOUBLE PRECISION PWV(kdlon, klev), PQS(kdlon, klev) + DOUBLE PRECISION POZON(kdlon, klev) ! mass fraction of ozone DOUBLE PRECISION PAER(kdlon, klev, 5) DOUBLE PRECISION PCLDLD(kdlon, klev) DOUBLE PRECISION PCLDLU(kdlon, klev) @@ -119,7 +160,7 @@ DOUBLE PRECISION POMEGA(kdlon, 2, klev) DOUBLE PRECISION PCG(kdlon, 2, klev) - DOUBLE PRECISION zfract(kdlon), zrmu0(kdlon), zdist + DOUBLE PRECISION zfract(kdlon), zrmu0(kdlon) DOUBLE PRECISION zheat(kdlon, klev), zcool(kdlon, klev) DOUBLE PRECISION zheat0(kdlon, klev), zcool0(kdlon, klev) @@ -130,34 +171,9 @@ DOUBLE PRECISION ztopsw0(kdlon), ztoplw0(kdlon) DOUBLE PRECISION zsolsw0(kdlon), zsollw0(kdlon) 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) !jq the following quantities are needed for the aerosol radiative forcings - real topswad(klon), solswad(klon) - ! output: aerosol direct forcing at TOA and surface - - real topswai(klon), solswai(klon) - ! output: aerosol indirect forcing atTOA and surface - - real tau_ae(klon, klev, 2), piz_ae(klon, klev, 2), cg_ae(klon, klev, 2) - ! aerosol optical properties (see aeropt.F) - - real cldtaupi(klon, klev) - ! cloud optical thickness for pre-industrial aerosol concentrations - ! (i.e., with a smaller droplet concentrationand thus larger droplet radii) - - logical ok_ade, ok_aie - ! switches whether to use aerosol direct (indirect) effects or not - - double precision tauae(kdlon, klev, 2) ! aer opt properties - double precision pizae(kdlon, klev, 2) - double precision cgae(kdlon, klev, 2) - DOUBLE PRECISION PTAUA(kdlon, 2, klev) ! present-day value of cloud opt thickness (PTAU is pre-industrial ! value), local use @@ -168,6 +184,7 @@ ! Aerosol direct forcing at TOAand surface DOUBLE PRECISION ztopswai(kdlon), zsolswai(kdlon) ! dito, indirect + real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2 !---------------------------------------------------------------------- @@ -185,26 +202,23 @@ cool = 0. heat0 = 0. cool0 = 0. - zdist = dist - PSCT = solaire / zdist / zdist - - loop_nbgr: DO j = 1, nb_gr - iof = kdlon * (j - 1) + PSCT = solaire / dist**2 + loop_iof: DO iof = 0, klon - kdlon, kdlon DO i = 1, kdlon zfract(i) = fract(iof+i) - zrmu0(i) = rmu0(iof+i) + zrmu0(i) = mu0(iof+i) PALBD(i, 1) = albedo(iof+i) - PALBD(i, 2) = alblw(iof+i) + PALBD(i, 2) = albedo(iof+i) PALBP(i, 1) = albedo(iof+i) - PALBP(i, 2) = alblw(iof+i) + PALBP(i, 2) = albedo(iof+i) ! cf. JLD pour etre en accord avec ORCHIDEE il faut mettre ! PEMIS(i) = 0.96 PEMIS(i) = 1.0 PVIEW(i) = 1.66 PPSOL(i) = paprs(iof+i, 1) - zx_alpha1 = (paprs(iof+i, 1)-pplay(iof+i, 2)) & - / (pplay(iof+i, 1)-pplay(iof+i, 2)) + zx_alpha1 = (paprs(iof+i, 1)-play(iof+i, 2)) & + / (play(iof+i, 1)-play(iof+i, 2)) zx_alpha2 = 1.0 - zx_alpha1 PTL(i, 1) = t(iof+i, 1) * zx_alpha1 + t(iof+i, 2) * zx_alpha2 PTL(i, klev+1) = t(iof+i, klev) @@ -221,16 +235,8 @@ PTAVE(i, k) = t(iof+i, k) PWV(i, k) = MAX (q(iof+i, k), 1.0e-12) PQS(i, k) = PWV(i, k) - ! wo: cm.atm (epaisseur en cm dans la situation standard) - ! POZON: kg/kg - 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 + POZON(i, k) = wo(iof+i, k) * RG * dobson_u * 1e3 & + / (paprs(iof+i, k) - paprs(iof+i, k+1)) PCLDLD(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k) PCLDLU(i, k) = cldfra(iof+i, k)*cldemi(iof+i, k) PCLDSW(i, k) = cldfra(iof+i, k) @@ -283,9 +289,9 @@ 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) + CALL LW(PPMB, PDP, PDT0, PEMIS, PTL, PTAVE, PWV, POZON, PAER, PCLDLD, & + PCLDLU, PVIEW, zcool, zcool0, ztoplw, zsollw, ztoplw0, zsollw0, & + zsollwdown, ZFLUP, ZFLDN, ZFLUP0, ZFLDN0) CALL SW(PSCT, zrmu0, zfract, PPMB, PDP, PPSOL, PALBD, PALBP, PTAVE, & PWV, PQS, POZON, PAER, PCLDSW, PTAU, POMEGA, PCG, zheat, zheat0, & zalbpla, ztopsw, zsolsw, ztopsw0, zsolsw0, ZFSUP, ZFSDN, ZFSUP0, & @@ -355,7 +361,7 @@ cool0(iof+i, k) = zcool0(i, k)/zznormcp ENDDO ENDDO - end DO loop_nbgr + end DO loop_iof END SUBROUTINE radlwsw