source: LMDZ5/branches/IPSLCM5A2.1_ISO/libf/phyiso/rrtm/rrtm_init_140gp.F90 @ 3331

Last change on this file since 3331 was 3331, checked in by acozic, 6 years ago

Add modification for isotopes

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