source: LMDZ6/trunk/libf/phylmd/ecrad/ifsrrtm/srtm_init.F90 @ 4773

Last change on this file since 4773 was 4773, checked in by idelkadi, 6 months ago
  • Update of Ecrad in LMDZ The same organization of the Ecrad offline version is retained in order to facilitate the updating of Ecrad in LMDZ and the comparison between online and offline results. version 1.6.1 of Ecrad (https://github.com/lguez/ecrad.git)
  • Implementation of the double call of Ecrad in LMDZ


File size: 3.7 KB
Line 
1SUBROUTINE SRTM_INIT(CDIRECTORY, NWVCONTINUUM)
2
3!-- read in the basic coefficients to configure RRTM_SW
4!- creates module YOESRTWN with BG, NSPA, NSPB, WAVENUM1, WAVENUM2,
5!  DELWAVE, PREF, PREFLOG, TREF
6
7USE PARKIND1  ,ONLY : JPIM , JPRB
8USE YOMHOOK   ,ONLY : LHOOK, DR_HOOK, JPHOOK
9
10USE PARSRTM  , ONLY : JPG, JPSW
11USE YOESRTM  , ONLY : NGN
12USE YOESRTWN , ONLY : NG, NGM, WT, NGC, RWGT, WTSM
13!USE YOESRTWN , ONLY : NG, NGM, WT, NGC, NGN, RWGT, WTSM
14!USE YOMLUN   , ONLY : NULOUT
15
16IMPLICIT NONE
17
18CHARACTER(LEN=*), INTENT(IN) :: CDIRECTORY
19
20! Water vapour continuum model (0=default MT_CKD2.5, 1=CAVIAR)
21INTEGER(KIND=JPIM), INTENT(IN), OPTIONAL :: NWVCONTINUUM
22
23! Local variables
24INTEGER(KIND=JPIM) :: IGC, IGCSM, IBND, IG, IND, IPR, IPRSM
25REAL(KIND=JPRB)    :: ZWTSUM
26
27REAL(KIND=JPHOOK) :: ZHOOK_HANDLE
28
29!#include "susrtmcf.intfb.h"
30#include "susrtm.intfb.h"
31#include "srtm_kgb16.intfb.h"
32#include "srtm_kgb17.intfb.h"
33#include "srtm_kgb18.intfb.h"
34#include "srtm_kgb19.intfb.h"
35#include "srtm_kgb20.intfb.h"
36#include "srtm_kgb21.intfb.h"
37#include "srtm_kgb22.intfb.h"
38#include "srtm_kgb23.intfb.h"
39#include "srtm_kgb24.intfb.h"
40#include "srtm_kgb25.intfb.h"
41#include "srtm_kgb26.intfb.h"
42#include "srtm_kgb27.intfb.h"
43#include "srtm_kgb28.intfb.h"
44#include "srtm_kgb29.intfb.h"
45!#include "susrtop.intfb.h"
46
47#include "modify_wv_continuum.intfb.h"
48
49#include "srtm_cmbgb16.intfb.h"
50#include "srtm_cmbgb17.intfb.h"
51#include "srtm_cmbgb18.intfb.h"
52#include "srtm_cmbgb19.intfb.h"
53#include "srtm_cmbgb20.intfb.h"
54#include "srtm_cmbgb21.intfb.h"
55#include "srtm_cmbgb22.intfb.h"
56#include "srtm_cmbgb23.intfb.h"
57#include "srtm_cmbgb24.intfb.h"
58#include "srtm_cmbgb25.intfb.h"
59#include "srtm_cmbgb26.intfb.h"
60#include "srtm_cmbgb27.intfb.h"
61#include "srtm_cmbgb28.intfb.h"
62#include "srtm_cmbgb29.intfb.h"
63
64IF (LHOOK) CALL DR_HOOK('SRTM_INIT',0,ZHOOK_HANDLE)
65
66!CALL SUSRTMCF
67CALL SUSRTM
68
69!-- read in the molecular absorption coefficients
70
71CALL SRTM_KGB16(CDIRECTORY)
72CALL SRTM_KGB17
73CALL SRTM_KGB18
74CALL SRTM_KGB19
75CALL SRTM_KGB20
76CALL SRTM_KGB21
77CALL SRTM_KGB22
78CALL SRTM_KGB23
79CALL SRTM_KGB24
80CALL SRTM_KGB25
81CALL SRTM_KGB26
82CALL SRTM_KGB27
83CALL SRTM_KGB28
84CALL SRTM_KGB29
85
86IF (PRESENT(NWVCONTINUUM)) THEN
87  ! Modify the shortwave water vapour continuum, if requested
88  CALL MODIFY_WV_CONTINUUM(NWVCONTINUUM)
89END IF
90
91!-- read in the cloud optical properties
92!- creates module YOESRTOP with EXTLIQ1, SSALIQ1, ASYLIQ1,
93!  EXTICE3, SSAICE3, ASYICE3, FDLICE3 
94
95!-- RRTM_SW cloud optical properties are not used
96!   SRTM_CLDPROP is not called
97!   no need to call SUSRTOP
98
99!CALL SUSRTOP ( -1 )
100
101
102!Mike Iacono 20050804
103!-- Perform g-point reduction from 16 per band (224 total points) to
104!-- a band dependent number (112 total points) for all absorption
105!-- coefficient input data and Planck fraction input data.
106!-- Compute relative weighting for new g-point combinations.
107
108IGCSM = 0
109DO IBND = 1,JPSW
110  IPRSM = 0
111  IF (NGC(IBND) < JPG) THEN
112    DO IGC = 1,NGC(IBND)
113      IGCSM = IGCSM + 1
114      ZWTSUM = 0.
115      DO IPR = 1, NGN(IGCSM)
116        IPRSM = IPRSM + 1
117        ZWTSUM = ZWTSUM + WT(IPRSM)
118      ENDDO
119      WTSM(IGC) = ZWTSUM
120    ENDDO
121
122    DO IG = 1,NG(IBND+15)
123      IND = (IBND-1)*JPG + IG
124      RWGT(IND) = WT(IG)/WTSM(NGM(IND))
125    ENDDO
126  ELSE
127    DO IG = 1,NG(IBND+15)
128      IGCSM = IGCSM + 1
129      IND = (IBND-1)*JPG + IG
130      RWGT(IND) = 1.0
131    ENDDO
132  ENDIF
133ENDDO
134
135CALL SRTM_CMBGB16
136CALL SRTM_CMBGB17
137CALL SRTM_CMBGB18
138CALL SRTM_CMBGB19
139CALL SRTM_CMBGB20
140CALL SRTM_CMBGB21
141CALL SRTM_CMBGB22
142CALL SRTM_CMBGB23
143CALL SRTM_CMBGB24
144CALL SRTM_CMBGB25
145CALL SRTM_CMBGB26
146CALL SRTM_CMBGB27
147CALL SRTM_CMBGB28
148CALL SRTM_CMBGB29
149
150!-----------------------------------------------------------------------
151IF (LHOOK) CALL DR_HOOK('SRTM_INIT',1,ZHOOK_HANDLE)
152END SUBROUTINE SRTM_INIT
153
Note: See TracBrowser for help on using the repository browser.