source: LMDZ6/trunk/libf/phylmd/ecrad/rrtm_cmbgb5.F90 @ 3981

Last change on this file since 3981 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: 3.1 KB
Line 
1!***************************************************************************
2SUBROUTINE RRTM_CMBGB5
3!***************************************************************************
4
5!     BAND 5:  700-820 cm-1 (low - H2O,CO2; high - O3,CO2)
6!     ABozzo 201306 updated to rrtmg v4.85
7!     band 5:  700-820 cm-1 (low key - h2o,co2; low minor - o3, ccl4)
8!                           (high key - o3,co2)
9!***************************************************************************
10
11! Parameters
12USE PARKIND1  ,ONLY : JPIM     ,JPRB
13USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
14
15USE YOERRTO5 , ONLY : KAO     ,KBO     ,SELFREFO   ,FORREFO, FRACREFAO  ,&
16 & FRACREFBO, CCL4O, KAO_MO3
17USE YOERRTA5 , ONLY : KA      ,KB      ,SELFREF    ,FORREF, FRACREFA   ,&
18 & FRACREFB , CCL4, KA_MO3 
19USE YOERRTRWT, ONLY : RWGT
20USE YOERRTFTR, ONLY : NGC      ,NGS      ,NGN     
21
22IMPLICIT NONE
23
24INTEGER(KIND=JPIM) :: IGC, IPR, IPRSM, JN, JP, JT
25
26REAL(KIND=JPRB) :: Z_SUMF, Z_SUMK
27REAL(KIND=JPRB) :: ZHOOK_HANDLE
28
29IF (LHOOK) CALL DR_HOOK('RRTM_CMBGB5',0,ZHOOK_HANDLE)
30DO JN = 1,9
31  DO JT = 1,5
32    DO JP = 1,13
33      IPRSM = 0
34      DO IGC = 1,NGC(5)
35        Z_SUMK = 0.0_JPRB
36        DO IPR = 1, NGN(NGS(4)+IGC)
37          IPRSM = IPRSM + 1
38
39          Z_SUMK = Z_SUMK + KAO(JN,JT,JP,IPRSM)*RWGT(IPRSM+64)
40        ENDDO
41
42        KA(JN,JT,JP,IGC) = Z_SUMK
43      ENDDO
44    ENDDO
45  ENDDO
46ENDDO
47DO JN = 1,5
48  DO JT = 1,5
49    DO JP = 13,59
50      IPRSM = 0
51      DO IGC = 1,NGC(5)
52        Z_SUMK = 0.0_JPRB
53        DO IPR = 1, NGN(NGS(4)+IGC)
54          IPRSM = IPRSM + 1
55
56          Z_SUMK = Z_SUMK + KBO(JN,JT,JP,IPRSM)*RWGT(IPRSM+64)
57        ENDDO
58
59        KB(JN,JT,JP,IGC) = Z_SUMK
60      ENDDO
61    ENDDO
62  ENDDO
63ENDDO
64
65 DO JN = 1,9
66    DO JT = 1,19
67       IPRSM = 0
68       DO IGC = 1,NGC(5)
69          Z_SUMK = 0.0_JPRB
70          DO IPR = 1, NGN(NGS(4)+IGC)
71               IPRSM = IPRSM + 1
72               Z_SUMK = Z_SUMK + KAO_MO3(JN,JT,IPRSM)*RWGT(IPRSM+64)
73          ENDDO
74          KA_MO3(JN,JT,IGC) = Z_SUMK
75       ENDDO
76    ENDDO
77ENDDO
78
79
80
81DO JT = 1,10
82  IPRSM = 0
83  DO IGC = 1,NGC(5)
84    Z_SUMK = 0.0_JPRB
85    DO IPR = 1, NGN(NGS(4)+IGC)
86      IPRSM = IPRSM + 1
87
88      Z_SUMK = Z_SUMK + SELFREFO(JT,IPRSM)*RWGT(IPRSM+64)
89    ENDDO
90
91    SELFREF(JT,IGC) = Z_SUMK
92  ENDDO
93ENDDO
94
95DO JT = 1,4
96   IPRSM = 0
97   DO IGC = 1,NGC(5)
98      Z_SUMK = 0.0_JPRB
99      DO IPR = 1, NGN(NGS(4)+IGC)
100         IPRSM = IPRSM + 1
101         Z_SUMK = Z_SUMK + FORREFO(JT,IPRSM)*RWGT(IPRSM+64)
102      ENDDO
103      FORREF(JT,IGC) = Z_SUMK
104   ENDDO
105ENDDO
106
107
108
109DO JP = 1,9
110  IPRSM = 0
111  DO IGC = 1,NGC(5)
112    Z_SUMF = 0.0_JPRB
113    DO IPR = 1, NGN(NGS(4)+IGC)
114      IPRSM = IPRSM + 1
115
116      Z_SUMF = Z_SUMF + FRACREFAO(IPRSM,JP)
117    ENDDO
118
119    FRACREFA(IGC,JP) = Z_SUMF
120  ENDDO
121ENDDO
122
123DO JP = 1,5
124  IPRSM = 0
125  DO IGC = 1,NGC(5)
126    Z_SUMF = 0.0_JPRB
127    DO IPR = 1, NGN(NGS(4)+IGC)
128      IPRSM = IPRSM + 1
129
130      Z_SUMF = Z_SUMF + FRACREFBO(IPRSM,JP)
131    ENDDO
132
133    FRACREFB(IGC,JP) = Z_SUMF
134  ENDDO
135ENDDO
136
137IPRSM = 0
138DO IGC = 1,NGC(5)
139  Z_SUMK = 0.0_JPRB
140  DO IPR = 1, NGN(NGS(4)+IGC)
141    IPRSM = IPRSM + 1
142
143    Z_SUMK = Z_SUMK + CCL4O(IPRSM)*RWGT(IPRSM+64)
144  ENDDO
145
146  CCL4(IGC) = Z_SUMK
147ENDDO
148
149
150IF (LHOOK) CALL DR_HOOK('RRTM_CMBGB5',1,ZHOOK_HANDLE)
151END SUBROUTINE RRTM_CMBGB5
Note: See TracBrowser for help on using the repository browser.