source: LMDZ6/trunk/libf/phylmd/ecrad/rrtm_cmbgb7.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.2 KB
Line 
1!***************************************************************************
2SUBROUTINE RRTM_CMBGB7
3!***************************************************************************
4
5!     BAND 7:  980-1080 cm-1 (low - H2O,O3; high - O3)
6!     ABozzo 201306 updated to rrtmg v4.85
7!     band 7:  980-1080 cm-1 (low key - h2o,o3; low minor - co2)
8!                            (high key - o3; high minor - co2)
9!***************************************************************************
10
11! Parameters
12USE PARKIND1  ,ONLY : JPIM     ,JPRB
13USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
14
15USE YOERRTO7 , ONLY : KAO     ,KBO     ,SELFREFO   ,FORREFO, FRACREFAO  ,&
16 & FRACREFBO,  KAO_MCO2     ,KBO_MCO2 
17USE YOERRTA7 , ONLY : KA      ,KB      ,SELFREF    ,FORREF, FRACREFA   ,&
18 & FRACREFB,  KA_MCO2     ,KB_MCO2     
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_CMBGB7',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(7)
35        Z_SUMK = 0.0_JPRB
36        DO IPR = 1, NGN(NGS(6)+IGC)
37          IPRSM = IPRSM + 1
38
39          Z_SUMK = Z_SUMK + KAO(JN,JT,JP,IPRSM)*RWGT(IPRSM+96)
40        ENDDO
41
42        KA(JN,JT,JP,IGC) = Z_SUMK
43      ENDDO
44    ENDDO
45  ENDDO
46ENDDO
47DO JT = 1,5
48  DO JP = 13,59
49    IPRSM = 0
50    DO IGC = 1,NGC(7)
51      Z_SUMK = 0.0_JPRB
52      DO IPR = 1, NGN(NGS(6)+IGC)
53        IPRSM = IPRSM + 1
54
55        Z_SUMK = Z_SUMK + KBO(JT,JP,IPRSM)*RWGT(IPRSM+96)
56      ENDDO
57
58      KB(JT,JP,IGC) = Z_SUMK
59    ENDDO
60  ENDDO
61ENDDO
62
63DO JN = 1,9
64      DO JT = 1,19
65         IPRSM = 0
66         DO IGC = 1,NGC(7)
67            Z_SUMK = 0.0_JPRB
68            DO IPR = 1, NGN(NGS(6)+IGC)
69               IPRSM = IPRSM + 1
70               Z_SUMK = Z_SUMK + KAO_MCO2(JN,JT,IPRSM)*RWGT(IPRSM+96)
71            ENDDO
72            KA_MCO2(JN,JT,IGC) = Z_SUMK
73         ENDDO
74       ENDDO
75ENDDO
76
77DO JT = 1,19
78      IPRSM = 0
79      DO IGC = 1,NGC(7)
80         Z_SUMK = 0.0_JPRB
81         DO IPR = 1, NGN(NGS(6)+IGC)
82            IPRSM = IPRSM + 1
83            Z_SUMK = Z_SUMK + KBO_MCO2(JT,IPRSM)*RWGT(IPRSM+96)
84         ENDDO
85         KB_MCO2(JT,IGC) = Z_SUMK
86      ENDDO
87ENDDO
88
89
90DO JT = 1,10
91  IPRSM = 0
92  DO IGC = 1,NGC(7)
93    Z_SUMK = 0.0_JPRB
94    DO IPR = 1, NGN(NGS(6)+IGC)
95      IPRSM = IPRSM + 1
96
97      Z_SUMK = Z_SUMK + SELFREFO(JT,IPRSM)*RWGT(IPRSM+96)
98    ENDDO
99
100    SELFREF(JT,IGC) = Z_SUMK
101  ENDDO
102ENDDO
103
104DO JT = 1,4
105      IPRSM = 0
106      DO IGC = 1,NGC(7)
107         Z_SUMK = 0.0_JPRB
108         DO IPR = 1, NGN(NGS(6)+IGC)
109            IPRSM = IPRSM + 1
110            Z_SUMK = Z_SUMK + FORREFO(JT,IPRSM)*RWGT(IPRSM+96)
111         ENDDO
112         FORREF(JT,IGC) = Z_SUMK
113      ENDDO
114ENDDO
115
116DO JP = 1,9
117  IPRSM = 0
118  DO IGC = 1,NGC(7)
119    Z_SUMF = 0.0_JPRB
120    DO IPR = 1, NGN(NGS(6)+IGC)
121      IPRSM = IPRSM + 1
122
123      Z_SUMF = Z_SUMF + FRACREFAO(IPRSM,JP)
124    ENDDO
125
126    FRACREFA(IGC,JP) = Z_SUMF
127  ENDDO
128ENDDO
129
130IPRSM = 0
131DO IGC = 1,NGC(7)
132  Z_SUMF = 0.0_JPRB
133  DO IPR = 1, NGN(NGS(6)+IGC)
134    IPRSM = IPRSM + 1
135
136    Z_SUMF = Z_SUMF + FRACREFBO(IPRSM)
137  ENDDO
138
139  FRACREFB(IGC) = Z_SUMF
140ENDDO
141
142
143IF (LHOOK) CALL DR_HOOK('RRTM_CMBGB7',1,ZHOOK_HANDLE)
144END SUBROUTINE RRTM_CMBGB7
Note: See TracBrowser for help on using the repository browser.