source: LMDZ6/trunk/libf/phylmd/ecrad/srtm_cmbgb20.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.1 KB
Line 
1SUBROUTINE SRTM_CMBGB20
2
3!     BAND 20:  5150-6150 cm-1 (low - H2O; high - H2O)
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 YOESRTA20, ONLY : KA, KB, SELFREF, FORREF, ABSCH4, SFLUXREF, &
13                    & KAC, KBC, SELFREFC, FORREFC, ABSCH4C, SFLUXREFC
14
15IMPLICIT NONE
16
17! Local variables
18INTEGER(KIND=JPIM) :: JT, JP, IGC, IPR, IPRSM
19REAL(KIND=JPRB)    :: ZSUMK, ZSUMF1, ZSUMF2
20
21REAL(KIND=JPRB) :: ZHOOK_HANDLE
22!     ------------------------------------------------------------------
23IF (LHOOK) CALL DR_HOOK('SRTM_CMBGB20',0,ZHOOK_HANDLE)
24
25DO JT = 1,5
26  DO JP = 1,13
27    IPRSM = 0
28    DO IGC = 1,NGC(5)
29      ZSUMK = 0.
30      DO IPR = 1, NGN(NGS(4)+IGC)
31        IPRSM = IPRSM + 1
32        ZSUMK = ZSUMK + KA(JT,JP,IPRSM)*RWGT(IPRSM+64)
33      ENDDO
34      KAC(JT,JP,IGC) = ZSUMK
35    ENDDO
36  ENDDO
37
38  DO JP = 13,59
39    IPRSM = 0
40    DO IGC = 1,NGC(5)
41      ZSUMK = 0.
42      DO IPR = 1, NGN(NGS(4)+IGC)
43        IPRSM = IPRSM + 1
44        ZSUMK = ZSUMK + KB(JT,JP,IPRSM)*RWGT(IPRSM+64)
45      ENDDO
46      KBC(JT,JP,IGC) = ZSUMK
47    ENDDO
48  ENDDO
49ENDDO
50
51DO JT = 1,10
52  IPRSM = 0
53  DO IGC = 1,NGC(5)
54    ZSUMK = 0.
55    DO IPR = 1, NGN(NGS(4)+IGC)
56      IPRSM = IPRSM + 1
57      ZSUMK = ZSUMK + SELFREF(JT,IPRSM)*RWGT(IPRSM+64)
58    ENDDO
59    SELFREFC(JT,IGC) = ZSUMK
60  ENDDO
61ENDDO
62
63DO JT = 1,4
64  IPRSM = 0
65  DO IGC = 1,NGC(5)
66    ZSUMK = 0.
67    DO IPR = 1, NGN(NGS(4)+IGC)
68      IPRSM = IPRSM + 1
69      ZSUMK = ZSUMK + FORREF(JT,IPRSM)*RWGT(IPRSM+64)
70    ENDDO
71    FORREFC(JT,IGC) = ZSUMK
72  ENDDO
73ENDDO
74
75IPRSM = 0
76DO IGC = 1,NGC(5)
77  ZSUMF1 = 0.
78  ZSUMF2 = 0.
79  DO IPR = 1, NGN(NGS(4)+IGC)
80    IPRSM = IPRSM + 1
81    ZSUMF1 = ZSUMF1 + SFLUXREF(IPRSM)
82    ZSUMF2 = ZSUMF2 + ABSCH4(IPRSM)*RWGT(IPRSM+64)
83  ENDDO
84  SFLUXREFC(IGC) = ZSUMF1
85  ABSCH4C(IGC) = ZSUMF2
86ENDDO
87
88!     -----------------------------------------------------------------
89IF (LHOOK) CALL DR_HOOK('SRTM_CMBGB20',1,ZHOOK_HANDLE)
90END SUBROUTINE SRTM_CMBGB20
91
Note: See TracBrowser for help on using the repository browser.