1 | SUBROUTINE SRTM_KGB27 |
---|
2 | |
---|
3 | ! Originally by J.Delamere, Atmospheric & Environmental Research. |
---|
4 | ! Revision: 2.4 |
---|
5 | ! BAND 16: 29000-38000 cm-1 (low - O3; high - O3) |
---|
6 | ! Reformatted for F90 by JJMorcrette, ECMWF |
---|
7 | ! G.Mozdzynski March 2011 read constants from files |
---|
8 | ! T. Wilhelmsson and K. Yessad (Oct 2013) Geometry and setup refactoring. |
---|
9 | ! ------------------------------------------------------------------ |
---|
10 | |
---|
11 | USE PARKIND1 , ONLY : JPRB |
---|
12 | USE YOMHOOK , ONLY : LHOOK, DR_HOOK |
---|
13 | USE YOMLUN , ONLY : NULRAD |
---|
14 | USE YOMMP0 , ONLY : NPROC, MYPROC |
---|
15 | USE MPL_MODULE, ONLY : MPL_BROADCAST |
---|
16 | USE YOMTAG , ONLY : MTAGRAD |
---|
17 | USE YOESRTA27 , ONLY : KA, KB, KA_D, KB_D, SFLUXREF, RAYL, SCALEKUR, LAYREFFR |
---|
18 | |
---|
19 | ! ------------------------------------------------------------------ |
---|
20 | |
---|
21 | IMPLICIT NONE |
---|
22 | |
---|
23 | ! KURUCZ |
---|
24 | ! The following values were obtained using the "low resolution" |
---|
25 | ! version of the Kurucz solar source function. For unknown reasons, |
---|
26 | ! the total irradiance in this band differs from the corresponding |
---|
27 | ! total in the "high-resolution" version of the Kurucz function. |
---|
28 | ! Therefore, below these values are scaled by the factor SCALEKUR. |
---|
29 | REAL(KIND=JPRB) :: ZHOOK_HANDLE |
---|
30 | |
---|
31 | #include "abor1.intfb.h" |
---|
32 | |
---|
33 | IF (LHOOK) CALL DR_HOOK('SRTM_KGB27',0,ZHOOK_HANDLE) |
---|
34 | |
---|
35 | IF( MYPROC==1 )THEN |
---|
36 | READ(NULRAD,ERR=1001) KA_D,KB_D |
---|
37 | KA = REAL(KA_D,JPRB) |
---|
38 | KB = REAL(KB_D,JPRB) |
---|
39 | ENDIF |
---|
40 | IF( NPROC>1 )THEN |
---|
41 | CALL MPL_BROADCAST (KA,MTAGRAD,1,CDSTRING='SRTM_KGB27:') |
---|
42 | CALL MPL_BROADCAST (KB,MTAGRAD,1,CDSTRING='SRTM_KGB27:') |
---|
43 | ENDIF |
---|
44 | |
---|
45 | SFLUXREF = (/ & |
---|
46 | & 14.0526_JPRB , 11.4794_JPRB , 8.72590_JPRB , 5.56966_JPRB , & |
---|
47 | & 3.80927_JPRB , 1.57690_JPRB , 1.15099_JPRB , 1.10012_JPRB , & |
---|
48 | & 0.658212_JPRB , 5.86859E-02_JPRB, 5.56186E-02_JPRB, 4.68040E-02_JPRB, & |
---|
49 | & 3.64897E-02_JPRB, 3.58053E-02_JPRB, 1.38130E-02_JPRB, 1.90193E-03_JPRB /) |
---|
50 | |
---|
51 | ! Rayleigh extinction coefficient at v = 2925 cm-1. |
---|
52 | RAYL = (/ & |
---|
53 | & 3.44534E-06_JPRB,4.14480E-06_JPRB,4.95069E-06_JPRB,5.81204E-06_JPRB, & |
---|
54 | & 6.69748E-06_JPRB,7.56488E-06_JPRB,8.36344E-06_JPRB,9.04135E-06_JPRB, & |
---|
55 | & 9.58324E-06_JPRB,9.81542E-06_JPRB,9.75119E-06_JPRB,9.74533E-06_JPRB, & |
---|
56 | & 9.74139E-06_JPRB,9.73525E-06_JPRB,9.73577E-06_JPRB,9.73618E-06_JPRB /) |
---|
57 | |
---|
58 | SCALEKUR = 50.15_JPRB/48.37_JPRB |
---|
59 | |
---|
60 | LAYREFFR = 32 |
---|
61 | |
---|
62 | ! ------------------------------------------------------------------ |
---|
63 | |
---|
64 | ! The array KA contains absorption coefs at the 16 chosen g-values |
---|
65 | ! for a range of pressure levels> ~100mb, temperatures, and binary |
---|
66 | ! species parameters (see taumol.f for definition). The first |
---|
67 | ! index in the array, JS, runs from 1 to 9, and corresponds to |
---|
68 | ! different values of the binary species parameter. For instance, |
---|
69 | ! JS=1 refers to dry air, JS = 2 corresponds to the paramter value 1/8, |
---|
70 | ! JS = 3 corresponds to the parameter value 2/8, etc. The second index |
---|
71 | ! in the array, JT, which runs from 1 to 5, corresponds to different |
---|
72 | ! temperatures. More specifically, JT = 3 means that the data are for |
---|
73 | ! the reference temperature TREF for this pressure level, JT = 2 refers |
---|
74 | ! to TREF-15, JT = 1 is for TREF-30, JT = 4 is for TREF+15, and JT = 5 |
---|
75 | ! is for TREF+30. The third index, JP, runs from 1 to 13 and refers |
---|
76 | ! to the JPth reference pressure level (see taumol.f for these levels |
---|
77 | ! in mb). The fourth index, IG, goes from 1 to 16, and indicates |
---|
78 | ! which g-interval the absorption coefficients are for. |
---|
79 | ! ----------------------------------------------------------------- |
---|
80 | |
---|
81 | ! ----------------------------------------------------------------- |
---|
82 | ! The array KB contains absorption coefs at the 16 chosen g-values |
---|
83 | ! for a range of pressure levels < ~100mb and temperatures. The first |
---|
84 | ! index in the array, JT, which runs from 1 to 5, corresponds to |
---|
85 | ! different temperatures. More specifically, JT = 3 means that the |
---|
86 | ! data are for the reference temperature TREF for this pressure |
---|
87 | ! level, JT = 2 refers to the temperature TREF-15, JT = 1 is for |
---|
88 | ! TREF-30, JT = 4 is for TREF+15, and JT = 5 is for TREF+30. |
---|
89 | ! The second index, JP, runs from 13 to 59 and refers to the JPth |
---|
90 | ! reference pressure level (see taumol.f for the value of these |
---|
91 | ! pressure levels in mb). The third index, IG, goes from 1 to 16, |
---|
92 | ! and tells us which g-interval the absorption coefficients are for. |
---|
93 | ! ----------------------------------------------------------------- |
---|
94 | |
---|
95 | |
---|
96 | ! ----------------------------------------------------------------- |
---|
97 | IF (LHOOK) CALL DR_HOOK('SRTM_KGB27',1,ZHOOK_HANDLE) |
---|
98 | RETURN |
---|
99 | |
---|
100 | 1001 CONTINUE |
---|
101 | CALL ABOR1("SRTM_KGB27:ERROR READING FILE RADSRTM") |
---|
102 | |
---|
103 | END SUBROUTINE SRTM_KGB27 |
---|