source: LMDZ6/branches/LMDZ_ECRad/libf/phylmd/ecrad/ifsrrtm/rrtm_init_140gp.F90 @ 4999

Last change on this file since 4999 was 4728, checked in by idelkadi, 11 months ago

Update of ecrad in the LMDZ_ECRad branch of LMDZ:

  • version 1.6.1 of ecrad
  • files are no longer grouped in the same ecrad directory.
  • the structure of ecrad offline is preserved to facilitate updating in LMDZ
  • cfg.bld modified to take into account the new added subdirectories.
  • the interface routines and those added in ecrad are moved to the phylmd directory
File size: 4.1 KB
Line 
1!***************************************************************************
2SUBROUTINE RRTM_INIT_140GP(CDIRECTORY)
3!***************************************************************************
4!     Reformatted for F90 by JJMorcrette, ECMWF, 980714
5
6!     JJMorcrette 20110613 flexible number of g-points
7
8! Parameters
9USE PARKIND1  ,ONLY : JPIM     ,JPRB
10USE YOMHOOK   ,ONLY : LHOOK, DR_HOOK, JPHOOK
11
12USE PARRRTM  , ONLY : JPBAND   ,JPG
13USE YOERRTM  , ONLY : JPGPT
14USE YOERRTWN , ONLY : NG       
15USE YOERRTFTR, ONLY : NGC      ,NGN      ,NGM     , WT
16! Output
17USE YOERRTBG2, ONLY : CORR1    ,CORR2
18USE YOERRTRWT, ONLY : FREFA    ,FREFB    ,FREFADF  ,FREFBDF   ,RWGT
19!USE YOMLUN   , ONLY : NULOUT
20
21IMPLICIT NONE
22
23CHARACTER(LEN=*), INTENT(IN) :: CDIRECTORY
24
25REAL(KIND=JPRB) :: ZWTSM(JPG)
26
27INTEGER(KIND=JPIM) :: I, IBND, IG, IGC, IGCSM, IND, IPR, IPRSM, IPT
28
29REAL(KIND=JPRB) :: ZFP, ZRTFP, ZWTSUM
30REAL(KIND=JPHOOK) :: ZHOOK_HANDLE
31
32!#include "surrtmcf.intfb.h"
33#include "surrtftr.intfb.h"
34
35#include "rrtm_kgb1.intfb.h"
36#include "rrtm_kgb10.intfb.h"
37#include "rrtm_kgb11.intfb.h"
38#include "rrtm_kgb12.intfb.h"
39#include "rrtm_kgb13.intfb.h"
40#include "rrtm_kgb14.intfb.h"
41#include "rrtm_kgb15.intfb.h"
42#include "rrtm_kgb16.intfb.h"
43#include "rrtm_kgb2.intfb.h"
44#include "rrtm_kgb3.intfb.h"
45#include "rrtm_kgb4.intfb.h"
46#include "rrtm_kgb5.intfb.h"
47#include "rrtm_kgb6.intfb.h"
48#include "rrtm_kgb7.intfb.h"
49#include "rrtm_kgb8.intfb.h"
50#include "rrtm_kgb9.intfb.h"
51
52#include "rrtm_cmbgb1.intfb.h"
53#include "rrtm_cmbgb10.intfb.h"
54#include "rrtm_cmbgb11.intfb.h"
55#include "rrtm_cmbgb12.intfb.h"
56#include "rrtm_cmbgb13.intfb.h"
57#include "rrtm_cmbgb14.intfb.h"
58#include "rrtm_cmbgb15.intfb.h"
59#include "rrtm_cmbgb16.intfb.h"
60#include "rrtm_cmbgb2.intfb.h"
61#include "rrtm_cmbgb3.intfb.h"
62#include "rrtm_cmbgb4.intfb.h"
63#include "rrtm_cmbgb5.intfb.h"
64#include "rrtm_cmbgb6.intfb.h"
65#include "rrtm_cmbgb7.intfb.h"
66#include "rrtm_cmbgb8.intfb.h"
67#include "rrtm_cmbgb9.intfb.h"
68
69IF (LHOOK) CALL DR_HOOK('RRTM_INIT_140GP',0,ZHOOK_HANDLE)
70
71!CALL SURRTMCF
72CALL SURRTFTR
73
74! Read the absorption-related coefficients over the 16 x 16 g-points
75
76CALL RRTM_KGB1(CDIRECTORY)
77CALL RRTM_KGB2
78CALL RRTM_KGB3
79CALL RRTM_KGB4
80CALL RRTM_KGB5
81CALL RRTM_KGB6
82CALL RRTM_KGB7
83CALL RRTM_KGB8
84CALL RRTM_KGB9
85CALL RRTM_KGB10
86CALL RRTM_KGB11
87CALL RRTM_KGB12
88CALL RRTM_KGB13
89CALL RRTM_KGB14
90CALL RRTM_KGB15
91CALL RRTM_KGB16
92
93!  Calculate lookup tables for functions needed in routine TAUMOL (TAUGB2)
94
95CORR1(0) = 1.0_JPRB
96CORR1(200) = 1.0_JPRB
97CORR2(0) = 1.0_JPRB
98CORR2(200) = 1.0_JPRB
99DO I = 1,199
100  ZFP = 0.005_JPRB*REAL(I)
101  ZRTFP = SQRT(ZFP)
102  CORR1(I) = ZRTFP/ZFP
103  CORR2(I) = (1.0_JPRB-ZRTFP)/(1.0_JPRB-ZFP)
104ENDDO
105
106!  Perform g-point reduction from 16 per band (256 total points) to
107!  a band dependant number (140 total points) for all absorption
108!  coefficient input data and Planck fraction input data.
109!  Compute relative weighting for new g-point combinations.
110
111IGCSM = 0
112DO IBND = 1,JPBAND
113  IPRSM = 0
114  IF (NGC(IBND) < 16) THEN
115    DO IGC = 1,NGC(IBND)
116      IGCSM = IGCSM + 1
117      ZWTSUM = 0.0_JPRB
118      DO IPR = 1, NGN(IGCSM)
119        IPRSM = IPRSM + 1
120        ZWTSUM = ZWTSUM + WT(IPRSM)
121      ENDDO
122      ZWTSM(IGC) = ZWTSUM
123    ENDDO
124
125    DO IG = 1,NG(IBND)
126      IND = (IBND-1)*16 + IG
127      RWGT(IND) = WT(IG)/ZWTSM(NGM(IND))
128    ENDDO
129  ELSE
130    DO IG = 1,NG(IBND)
131      IGCSM = IGCSM + 1
132      IND = (IBND-1)*16 + IG
133      RWGT(IND) = 1.0_JPRB
134    ENDDO
135  ENDIF
136ENDDO
137
138!  Initialize arrays for combined Planck fraction data.
139
140DO IPT = 1,13
141  DO IPR = 1, JPGPT
142    FREFA(IPR,IPT) = 0.0_JPRB
143    FREFADF(IPR,IPT) = 0.0_JPRB
144  ENDDO
145ENDDO
146DO IPT = 1,6
147  DO IPR = 1, JPGPT
148    FREFB(IPR,IPT) = 0.0_JPRB
149    FREFBDF(IPR,IPT) = 0.0_JPRB
150  ENDDO
151ENDDO
152
153!  Reduce g-points for relevant data in each LW spectral band.
154
155CALL RRTM_CMBGB1
156CALL RRTM_CMBGB2
157CALL RRTM_CMBGB3
158CALL RRTM_CMBGB4
159CALL RRTM_CMBGB5
160CALL RRTM_CMBGB6
161CALL RRTM_CMBGB7
162CALL RRTM_CMBGB8
163CALL RRTM_CMBGB9
164CALL RRTM_CMBGB10
165CALL RRTM_CMBGB11
166CALL RRTM_CMBGB12
167CALL RRTM_CMBGB13
168CALL RRTM_CMBGB14
169CALL RRTM_CMBGB15
170CALL RRTM_CMBGB16
171
172IF (LHOOK) CALL DR_HOOK('RRTM_INIT_140GP',1,ZHOOK_HANDLE)
173END SUBROUTINE RRTM_INIT_140GP
Note: See TracBrowser for help on using the repository browser.