source: LMDZ6/trunk/libf/phylmd/ecrad/rrtm_cmbgb6.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: 2.5 KB
Line 
1!***************************************************************************
2SUBROUTINE RRTM_CMBGB6
3!***************************************************************************
4
5!     BAND 6:  820-980 cm-1 (low - H2O; high - nothing)
6!     ABozzo 201306 updated to rrtmg v4.85
7!     band 6:  820-980 cm-1 (low key - h2o; low minor - co2)
8!                           (high key - nothing; high minor - cfc11, cfc12)
9!***************************************************************************
10
11! Parameters
12USE PARKIND1  ,ONLY : JPIM     ,JPRB
13USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
14
15USE YOERRTO6 , ONLY : KAO     ,SELFREFO   , FORREFO, FRACREFAO  ,&
16 & KAO_MCO2 ,CFC11ADJO,CFC12O 
17USE YOERRTA6 , ONLY : KA      ,SELFREF    , FORREF, FRACREFA   ,&
18 & KA_MCO2  ,CFC11ADJ ,CFC12 
19USE YOERRTRWT, ONLY : RWGT
20USE YOERRTFTR, ONLY : NGC      ,NGS      ,NGN     
21
22IMPLICIT NONE
23
24INTEGER(KIND=JPIM) :: IGC, IPR, IPRSM, JP, JT
25
26REAL(KIND=JPRB) :: Z_SUMF, Z_SUMK, Z_SUMK2, Z_SUMK3
27REAL(KIND=JPRB) :: ZHOOK_HANDLE
28
29IF (LHOOK) CALL DR_HOOK('RRTM_CMBGB6',0,ZHOOK_HANDLE)
30DO JT = 1,5
31  DO JP = 1,13
32    IPRSM = 0
33    DO IGC = 1,NGC(6)
34      Z_SUMK = 0.0_JPRB
35      DO IPR = 1, NGN(NGS(5)+IGC)
36        IPRSM = IPRSM + 1
37
38        Z_SUMK = Z_SUMK + KAO(JT,JP,IPRSM)*RWGT(IPRSM+80)
39      ENDDO
40
41      KA(JT,JP,IGC) = Z_SUMK
42    ENDDO
43  ENDDO
44ENDDO
45
46DO JT = 1,19
47    IPRSM = 0
48    DO IGC = 1,NGC(6)
49        Z_SUMK = 0.0_JPRB
50        DO IPR = 1, NGN(NGS(5)+IGC)
51            IPRSM = IPRSM + 1
52            Z_SUMK = Z_SUMK + KAO_MCO2(JT,IPRSM)*RWGT(IPRSM+80)
53        ENDDO
54        KA_MCO2(JT,IGC) = Z_SUMK
55    ENDDO
56ENDDO
57
58DO JT = 1,10
59  IPRSM = 0
60  DO IGC = 1,NGC(6)
61    Z_SUMK = 0.0_JPRB
62    DO IPR = 1, NGN(NGS(5)+IGC)
63      IPRSM = IPRSM + 1
64
65      Z_SUMK = Z_SUMK + SELFREFO(JT,IPRSM)*RWGT(IPRSM+80)
66    ENDDO
67
68    SELFREF(JT,IGC) = Z_SUMK
69  ENDDO
70ENDDO
71
72DO JT = 1,4
73   IPRSM = 0
74   DO IGC = 1,NGC(6)
75      Z_SUMK = 0.0_JPRB
76      DO IPR = 1, NGN(NGS(5)+IGC)
77         IPRSM = IPRSM + 1
78         Z_SUMK = Z_SUMK + FORREFO(JT,IPRSM)*RWGT(IPRSM+80)
79      ENDDO
80      FORREF(JT,IGC) = Z_SUMK
81   ENDDO
82ENDDO
83
84IPRSM = 0
85DO IGC = 1,NGC(6)
86  Z_SUMF = 0.0_JPRB
87  Z_SUMK2= 0.0_JPRB
88  Z_SUMK3= 0.0_JPRB
89  DO IPR = 1, NGN(NGS(5)+IGC)
90    IPRSM = IPRSM + 1
91
92    Z_SUMF = Z_SUMF + FRACREFAO(IPRSM)
93    Z_SUMK2= Z_SUMK2+ CFC11ADJO(IPRSM)*RWGT(IPRSM+80)
94    Z_SUMK3= Z_SUMK3+ CFC12O(IPRSM)*RWGT(IPRSM+80)
95  ENDDO
96
97  FRACREFA(IGC) = Z_SUMF
98  CFC11ADJ(IGC) = Z_SUMK2
99  CFC12(IGC) = Z_SUMK3
100ENDDO
101
102
103IF (LHOOK) CALL DR_HOOK('RRTM_CMBGB6',1,ZHOOK_HANDLE)
104END SUBROUTINE RRTM_CMBGB6
Note: See TracBrowser for help on using the repository browser.