source: LMDZ6/trunk/libf/phylmd/ecrad/srtm_cmbgb24.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.7 KB
Line 
1SUBROUTINE SRTM_CMBGB24
2
3!     BAND 24:  12850-16000 cm-1 (low - H2O,O2; high - O2)
4!-----------------------------------------------------------------------
5
6USE PARKIND1  ,ONLY : JPIM , JPRB
7USE YOMHOOK   ,ONLY : LHOOK, DR_HOOK
8
9USE YOESRTM  , ONLY : NGN
10USE YOESRTWN , ONLY : NGC, NGS, RWGT
11!USE YOESRTWN , ONLY : NGC, NGS, NGN, RWGT
12USE YOESRTA24, ONLY : KA, KB, SELFREF, FORREF, SFLUXREF, &
13                    & ABSO3A, ABSO3B, RAYLA, RAYLB, &
14                    & KAC, KBC, SELFREFC, FORREFC, SFLUXREFC, &
15                    & ABSO3AC, ABSO3BC, RAYLAC, RAYLBC
16
17IMPLICIT NONE
18
19! Local variables
20INTEGER(KIND=JPIM) :: JN, JT, JP, IGC, IPR, IPRSM
21REAL(KIND=JPRB)    :: ZSUMK, ZSUMF1, ZSUMF2, ZSUMF3
22
23REAL(KIND=JPRB) :: ZHOOK_HANDLE
24!     ------------------------------------------------------------------
25IF (LHOOK) CALL DR_HOOK('SRTM_CMBGB24',0,ZHOOK_HANDLE)
26
27DO JN = 1,9
28  DO JT = 1,5
29    DO JP = 1,13
30      IPRSM = 0
31      DO IGC = 1,NGC(9)
32        ZSUMK = 0.
33        DO IPR = 1, NGN(NGS(8)+IGC)
34          IPRSM = IPRSM + 1
35          ZSUMK = ZSUMK + KA(JN,JT,JP,IPRSM)*RWGT(IPRSM+128)
36        ENDDO
37        KAC(JN,JT,JP,IGC) = ZSUMK
38      ENDDO
39    ENDDO
40  ENDDO
41ENDDO
42
43DO JT = 1,5
44  DO JP = 13,59
45    IPRSM = 0
46    DO IGC = 1,NGC(9)
47      ZSUMK = 0.
48      DO IPR = 1, NGN(NGS(8)+IGC)
49        IPRSM = IPRSM + 1
50        ZSUMK = ZSUMK + KB(JT,JP,IPRSM)*RWGT(IPRSM+128)
51      ENDDO
52      KBC(JT,JP,IGC) = ZSUMK
53    ENDDO
54  ENDDO
55ENDDO
56
57DO JT = 1,10
58  IPRSM = 0
59  DO IGC = 1,NGC(9)
60    ZSUMK = 0.
61    DO IPR = 1, NGN(NGS(8)+IGC)
62      IPRSM = IPRSM + 1
63      ZSUMK = ZSUMK + SELFREF(JT,IPRSM)*RWGT(IPRSM+128)
64    ENDDO
65    SELFREFC(JT,IGC) = ZSUMK
66  ENDDO
67ENDDO
68
69DO JT = 1,3
70  IPRSM = 0
71  DO IGC = 1,NGC(9)
72    ZSUMK = 0.
73    DO IPR = 1, NGN(NGS(8)+IGC)
74      IPRSM = IPRSM + 1
75      ZSUMK = ZSUMK + FORREF(JT,IPRSM)*RWGT(IPRSM+128)
76    ENDDO
77    FORREFC(JT,IGC) = ZSUMK
78  ENDDO
79ENDDO
80
81IPRSM = 0
82DO IGC = 1,NGC(9)
83  ZSUMF1 = 0.
84  ZSUMF2 = 0.
85  ZSUMF3 = 0.
86  DO IPR = 1, NGN(NGS(8)+IGC)
87    IPRSM = IPRSM + 1
88    ZSUMF1 = ZSUMF1 + RAYLB(IPRSM)*RWGT(IPRSM+128)
89    ZSUMF2 = ZSUMF2 + ABSO3A(IPRSM)*RWGT(IPRSM+128)
90    ZSUMF3 = ZSUMF3 + ABSO3B(IPRSM)*RWGT(IPRSM+128)
91  ENDDO
92  RAYLBC(IGC) = ZSUMF1
93  ABSO3AC(IGC) = ZSUMF2
94  ABSO3BC(IGC) = ZSUMF3
95ENDDO
96
97DO JP = 1,9
98  IPRSM = 0
99  DO IGC = 1,NGC(9)
100    ZSUMF1 = 0.
101    ZSUMF2 = 0.
102    DO IPR = 1, NGN(NGS(8)+IGC)
103      IPRSM = IPRSM + 1
104      ZSUMF1 = ZSUMF1 + SFLUXREF(IPRSM,JP)
105      ZSUMF2 = ZSUMF2 + RAYLA(IPRSM,JP)*RWGT(IPRSM+128)
106    ENDDO
107    SFLUXREFC(IGC,JP) = ZSUMF1
108    RAYLAC(IGC,JP) = ZSUMF2
109  ENDDO
110ENDDO
111
112!     -----------------------------------------------------------------
113IF (LHOOK) CALL DR_HOOK('SRTM_CMBGB24',1,ZHOOK_HANDLE)
114END SUBROUTINE SRTM_CMBGB24
115
Note: See TracBrowser for help on using the repository browser.