source: LMDZ6/trunk/libf/phylmd/ecrad/rrtm_prepare_gases.F90 @ 3908

Last change on this file since 3908 was 3908, checked in by idelkadi, 3 years ago

Online implementation of the radiative transfer code ECRAD in the LMDZ model.

  • Inclusion of the ecrad directory containing the sources of the ECRAD code
    • interface routine : radiation_scheme.F90
  • Adaptation of compilation scripts :
    • compilation under CPP key CPP_ECRAD
    • compilation with option "-rad ecard" or "-ecard true"
    • The "-rad old/rtm/ecran" build option will need to replace the "-rrtm true" and "-ecrad true" options in the future.
  • Runing LMDZ simulations with ecrad, you need :
    • logical key iflag_rrtm = 2 in physiq.def
    • namelist_ecrad (DefLists?)
    • the directory "data" containing the configuration files is temporarily placed in ../libfphylmd/ecrad/
  • Compilation and execution are tested in the 1D case. The repository under svn would allow to continue the implementation work: tests, verification of the results, ...
File size: 8.7 KB
Line 
1SUBROUTINE RRTM_PREPARE_GASES &
2 &( KIDIA, KFDIA, KLON, KLEV, &
3 &  PAPH , PAP , &
4 &  PTH  , PT  , &
5 &  PQ   , PCO2 , PCH4, PN2O  , PNO2, PC11, PC12, PC22, PCL4, POZN, &
6 &  PCOLDRY, PWBRODL, PWKL, PWX , &
7 &  PAVEL  , PTAVEL , PZ  , PTZ , KREFLECT) 
8
9!----compiled for Cray with -h nopattern----
10
11!     Prepare the units of the gas concentrations for the longwave
12!     RRTM gas absorption model.  This file is adapted from
13!     rrtm_ecrt_140gp_mcica.F90, written mainly by Jean-Jacques
14!     Morcrette.
15
16!- Original
17!     2015-07-15  Robin Hogan
18
19!- Modifications
20
21USE PARKIND1 , ONLY : JPIM, JPRB
22USE YOMHOOK  , ONLY : LHOOK, DR_HOOK
23USE YOMCST   , ONLY : RG
24USE PARRRTM  , ONLY : JPBAND, JPXSEC, JPINPX 
25USE YOMDYNCORE,ONLY : RPLRG
26
27!------------------------------Arguments--------------------------------
28
29IMPLICIT NONE
30
31INTEGER(KIND=JPIM),INTENT(IN)    :: KLON! Number of atmospheres (longitudes)
32INTEGER(KIND=JPIM),INTENT(IN)    :: KLEV! Number of atmospheric layers
33INTEGER(KIND=JPIM),INTENT(IN)    :: KIDIA, KFDIA
34
35REAL(KIND=JPRB)   ,INTENT(IN)    :: PAPH(KLON,KLEV+1) ! Interface pressures (Pa)
36REAL(KIND=JPRB)   ,INTENT(IN)    :: PAP(KLON,KLEV) ! Layer pressures (Pa)
37REAL(KIND=JPRB)   ,INTENT(IN)    :: PTH(KLON,KLEV+1) ! Interface temperatures (K)
38REAL(KIND=JPRB)   ,INTENT(IN)    :: PT(KLON,KLEV) ! Layer temperature (K)
39REAL(KIND=JPRB)   ,INTENT(IN)    :: PQ(KLON,KLEV) ! H2O specific humidity (mmr)
40REAL(KIND=JPRB)   ,INTENT(IN)    :: PCO2(KLON,KLEV) ! CO2 mass mixing ratio
41REAL(KIND=JPRB)   ,INTENT(IN)    :: PCH4(KLON,KLEV) ! CH4 mass mixing ratio
42REAL(KIND=JPRB)   ,INTENT(IN)    :: PN2O(KLON,KLEV) ! N2O mass mixing ratio
43REAL(KIND=JPRB)   ,INTENT(IN)    :: PNO2(KLON,KLEV) ! NO2 mass mixing ratio
44REAL(KIND=JPRB)   ,INTENT(IN)    :: PC11(KLON,KLEV) ! CFC11 mass mixing ratio
45REAL(KIND=JPRB)   ,INTENT(IN)    :: PC12(KLON,KLEV) ! CFC12 mass mixing ratio
46REAL(KIND=JPRB)   ,INTENT(IN)    :: PC22(KLON,KLEV) ! CFC22 mass mixing ratio
47REAL(KIND=JPRB)   ,INTENT(IN)    :: PCL4(KLON,KLEV) ! CCL4  mass mixing ratio
48REAL(KIND=JPRB)   ,INTENT(IN)    :: POZN(KLON,KLEV) ! O3 mass mixing ratio
49
50REAL(KIND=JPRB)   ,INTENT(OUT)   :: PCOLDRY(KIDIA:KFDIA,KLEV)
51REAL(KIND=JPRB)   ,INTENT(OUT)   :: PWBRODL(KIDIA:KFDIA,KLEV) ! broadening gas column density (mol/cm2)
52REAL(KIND=JPRB)   ,INTENT(OUT)   :: PWKL(KIDIA:KFDIA,JPINPX,KLEV)
53REAL(KIND=JPRB)   ,INTENT(OUT)   :: PWX(KIDIA:KFDIA,JPXSEC,KLEV) ! Amount of trace gases
54REAL(KIND=JPRB)   ,INTENT(OUT)   :: PAVEL(KIDIA:KFDIA,KLEV)
55REAL(KIND=JPRB)   ,INTENT(OUT)   :: PTAVEL(KIDIA:KFDIA,KLEV)
56REAL(KIND=JPRB)   ,INTENT(OUT)   :: PZ(KIDIA:KFDIA,0:KLEV)
57REAL(KIND=JPRB)   ,INTENT(OUT)   :: PTZ(KIDIA:KFDIA,0:KLEV)
58INTEGER(KIND=JPIM),INTENT(OUT)   :: KREFLECT(KIDIA:KFDIA)
59
60!      real rch4                       ! CH4 mass mixing ratio
61!      real rn2o                       ! N2O mass mixing ratio
62!      real rcfc11                     ! CFC11 mass mixing ratio
63!      real rcfc12                     ! CFC12 mass mixing ratio
64!      real rcfc22                     ! CFC22 mass mixing ratio
65!      real rccl4                      ! CCl4  mass mixing ratio
66!- from PROFILE             
67!- from SURFACE             
68REAL(KIND=JPRB) :: ZAMD                  ! Effective molecular weight of dry air (g/mol)
69REAL(KIND=JPRB) :: ZAMW                  ! Molecular weight of water vapor (g/mol)
70REAL(KIND=JPRB) :: ZAMCO2                ! Molecular weight of carbon dioxide (g/mol)
71REAL(KIND=JPRB) :: ZAMO                  ! Molecular weight of ozone (g/mol)
72REAL(KIND=JPRB) :: ZAMCH4                ! Molecular weight of methane (g/mol)
73REAL(KIND=JPRB) :: ZAMN2O                ! Molecular weight of nitrous oxide (g/mol)
74REAL(KIND=JPRB) :: ZAMC11                ! Molecular weight of CFC11 (g/mol) - CFCL3
75REAL(KIND=JPRB) :: ZAMC12                ! Molecular weight of CFC12 (g/mol) - CF2CL2
76REAL(KIND=JPRB) :: ZAMC22                ! Molecular weight of CFC22 (g/mol) - CHF2CL
77REAL(KIND=JPRB) :: ZAMCL4                ! Molecular weight of CCl4  (g/mol) - CCL4
78REAL(KIND=JPRB) :: ZAVGDRO               ! Avogadro's number (molecules/mole)
79REAL(KIND=JPRB) :: ZGRAVIT               ! Gravitational acceleration (cm/s**2)
80
81REAL(KIND=JPRB) :: ZSUMMOL
82
83! Atomic weights for conversion from mass to volume mixing ratios; these
84!  are the same values used in ECRT to assure accurate conversion to vmr
85data ZAMD   /  28.970_JPRB    /
86data ZAMW   /  18.0154_JPRB   /
87data ZAMCO2 /  44.011_JPRB    /
88data ZAMO   /  47.9982_JPRB   /
89data ZAMCH4 /  16.043_JPRB    /
90data ZAMN2O /  44.013_JPRB    /
91data ZAMC11 / 137.3686_JPRB   /
92data ZAMC12 / 120.9140_JPRB   /
93data ZAMC22 /  86.4690_JPRB   /
94data ZAMCL4 / 153.8230_JPRB   /
95data ZAVGDRO/ 6.02214E23_JPRB /
96
97INTEGER(KIND=JPIM) :: IATM, JMOL, IXMAX, J1, J2, JK, JL
98INTEGER(KIND=JPIM) :: ITMOL, INXMOL
99
100REAL(KIND=JPRB) :: ZAMM
101
102REAL(KIND=JPRB) :: ZHOOK_HANDLE
103
104! ***
105
106! *** mji
107! Initialize all molecular amounts to zero here,
108! then pass ECRT amounts into RRTM arrays below.
109
110!      DATA ZWKL /MAXPRDW*0.0/
111!      DATA ZWX  /MAXPROD*0.0/
112!      DATA KREFLECT /0/
113
114! Activate cross section molecules:
115!     NXMOL     - number of cross-sections input by user
116!     IXINDX(I) - index of cross-section molecule corresponding to Ith
117!                 cross-section specified by user
118!                 = 0 -- not allowed in RRTM
119!                 = 1 -- CCL4
120!                 = 2 -- CFC11
121!                 = 3 -- CFC12
122!                 = 4 -- CFC22
123!      DATA KXMOL  /2/
124!      DATA KXINDX /0,2,3,0,31*0/
125
126!      IREFLECT=KREFLECT
127!      NXMOL=KXMOL
128
129ASSOCIATE(NFLEVG=>KLEV)
130IF (LHOOK) CALL DR_HOOK('RRTM_PREPARE_GASES',0,ZHOOK_HANDLE)
131
132ZGRAVIT=(RG/RPLRG)*1.E2_JPRB
133
134DO JL = KIDIA, KFDIA
135  KREFLECT(JL)=0
136  INXMOL=2
137ENDDO
138
139!DO J1=1,35
140! IXINDX(J1)=0
141DO J2=1,KLEV
142  DO J1=1,35
143    DO JL = KIDIA, KFDIA
144      PWKL(JL,J1,J2)=0.0_JPRB
145    ENDDO
146  ENDDO
147ENDDO
148!IXINDX(2)=2
149!IXINDX(3)=3
150
151!     Set parameters needed for RRTM execution:
152IATM    = 0
153!      IXSECT  = 1
154!      NUMANGS = 0
155!      IOUT    = -1
156IXMAX   = 4
157
158DO JL = KIDIA, KFDIA
159!     Install ECRT arrays into RRTM arrays for pressure, temperature,
160!     and molecular amounts.  Pressures are converted from Pascals
161!     (ECRT) to mb (RRTM).  H2O, CO2, O3 and trace gas amounts are
162!     converted from mass mixing ratio to volume mixing ratio.  CO2
163!     converted with same dry air and CO2 molecular weights used in
164!     ECRT to assure correct conversion back to the proper CO2 vmr.
165!     The dry air column COLDRY (in molec/cm2) is calculated from
166!     the level pressures PZ (in mb) based on the hydrostatic equation
167!     and includes a correction to account for H2O in the layer.  The
168!     molecular weight of moist air (amm) is calculated for each layer.
169!     Note: RRTM levels count from bottom to top, while the ECRT input
170!     variables count from the top down and must be reversed
171  ITMOL = 7
172  PZ(JL,0) = PAPH(JL,KLEV+1)/100._JPRB
173  PTZ(JL,0) = PTH(JL,KLEV+1)
174ENDDO
175
176  DO JK = 1, KLEV
177    DO JL = KIDIA, KFDIA
178    PAVEL(JL,JK) = PAP(JL,KLEV-JK+1)/100._JPRB
179    PTAVEL(JL,JK) = PT(JL,KLEV-JK+1)
180    PZ(JL,JK) = PAPH(JL,KLEV-JK+1)/100._JPRB
181    PTZ(JL,JK) = PTH(JL,KLEV-JK+1)
182    PWKL(JL,1,JK) = PQ(JL,KLEV-JK+1)*ZAMD/ZAMW
183    PWKL(JL,2,JK) = PCO2(JL,KLEV-JK+1)*ZAMD/ZAMCO2
184    PWKL(JL,3,JK) = POZN(JL,KLEV-JK+1)*ZAMD/ZAMO
185    PWKL(JL,4,JK) = PN2O(JL,KLEV-JK+1)*ZAMD/ZAMN2O
186    PWKL(JL,6,JK) = PCH4(JL,KLEV-JK+1)*ZAMD/ZAMCH4
187    PWKL(JL,7,JK) = 0.209488_JPRB
188    ZAMM = (1.0_JPRB-PWKL(JL,1,JK))*ZAMD + PWKL(JL,1,JK)*ZAMW
189    PCOLDRY(JL,JK) = (PZ(JL,JK-1)-PZ(JL,JK))*1.E3_JPRB*ZAVGDRO/(ZGRAVIT*ZAMM*(1.0_JPRB+PWKL(JL,1,JK)))
190  ENDDO
191  ENDDO
192
193  DO J2=1,KLEV
194    DO J1=1,JPXSEC
195      DO JL = KIDIA, KFDIA
196        PWX(JL,J1,J2)=0.0_JPRB
197      ENDDO
198    ENDDO
199  ENDDO
200
201  DO JK = 1, KLEV
202DO JL = KIDIA, KFDIA
203!- Set cross section molecule amounts from ECRT; convert to vmr
204    PWX(JL,1,JK) = PCL4(JL,KLEV-JK+1) * ZAMD/ZAMCL4
205    PWX(JL,2,JK) = PC11(JL,KLEV-JK+1) * ZAMD/ZAMC11
206    PWX(JL,3,JK) = PC12(JL,KLEV-JK+1) * ZAMD/ZAMC12
207    PWX(JL,4,JK) = PC22(JL,KLEV-JK+1) * ZAMD/ZAMC22
208    PWX(JL,1,JK) = PCOLDRY(JL,JK) * PWX(JL,1,JK) * 1.E-20_JPRB
209    PWX(JL,2,JK) = PCOLDRY(JL,JK) * PWX(JL,2,JK) * 1.E-20_JPRB
210    PWX(JL,3,JK) = PCOLDRY(JL,JK) * PWX(JL,3,JK) * 1.E-20_JPRB
211    PWX(JL,4,JK) = PCOLDRY(JL,JK) * PWX(JL,4,JK) * 1.E-20_JPRB
212
213!- Here, all molecules in WKL and WX are in volume mixing ratio; convert to
214!  molec/cm2 based on COLDRY for use in RRTM
215
216!CDIR UNROLL=6
217ZSUMMOL = 0.0_JPRB
218!AB broadening gases
219    DO JMOL = 2, ITMOL
220      ZSUMMOL = ZSUMMOL + PWKL(JL,JMOL,JK)
221    ENDDO
222    PWBRODL(JL,JK) = PCOLDRY(JL,JK) * (1._JPRB - ZSUMMOL)
223    DO JMOL = 1, ITMOL
224      PWKL(JL,JMOL,JK) = PCOLDRY(JL,JK) * PWKL(JL,JMOL,JK)
225    ENDDO   
226  ENDDO
227ENDDO
228
229!     ------------------------------------------------------------------
230IF (LHOOK) CALL DR_HOOK('RRTM_PREPARE_GASES',1,ZHOOK_HANDLE)
231END ASSOCIATE
232END SUBROUTINE RRTM_PREPARE_GASES
Note: See TracBrowser for help on using the repository browser.