1 | diff --git a/io/bufr/ropp2bufr_mod.f90 b/io/bufr/ropp2bufr_mod.f90
|
---|
2 | index f022f6f..65ee5ea 100644
|
---|
3 | --- a/io/bufr/ropp2bufr_mod.f90
|
---|
4 | +++ b/io/bufr/ropp2bufr_mod.f90
|
---|
5 | @@ -872,7 +872,7 @@ SUBROUTINE ConvertROPPtoBUFR ( ROdata, & ! (in)
|
---|
6 | ROdata%Lev1b%Npoints = 0
|
---|
7 | END IF
|
---|
8 |
|
---|
9 | - Values(IE+1) = ROdata%Lev1b%Npoints ! [031002] Replication factor
|
---|
10 | + Values(IE+1) = ROdata%Lev1b%Npoints ! [031002] Replication factor
|
---|
11 | nRepFac = nRepFac + 1
|
---|
12 | RepFac(nRepFac) = NINT(Values(IE+1))
|
---|
13 |
|
---|
14 | @@ -880,17 +880,17 @@ SUBROUTINE ConvertROPPtoBUFR ( ROdata, & ! (in)
|
---|
15 |
|
---|
16 | ! Coordinates
|
---|
17 |
|
---|
18 | - Values(IE+2) = REAL(ROdata%Lev1b%Lat_tp(in)) ! [005001] Latitude (deg)
|
---|
19 | + Values(IE+2) = REAL(ROdata%Lev1b%Lat_tp(in)) ! [005001] Latitude (deg)
|
---|
20 | IF ( ABS(Values(IE+2)) > 90.0 ) &
|
---|
21 | Values(IE+2) = MISSING
|
---|
22 |
|
---|
23 | - Values(IE+3) = REAL(ROdata%Lev1b%Lon_tp(in)) ! [006001] Longitude (deg)
|
---|
24 | + Values(IE+3) = REAL(ROdata%Lev1b%Lon_tp(in)) ! [006001] Longitude (deg)
|
---|
25 | IF ( Values(IE+3) > 180.0 ) &
|
---|
26 | Values(IE+3) = Values(IE+3) - 360.0
|
---|
27 | IF ( ABS(Values(IE+3)) > 180.0 ) &
|
---|
28 | Values(IE+3) = MISSING
|
---|
29 |
|
---|
30 | - Values(IE+4) = REAL(ROdata%Lev1b%Azimuth_tp(in)) ! [005021] Line of sight bearing (degT)
|
---|
31 | + Values(IE+4) = REAL(ROdata%Lev1b%Azimuth_tp(in)) ! [005021] Line of sight bearing (degT)
|
---|
32 | IF ( Values(IE+4) < 0.0 .OR. &
|
---|
33 | Values(IE+4) >= 360.0 ) &
|
---|
34 | Values(IE+4) = MISSING
|
---|
35 | @@ -899,84 +899,84 @@ SUBROUTINE ConvertROPPtoBUFR ( ROdata, & ! (in)
|
---|
36 |
|
---|
37 | nRepFac = nRepFac + 1
|
---|
38 | IF ( CorrOnly ) THEN
|
---|
39 | - Values(IE+5) = 1 ! [031001] Replication factor
|
---|
40 | + Values(IE+5) = 1 ! [031001] Replication factor
|
---|
41 | IE = IE - 12
|
---|
42 | RepFac(nRepFac) = 1
|
---|
43 | ELSE
|
---|
44 | - Values(IE+5) = 3 ! [031001] Replication factor
|
---|
45 | + Values(IE+5) = 3 ! [031001] Replication factor
|
---|
46 | RepFac(nRepFac) = 3
|
---|
47 |
|
---|
48 | ! L1 data
|
---|
49 |
|
---|
50 | - Values(IE+6) = FreqL1 ! [002121] L1=1.5Ghz
|
---|
51 | + Values(IE+6) = FreqL1 ! [002121] L1=1.5Ghz
|
---|
52 |
|
---|
53 | - Values(IE+7) = REAL(ROdata%Lev1b%Impact_L1(in)) ! [007040] Impact parameter (m)
|
---|
54 | + Values(IE+7) = REAL(ROdata%Lev1b%Impact_L1(in), KIND=dp) ! [007040] Impact parameter (m)
|
---|
55 | IF ( Values(IE+7) < 6200000.0_dp .OR. &
|
---|
56 | Values(IE+7) > 6600000.0_dp ) &
|
---|
57 | Values(IE+7) = MISSING
|
---|
58 |
|
---|
59 | - Values(IE+8) = REAL(ROdata%Lev1b%BAngle_L1(in)) ! [015037] B/angle (rad)
|
---|
60 | + Values(IE+8) = REAL(ROdata%Lev1b%BAngle_L1(in)) ! [015037] B/angle (rad)
|
---|
61 | IF ( Values(IE+8) < -0.001 .OR. &
|
---|
62 | Values(IE+8) > 0.08288 ) &
|
---|
63 | Values(IE+8) = MISSING
|
---|
64 |
|
---|
65 | - Values(IE+9) = FOstats ! [008023] 1st order stats (rms)
|
---|
66 | + Values(IE+9) = FOstats ! [008023] 1st order stats (rms)
|
---|
67 |
|
---|
68 | - Values(IE+10) = REAL(ROdata%Lev1b%BAngle_L1_Sigma(in)) ! [015037] B/angle error (rad)
|
---|
69 | + Values(IE+10) = REAL(ROdata%Lev1b%BAngle_L1_Sigma(in)) ! [015037] B/angle error (rad)
|
---|
70 | IF ( Values(IE+10) < 0.0 .OR. &
|
---|
71 | - Values(IE+10) > 0.009485 ) & ! 1/8 (-3 bits) from 015037
|
---|
72 | + Values(IE+10) > 0.009485 ) & ! 1/8 (-3 bits) from 015037
|
---|
73 | Values(IE+10) = MISSING
|
---|
74 |
|
---|
75 | - Values(IE+11) = MISSING ! [008023] 1st order stats (off)
|
---|
76 | + Values(IE+11) = MISSING ! [008023] 1st order stats (off)
|
---|
77 |
|
---|
78 | ! L2 data
|
---|
79 |
|
---|
80 | - Values(IE+12) = FreqL2 ! [002121] L2=1.2Ghz
|
---|
81 | + Values(IE+12) = FreqL2 ! [002121] L2=1.2Ghz
|
---|
82 |
|
---|
83 | - Values(IE+13) = REAL(ROdata%Lev1b%Impact_L2(in)) ! [007040] Impact parameter (m)
|
---|
84 | + Values(IE+13) = REAL(ROdata%Lev1b%Impact_L2(in), KIND=dp) ! [007040] Impact parameter (m)
|
---|
85 | IF ( Values(IE+13) < 6200000.0_dp .OR. &
|
---|
86 | Values(IE+13) > 6600000.0_dp ) &
|
---|
87 | Values(IE+13) = MISSING
|
---|
88 |
|
---|
89 | - Values(IE+14) = REAL(ROdata%Lev1b%BAngle_L2(in)) ! [015037] B/angle (rad)
|
---|
90 | + Values(IE+14) = REAL(ROdata%Lev1b%BAngle_L2(in)) ! [015037] B/angle (rad)
|
---|
91 | IF ( Values(IE+14) < -0.001 .OR. &
|
---|
92 | Values(IE+14) > 0.08288 ) &
|
---|
93 | Values(IE+14) = MISSING
|
---|
94 |
|
---|
95 | - Values(IE+15) = FOstats ! [008023] 1st order stats (rms)
|
---|
96 | + Values(IE+15) = FOstats ! [008023] 1st order stats (rms)
|
---|
97 |
|
---|
98 | - Values(IE+16) = REAL(ROdata%Lev1b%BAngle_L2_Sigma(in)) ! [015037] B/angle error (rad)
|
---|
99 | + Values(IE+16) = REAL(ROdata%Lev1b%BAngle_L2_Sigma(in)) ! [015037] B/angle error (rad)
|
---|
100 | IF ( Values(IE+16) < 0.0 .OR. &
|
---|
101 | - Values(IE+16) > 0.009485 ) & ! 1/8 (-3 bits) from 015037
|
---|
102 | + Values(IE+16) > 0.009485 ) & ! 1/8 (-3 bits) from 015037
|
---|
103 | Values(IE+16) = MISSING
|
---|
104 |
|
---|
105 | - Values(IE+17) = MISSING ! [008023] 1st order stats (off)
|
---|
106 | + Values(IE+17) = MISSING ! [008023] 1st order stats (off)
|
---|
107 | END IF
|
---|
108 |
|
---|
109 | ! Corrected bending angle (always encoded)
|
---|
110 |
|
---|
111 | - Values(IE+18) = FreqLc ! [002121] corrected
|
---|
112 | + Values(IE+18) = FreqLc ! [002121] corrected
|
---|
113 |
|
---|
114 | - Values(IE+19) = REAL(ROdata%Lev1b%Impact(in)) ! [007040] Impact parameter (m)
|
---|
115 | + Values(IE+19) = REAL(ROdata%Lev1b%Impact(in), KIND=dp) ! [007040] Impact parameter (m)
|
---|
116 | IF ( Values(IE+19) < 6200000.0_dp .OR. &
|
---|
117 | Values(IE+19) > 6600000.0_dp ) &
|
---|
118 | Values(IE+19) = MISSING
|
---|
119 |
|
---|
120 | - Values(IE+20) = REAL(ROdata%Lev1b%BAngle(in)) ! [015037] B/Ang (rad)
|
---|
121 | + Values(IE+20) = REAL(ROdata%Lev1b%BAngle(in)) ! [015037] B/Ang (rad)
|
---|
122 | IF ( Values(IE+20) < -0.001 .OR. &
|
---|
123 | Values(IE+20) > 0.08288 ) &
|
---|
124 | Values(IE+20) = MISSING
|
---|
125 |
|
---|
126 | - Values(IE+21) = FOstats ! [008023] 1st order stats (rms)
|
---|
127 | + Values(IE+21) = FOstats ! [008023] 1st order stats (rms)
|
---|
128 |
|
---|
129 | - Values(IE+22) = REAL(ROdata%Lev1b%BAngle_Sigma(in)) ! [015037] Error in B/Ang (rad)
|
---|
130 | + Values(IE+22) = REAL(ROdata%Lev1b%BAngle_Sigma(in)) ! [015037] Error in B/Ang (rad)
|
---|
131 | IF ( Values(IE+22) < 0.0 .OR. &
|
---|
132 | - Values(IE+22) > 0.009485 ) & ! 1/8 (-3 bits) from 015037
|
---|
133 | + Values(IE+22) > 0.009485 ) & ! 1/8 (-3 bits) from 015037
|
---|
134 | Values(IE+22) = MISSING
|
---|
135 |
|
---|
136 | - Values(IE+23) = MISSING ! [008023] 1st order stats (off)
|
---|
137 | + Values(IE+23) = MISSING ! [008023] 1st order stats (off)
|
---|
138 |
|
---|
139 | - Values(IE+24) = REAL(ROdata%Lev1b%Bangle_Qual(in)) ! [033007] Percent confidence
|
---|
140 | + Values(IE+24) = REAL(ROdata%Lev1b%Bangle_Qual(in)) ! [033007] Percent confidence
|
---|
141 | IF ( Values(IE+24) < 0.0 .OR. &
|
---|
142 | Values(IE+24) > 100.0 ) &
|
---|
143 | Values(IE+24) = MISSING
|
---|
144 | diff --git a/io/ropp/ropp_io_read_ncdf_get.f90 b/io/ropp/ropp_io_read_ncdf_get.f90
|
---|
145 | index 11b09e9..d7a145a 100644
|
---|
146 | --- a/io/ropp/ropp_io_read_ncdf_get.f90
|
---|
147 | +++ b/io/ropp/ropp_io_read_ncdf_get.f90
|
---|
148 | @@ -1697,8 +1697,10 @@ CONTAINS
|
---|
149 | CALL ncdf_getatt('occulting_sat_id', readint)
|
---|
150 | WRITE(data%gns_id,'(A1,I3.3)') 'G', readint
|
---|
151 | readstr = ' '
|
---|
152 | - CALL ncdf_getatt('fiducial_id', readstr)
|
---|
153 | - IF(readstr /= " ") data%stn_id = readstr(1:4)
|
---|
154 | + IF (ncdf_isatt('fiducial_id')) THEN
|
---|
155 | + CALL ncdf_getatt('fiducial_id', readstr)
|
---|
156 | + IF(readstr /= " ") data%stn_id = readstr(1:4)
|
---|
157 | + ENDIF
|
---|
158 |
|
---|
159 | ! 6.4 Overall quality
|
---|
160 | ! -------------------
|
---|
161 | @@ -1819,20 +1821,23 @@ CONTAINS
|
---|
162 | CALL ncdf_getvar('Bend_ang', data%Lev1b%bangle)
|
---|
163 | data%Lev1b%units%bangle = "radians"
|
---|
164 |
|
---|
165 | - CALL ncdf_getvar('Opt_bend_ang', data%Lev1b%bangle_opt)
|
---|
166 | -
|
---|
167 | CALL ncdf_getvar('Bend_ang_stdv', data%Lev1b%bangle_sigma)
|
---|
168 | data%Lev1b%units%bangle_sigma = "radians"
|
---|
169 |
|
---|
170 | data%Lev1b%bangle_opt_sigma = data%Lev1b%bangle_sigma
|
---|
171 |
|
---|
172 | ! set the quality for bangle
|
---|
173 | - CALL ncdf_getatt('_FillValue', readreal, 'Opt_bend_ang')
|
---|
174 | +! CALL ncdf_getatt('_FillValue', readreal, 'Opt_bend_ang')
|
---|
175 | ! idx => WHERE( data%Lev1b%bangle > readreal, nidx)
|
---|
176 | ! IF (nidx > 0) data%Lev1b%bangle_qual(idx) = 100.0
|
---|
177 | WHERE (data%Lev1b%bangle > readreal) &
|
---|
178 | data%Lev1b%bangle_qual = 100.0
|
---|
179 | - data%Lev1b%bangle_opt_qual = data%Lev1b%bangle_qual
|
---|
180 | +
|
---|
181 | + IF (ncdf_isvar('Opt_bend_ang')) THEN
|
---|
182 | + CALL ncdf_getvar('Opt_bend_ang', data%Lev1b%bangle_opt)
|
---|
183 | + CALL ncdf_getatt('_FillValue', readreal, 'Opt_bend_ang')
|
---|
184 | + data%Lev1b%bangle_opt_qual = data%Lev1b%bangle_qual
|
---|
185 | + ENDIF
|
---|
186 |
|
---|
187 | ENDIF
|
---|
188 |
|
---|
189 | @@ -2268,8 +2273,8 @@ CONTAINS
|
---|
190 | REAL(wp), DIMENSION(:), ALLOCATABLE :: rs_phase_l1_iq ! I/Q contribution
|
---|
191 | Integer, DIMENSION(:), ALLOCATABLE :: tracking_state ! Tracking state
|
---|
192 |
|
---|
193 | - INTEGER :: n, n_cl, n_rs, first_valid, j
|
---|
194 | - INTEGER :: readint, readint2
|
---|
195 | + INTEGER :: n, n_cl, n_rs, first_valid, i, j
|
---|
196 | + INTEGER :: readint, readint2, readint3
|
---|
197 | REAL(EightByteReal) :: readreal, readreal2, ts, ts1
|
---|
198 | CHARACTER (len = 256) :: readstr, readstr2
|
---|
199 |
|
---|
200 | @@ -2334,11 +2339,9 @@ CONTAINS
|
---|
201 | data%overall_qual = 100.0_wp * readbyte1
|
---|
202 | data%units%overall_qual = '%'
|
---|
203 |
|
---|
204 | - ! open or closed loop data setting
|
---|
205 | - CALL ncdf_getvar(TRIM(tdir)//'rs_data_available', readbyte1)
|
---|
206 | - CALL ncdf_getvar(TRIM(tdir)//'ol_data_available', readbyte2)
|
---|
207 | -! IF ((readbyte1) .OR. (readbyte2)) data%PCD = IBSET(data%PCD, PCD_open_loop) - right now we only us RS, not OL
|
---|
208 | - IF ((readbyte1 /= 0) .OR. (readbyte2 /= 0)) data%PCD = IBSET(data%PCD, PCD_open_loop)
|
---|
209 | + ! open loop data used?
|
---|
210 | + CALL ncdf_getvar(TRIM(tdir)//'ol_data_used', readbyte1)
|
---|
211 | + IF (readbyte1 /= 0) data%PCD = IBSET(data%PCD, PCD_open_loop)
|
---|
212 |
|
---|
213 | ! setting or rising
|
---|
214 | CALL ncdf_getatt(TRIM(sdir)//'occultation/occultation_type', readstr)
|
---|
215 | @@ -2351,6 +2354,14 @@ CONTAINS
|
---|
216 | IF ((readbyte1 == 0) .AND. (readbyte2 == 0) .AND. (readbyte3 == 0)) &
|
---|
217 | data%PCD = IBSET(data%PCD, PCD_phase)
|
---|
218 |
|
---|
219 | + ! NRT or offline processing?
|
---|
220 | + CALL ncdf_getatt('environment', readstr)
|
---|
221 | + IF (TRIM(readstr) == 'Operational' .OR. &
|
---|
222 | + TRIM(readstr) == 'Validation') THEN
|
---|
223 | + data%PCD = IBCLR(data%PCD, PCD_offline)
|
---|
224 | + ELSE
|
---|
225 | + data%PCD = IBSET(data%PCD, PCD_offline)
|
---|
226 | + ENDIF
|
---|
227 |
|
---|
228 | ! 9.5 Date and time
|
---|
229 | ! -----------------
|
---|
230 | @@ -2940,6 +2951,8 @@ CONTAINS
|
---|
231 | ENDIF
|
---|
232 |
|
---|
233 | ! Software version is the ROPP software version, in the format 'vnn.mmm'.
|
---|
234 | + ! The last digit of the fractional part (mmm) is reserved for indicating
|
---|
235 | + ! the bending angle processing method in case of bufr encoding.
|
---|
236 | ! At ROPP8.0, a new variable, 'processing_software', has been introduced,
|
---|
237 | ! which can hold information about other software - in this case, the EUM
|
---|
238 | ! processing code that generated the data in the first place.
|
---|
239 | @@ -2947,8 +2960,36 @@ CONTAINS
|
---|
240 | data%software_version = ' ' ; readstr = ' ' ; readstr2 = ' '
|
---|
241 |
|
---|
242 | CALL ncdf_getatt('/status/processing/processor_name' , readstr)
|
---|
243 | -
|
---|
244 | - CALL ncdf_getatt('/status/processing/processor_version' ,readstr2)
|
---|
245 | + CALL ncdf_getatt('/status/processing/processor_version' , readstr2)
|
---|
246 | +
|
---|
247 | + i = SCAN(readstr2, ".", .FALSE.)
|
---|
248 | + j = SCAN(readstr2, ".", .TRUE.)
|
---|
249 | +
|
---|
250 | + IF (i < 2) THEN
|
---|
251 | + CALL message(msg_warn, "Processor version cannot be decoded")
|
---|
252 | + ELSE
|
---|
253 | + IF (i == j) THEN
|
---|
254 | + j = LEN_TRIM(readstr2) + 1
|
---|
255 | + READ(readstr2(1:i-1), FMT=*) readint
|
---|
256 | + READ(readstr2(i+1:j-1), FMT=*) readint2
|
---|
257 | + ELSE
|
---|
258 | + READ(readstr2(1:i-1), FMT=*) readint
|
---|
259 | + READ(readstr2(i+1:j-1), FMT=*) readint2
|
---|
260 | + ENDIF
|
---|
261 | + IF (getbufr) THEN
|
---|
262 | + SELECT CASE (TRIM(data%bangle_method))
|
---|
263 | + CASE ("FSI")
|
---|
264 | + readint3 = 1
|
---|
265 | + CASE ("GO")
|
---|
266 | + readint3 = 0
|
---|
267 | + CASE DEFAULT
|
---|
268 | + readint3 = 9
|
---|
269 | + END SELECT
|
---|
270 | + WRITE(data%software_version, '("v",i2.2,".",i2.2,i1)') readint, readint2, readint3
|
---|
271 | + ELSE
|
---|
272 | + WRITE(data%software_version, '("v",i2.2,".",i2.2)') readint, readint2
|
---|
273 | + ENDIF
|
---|
274 | + ENDIF
|
---|
275 |
|
---|
276 | data%processing_software = TRIM(readstr) // ' ' // TRIM(readstr2)
|
---|
277 |
|
---|