source: LMDZ6/trunk/libf/phylmd/ecrad/rrtm_cmbgb2.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: 2.6 KB
Line 
1!***************************************************************************
2SUBROUTINE RRTM_CMBGB2
3!***************************************************************************
4
5!     BAND 2:  250-500 cm-1 (low - H2O; high - H2O)
6! ABozzo May 2013 updated to last version of rrtmg
7!     band 2:  350-500 cm-1 (low key - h2o; high key - h2o)
8!***************************************************************************
9
10! Parameters
11USE PARKIND1  ,ONLY : JPIM     ,JPRB
12USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
13
14USE YOERRTO2 , ONLY : KAO     ,KBO     ,SELFREFO   ,FRACREFAO  ,&
15 & FRACREFBO  ,FORREFO 
16USE YOERRTA2 , ONLY : KA      ,KB      ,SELFREF    ,FRACREFA   ,&
17 & FRACREFB   ,FORREF       
18USE YOERRTRWT, ONLY : RWGT
19USE YOERRTFTR, ONLY : NGC      ,NGS      ,NGN     
20
21IMPLICIT NONE
22
23INTEGER(KIND=JPIM) :: IGC, IPR, IPRSM, JP, JT
24
25REAL(KIND=JPRB) :: Z_SUMF, Z_SUMK
26REAL(KIND=JPRB) :: ZHOOK_HANDLE
27
28IF (LHOOK) CALL DR_HOOK('RRTM_CMBGB2',0,ZHOOK_HANDLE)
29DO JT = 1,5
30  DO JP = 1,13
31    IPRSM = 0
32    DO IGC = 1,NGC(2)
33      Z_SUMK = 0.0_JPRB
34      DO IPR = 1, NGN(NGS(1)+IGC)
35        IPRSM = IPRSM + 1
36
37        Z_SUMK = Z_SUMK + KAO(JT,JP,IPRSM)*RWGT(IPRSM+16)
38      ENDDO
39
40      KA(JT,JP,IGC) = Z_SUMK
41    ENDDO
42  ENDDO
43  DO JP = 13,59
44    IPRSM = 0
45    DO IGC = 1,NGC(2)
46      Z_SUMK = 0.0_JPRB
47      DO IPR = 1, NGN(NGS(1)+IGC)
48        IPRSM = IPRSM + 1
49
50        Z_SUMK = Z_SUMK + KBO(JT,JP,IPRSM)*RWGT(IPRSM+16)
51      ENDDO
52!               KBC(JT,JP,IGC) = SUMK
53      KB(JT,JP,IGC) = Z_SUMK
54    ENDDO
55  ENDDO
56ENDDO
57
58DO JT = 1,10
59  IPRSM = 0
60  DO IGC = 1,NGC(2)
61    Z_SUMK = 0.0_JPRB
62    DO IPR = 1, NGN(NGS(1)+IGC)
63      IPRSM = IPRSM + 1
64
65      Z_SUMK = Z_SUMK + SELFREFO(JT,IPRSM)*RWGT(IPRSM+16)
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(2)
75      Z_SUMK = 0.0_JPRB
76        DO IPR = 1, NGN(NGS(1)+IGC)
77           IPRSM = IPRSM + 1
78           Z_SUMK = Z_SUMK + FORREFO(JT,IPRSM)*RWGT(IPRSM+16)
79        ENDDO
80      FORREF(JT,IGC) = Z_SUMK
81   ENDDO
82ENDDO
83
84
85IPRSM = 0
86DO IGC = 1,NGC(2)
87  Z_SUMK = 0.0_JPRB
88  Z_SUMF = 0.0_JPRB
89  DO IPR = 1, NGN(NGS(1)+IGC)
90    IPRSM = IPRSM + 1
91
92    Z_SUMK = Z_SUMK + FRACREFAO(IPRSM)
93    Z_SUMF = Z_SUMF + FRACREFBO(IPRSM)
94  ENDDO
95
96  FRACREFA(IGC) = Z_SUMK
97  FRACREFB(IGC) = Z_SUMF
98ENDDO
99
100!DO JP = 1,13
101!  DO IGC = 1,NGC(2)
102
103!    FREFA(NGS(1)+IGC,JP) = FRACREFA(IGC,JP)
104!  ENDDO
105!ENDDO
106!DO JP = 2,13
107!  DO IGC = 1,NGC(2)
108
109!    FREFADF(NGS(1)+IGC,JP) = FRACREFA(IGC,JP-1) -FRACREFA(IGC,JP)
110!  ENDDO
111!ENDDO
112!DO IGC = 1,NGC(2)
113
114!  FREFB(NGS(1)+IGC,1) = FRACREFB(IGC)
115!ENDDO
116
117IF (LHOOK) CALL DR_HOOK('RRTM_CMBGB2',1,ZHOOK_HANDLE)
118END SUBROUTINE RRTM_CMBGB2
Note: See TracBrowser for help on using the repository browser.