Ticket #163: ropp2bufr.f90

File ropp2bufr.f90, 87.7 KB (added by Huw Lewis, 16 years ago)

updated ropp2bufr.f90 file

Line 
1! $Id: ropp2bufr.f90 1959 2008-11-13 12:15:18Z frhl $
2
3MODULE ropp2bufrmod
4
5!****m* ropp2bufr/ropp2bufrmod *
6!
7! NAME
8! ropp2bufrmod - Module defining fixed values & subroutines/functions
9! for the ropp2bufr main program
10!
11! USED BY
12! ropp2bufr
13!
14! AUTHOR
15! Met Office, Exeter, UK.
16! Any comments on this software should be given via the GRAS SAF
17! Helpdesk at http://www.grassaf.org
18!
19! COPYRIGHT
20! (c) EUMETSAT. All rights reserved.
21! For further details please refer to the file COPYRIGHT
22! which you should have received as part of this distribution.
23!
24!****
25
26! Public fixed values for array sizes, etc
27
28! 'Version' is the version number of this complete application program
29
30 CHARACTER (LEN=*), PARAMETER :: Version = "V2.0 1-December-2008" ! Program version
31
32! GTS routing headers
33
34 CHARACTER (LEN=3), PARAMETER :: TTA = "IUT" ! Binary/UAir/Satellite
35 CHARACTER (LEN=2), PARAMETER :: ii = "14" ! Radio Occultation
36 INTEGER, PARAMETER :: RODescr = 310026 ! Table D descriptor for RO
37
38 REAL, PARAMETER :: MISSING = -9999999.0 ! Missing data flag value
39 INTEGER, PARAMETER :: BUFRunit = 20 ! BUFR file output stream
40 INTEGER, PARAMETER :: Bulsunit = 21 ! Bulletin Seq. file I/O stream
41 INTEGER, PARAMETER :: Input = 1 ! Filemode: r old
42 INTEGER, PARAMETER :: Output = 2 ! Filemode: w/r new
43
44 INTEGER, PARAMETER :: NOhdrs = 0 ! No GTS routings headers
45 INTEGER, PARAMETER :: ONLYhdrs = 1 ! GTS Routing headers only
46 INTEGER, PARAMETER :: X25hdrs = 2 ! Headers plus X.25 support
47 INTEGER, PARAMETER :: IPhdrs = 3 ! Headers plus IP support
48
49 INTEGER, PARAMETER :: ErrTim =-1 ! Time threshold rejection
50 INTEGER, PARAMETER :: ErrOK = 0 ! No error
51 INTEGER, PARAMETER :: ErrIO = 1 ! I/O error
52 INTEGER, PARAMETER :: ErrMem = 2 ! Memory allocation error
53
54 LOGICAL :: DEBUG = .FALSE. ! Debug mode
55
56!--------------------------------------------------------------------
57CONTAINS
58!--------------------------------------------------------------------
59SUBROUTINE GetOptions ( ROPPdsn, & ! (out)
60 nfiles, & ! (out)
61 BUFRdsn, & ! (out)
62 BulSeqdsn, & ! (out)
63 Thindsn, & ! (out)
64 OrigICAO, & ! (out)
65 OrigCentre, & ! (out)
66 GTShdrType, & ! (out)
67 RejTimeDiff, & ! (out)
68 CorrOnly, & ! (out)
69 nomet, & ! (out)
70 unordered ) ! (out)
71
72!****s* ropp2bufr/GetOptions *
73!
74! NAME
75! GetOptions - Get command line information & options or set defaults
76!
77! ARGUMENTS
78! ROPPdsn (out) chr ROPP input file name(s)
79! nfiles (out) int No. of ROPP input files
80! BUFRdsn (out) chr BUFR output file name
81! BulSeqdsn (out) chr Bulletin Sequence file name
82! Thindsn (out) chr Thinning control file name
83! OrigICAO (out) chr Originator ICAO code
84! OrigCentre (out) int Originator WMO code
85! GTShdrType (out) int GTS header type code
86! RejTimeDiff (out) int Rejection time threshold (minutes)
87! CorrOnly (out) log L1+L2 skip flag
88! nomet (out) log Met data skip flag
89! unordered (out) log Disable profile ordering flag
90!
91! CALLS
92! IARGC
93! GETARG
94! CT001033
95!
96! CALLED BY
97! ropp2bufr
98!
99! INCLUDES
100! portability.fi - system dependent settings (from BUFR package)
101! to support IARGC(), GETARG() & EXIT()
102!
103! MODULES
104! DateTimeTypes - Date & Time conversion definitions
105! ropp_tyoes
106!
107! SYNOPSIS
108! USE ropp2bufrmod
109! CHARACTER (LEN=100) :: roppdsn(100), bufrdsn, bulseqdsn
110! CHARACTER (LEN=4) :: origicao
111! INTEGER :: nfiles, origcentre, gtshdrtype, rejtimediff
112! LOGICAL :: corronly, nomet, unordered
113! CALL getOptions ( roppdsn, nfiles bufrdsn, bulseqdsn, thindsn, &
114! origicao, origcentre, gtshdrtype, &
115! rejtimediff, corronly, nomet, unordered )
116! On command line:
117! > ropp2bufr ropp_file [ropp_file...]
118! [-o bufr_file] [-c orig_code] [-g[n]]
119! [-s seq_file] [-p thin_file] [-t time]
120! [-u] [-l] [-m] [-h|?] [-v] [-d]
121!
122! DESCRIPTION
123! Provides a command line interface for the ROPP-to-BUFR
124! encoder application. See comments for main program ropp2bufr
125! for the command line details.
126!
127! SEE ALSO
128! ropp2bufr(1)
129!
130! AUTHOR
131! Met Office, Exeter, UK.
132! Any comments on this software should be given via the GRAS SAF
133! Helpdesk at http://www.grassaf.org
134!
135! COPYRIGHT
136! (c) EUMETSAT. All rights reserved.
137! For further details please refer to the file COPYRIGHT
138! which you should have received as part of this distribution.
139!
140!****
141
142 USE CodeTables, ONLY: CT001033
143 USE DateTimeTypes, ONLY: nMinPerHour
144
145! Include files
146
147 INCLUDE 'portability.fi'
148
149! Default Originating Centre (BUFR & ICAO) used if -c option
150! is not given on command line. Possible codes for GPSRO include:
151! 007/KWBC - Washington (USA)
152! 074/EGRR - Exeter (UK)
153! 078/EDZW - Offenbach (D)
154! 094/EKMI - Copenhagen (DK)
155! See BUFR code/flag table file (plain text version), code table 001033
156! for the full list of Originating Centres.
157
158 CHARACTER (LEN=*), PARAMETER :: DefOrigICAO = "EGRR" ! MetO Exeter
159 INTEGER, PARAMETER :: DefOrigCentre = 74 ! MetO Exeter
160
161 CHARACTER (LEN=8), PARAMETER :: Defdsn = "ropp.nc" ! Default input file name
162
163 INTEGER, PARAMETER :: DefRejTimeDiff = 1430 ! 23h50m in minutes
164
165! Argument list parameters
166
167 CHARACTER (LEN=*), INTENT(OUT) :: ROPPdsn(:) ! input ROPP file name(s)
168 CHARACTER (LEN=*), INTENT(OUT) :: BUFRdsn ! output BUFR file name
169 CHARACTER (LEN=*), INTENT(OUT) :: BulSeqdsn ! bulletin sequence file name
170 CHARACTER (LEN=*), INTENT(OUT) :: Thindsn ! thinning control file name
171 CHARACTER (LEN=*), INTENT(OUT) :: OrigICAO ! originating centre ICAO code
172 INTEGER, INTENT(OUT) :: nfiles ! No. of ROPP input files
173 INTEGER, INTENT(OUT) :: OrigCentre ! originating centre BUFR code
174 INTEGER, INTENT(OUT) :: GTShdrType ! code for GTS header generation
175 INTEGER, INTENT(OUT) :: RejTimeDiff ! reject obs older than this
176 LOGICAL, INTENT(OUT) :: CorrOnly ! .F. for L1+L2+C, .T. for C only
177 LOGICAL, INTENT(OUT) :: nomet ! .F. for met data, .T. to skip
178 LOGICAL, INTENT(OUT) :: unordered ! .T. to disable re-ordering of profiles
179
180! Local variables
181
182 INTEGER, PARAMETER :: descr = 001033 ! BUFR descriptor for originating
183 ! centre code table
184 CHARACTER (LEN=256) :: carg ! command line argument
185 CHARACTER (LEN=30) :: Centre ! decoded ICAO name of orig. centre
186 CHARACTER (LEN=256) :: ProgNam ! program name
187
188 INTEGER :: narg ! number of command line arguments
189 INTEGER :: ia ! loop counter
190 INTEGER :: ierr ! error status
191 INTEGER :: hh, mm ! hours & minutes
192 INTEGER :: oc ! originating centre
193
194!-------------------------------------------------------------
195! 1. Initialise
196!-------------------------------------------------------------
197
198 ROPPdsn(:) = DefDsn
199 nfiles = 0
200 BUFRdsn = " "
201 BulSeqdsn = " "
202 Thindsn = "375" ! to be interpreted as 'sample to no more than'
203 OrigICAO = " "
204 OrigCentre = DefOrigCentre
205 GTShdrType = NOhdrs
206 RejTimeDiff = 0
207 CorrOnly = .FALSE.
208 nomet = .FALSE.
209 unordered = .FALSE.
210
211 CALL GETARG ( 0, ProgNam )
212 ia = LEN_TRIM(ProgNam)
213 DO WHILE ( ia > 0 .AND. &
214 ProgNam(ia:ia) /= SysEndDirChr )
215 ia = ia - 1
216 END DO
217 ProgNam = ProgNam(ia+1:)
218 IF ( ProgNam == " " ) ProgNam = "ropp2bufr"
219
220!-------------------------------------------------------------
221! 2. Loop over all command line options.
222! If a switch has a trailing blank, then we need to get
223! the next string as it's argument.
224!-------------------------------------------------------------
225
226 ia = 1
227 narg = IARGC()
228
229 DO WHILE ( ia <= narg )
230
231 CALL GETARG ( ia, carg )
232 IF ( carg(1:1) == "?" ) carg = "-h"
233
234 IF ( carg(1:1) == "-" ) THEN ! is this an option introducer?
235 ! If so, which one?
236 SELECT CASE (carg(2:2))
237
238 CASE ("c","C") ! Originating centre code
239 carg(1:2) = " "
240 IF ( carg(3:) == " " ) THEN
241 ia = ia + 1
242 CALL GETARG ( ia, carg )
243 END IF
244 READ ( carg, *, IOSTAT=ierr ) oc
245 IF ( ierr == 0 ) OrigCentre = oc
246
247 CASE ("d","D") ! debug/diagnostics wanted
248 DEBUG = .TRUE.
249
250 CASE ("g","G") ! GTS headers wanted - any extra X.25 or IP?
251 SELECT CASE (carg(3:3))
252 CASE ("i","I" )
253 GTShdrType = IPhdrs ! headers + IP
254 CASE ("x","X")
255 GTShdrType = X25hdrs ! headers + X.25
256 CASE DEFAULT
257 GTShdrType = ONLYhdrs ! headers only
258 END SELECT
259
260 CASE ("l","L") ! no L1/L2 (Corrected only)
261 CorrOnly = .TRUE.
262
263 CASE ("m","M") ! no Met. (geophysical) data
264 nomet = .TRUE.
265
266 CASE ("o","O") ! Output file name
267 carg(1:2) = " "
268 IF ( carg(3:) == " " ) THEN
269 ia = ia + 1
270 CALL GETARG ( ia, carg )
271 END IF
272 BUFRdsn = ADJUSTL(carg)
273
274 CASE ("p","P") ! thinning control file name
275 carg(1:2) = " "
276 IF ( carg(3:) == " " ) THEN
277 ia = ia + 1
278 CALL GETARG ( ia, carg )
279 END IF
280 Thindsn = ADJUSTL(carg)
281
282 CASE ("s","S") ! Bulletin Sequence No. file name
283 carg(1:2) = " "
284 IF ( carg(3:) == " " ) THEN
285 ia = ia + 1
286 CALL GETARG ( ia, carg )
287 END IF
288 BulSeqdsn = ADJUSTL(carg)
289
290 CASE ("t","T") ! Reject time difference (hh:mm)
291 carg(1:2) = " "
292 IF ( carg(3:) == " " ) THEN
293 ia = ia + 1
294 CALL GETARG ( ia, carg )
295 END IF
296 carg = ADJUSTL(carg)
297 READ ( carg, "(BN,I2,1X,I2)", IOSTAT=ierr ) hh, mm
298 IF ( ierr == 0 ) RejTimeDiff = hh * nMinPerHour + mm
299
300 CASE ("u","U") ! Profile ordering
301 unordered = .TRUE.
302
303 CASE ("h","H") ! help
304 WRITE ( *, * ) "Purpose:"
305 WRITE ( *, * ) " Encode one or more ROPP-format files to WMO BUFR."
306 WRITE ( *, * ) "Usage:"
307 WRITE ( *, * ) "> ",TRIM(ProgNam)," ropp_file [ropp_file...] [-o bufr_file]"
308 WRITE ( *, * ) REPEAT(" ",LEN_TRIM(ProgNam)+13)//&
309 "[-c orig_code] [-g[n]] [-s seq_file]"
310 WRITE ( *, * ) REPEAT(" ",LEN_TRIM(ProgNam)+13)//&
311 "[-p thin_file|maxsamp] [-t time]"
312 WRITE ( *, * ) REPEAT(" ",LEN_TRIM(ProgNam)+13)//&
313 "[-u] [-l] [-d] [-m] [-h|?] [-v]"
314 WRITE ( *, * ) "Input:"
315 WRITE ( *, * ) " Files must be in ROPP V1.0 (TEXT or netCDF)"
316 WRITE ( *, * ) " or CLIMAP V2.2 (TEXT) format."
317 WRITE ( *, * ) "Options:"
318 WRITE ( *, * ) " -o BUFR output file name"
319 WRITE ( *, * ) " -c originating centre code value"
320 WRITE ( *, * ) " -g GTS routing headers/trailers required"
321 WRITE ( *, * ) " -gx GTS routine headers preceded by 4 leading"
322 WRITE ( *, * ) " null bytes for GTS X.25 transmission"
323 WRITE ( *, * ) " -gi GTS headers preceded by 10-byte leading"
324 WRITE ( *, * ) " size/type for GTS IP (FTP) transmission"
325 WRITE ( *, * ) " -s file containing last bulletin sequence number"
326 WRITE ( *, * ) " (updated on completion)"
327 WRITE ( *, * ) " -p thinning control file name or max. no. samples"
328 WRITE ( *, * ) " -t don't encode data older than 'time' ago (hh:mm)"
329 WRITE ( *, * ) " -u leave profiles unordered (i.e. in original order)"
330 WRITE ( *, * ) " -l specifies that L1+L2 data (Level 1b) are not encoded,"
331 WRITE ( *, * ) " only the ionospheric-corrected profile."
332 WRITE ( *, * ) " -m specifies that met data (Level 2c/d) are not encoded"
333 WRITE ( *, * ) " -d outputs additonal diagnostics to stdout"
334 WRITE ( *, * ) " -h or ? writes this help (and does nothing else)"
335 WRITE ( *, * ) " -v writes program version ID (and does nothing else)"
336 WRITE ( *, * ) "Defaults:"
337 WRITE ( *, * ) " Input file name : ropp.nc"
338 WRITE ( *, * ) " Output file name : from Occultation ID"
339 WRITE ( *, * ) " Originating centre code : 74 (Met Office, Exeter)"
340 WRITE ( *, * ) " GTS routing headers : not generated"
341 WRITE ( *, * ) " Bulletin sequence nos. : starts at 001"
342 WRITE ( *, * ) " Reject time difference : 00:00 (no rejection on time)"
343 WRITE ( *, * ) " unless -g* option, when: 23:50 (assuming NRT on GTS)"
344 WRITE ( *, * ) " Thinning : sample to <= 375 levels"
345 WRITE ( *, * ) " Re-ordering : descending profiles re-ordered to ascending"
346 WRITE ( *, * ) "Output:"
347 WRITE ( *, * ) " One output BUFR message"
348 WRITE ( *, * ) "See ropp2bufr(1) for details."
349 WRITE ( *, * ) " "
350 CALL EXIT(ErrOK)
351
352 CASE ("v","V") ! program version
353 WRITE ( *, FMT="(A/)" ) TRIM(ProgNam)//": Version "// TRIM(Version)
354 CALL EXIT(ErrOK)
355
356 CASE DEFAULT ! unknown option
357 END SELECT
358
359 ELSE ! not an option - must be an input name
360 nfiles = nfiles + 1
361 ROPPdsn(nfiles) = carg
362 END IF
363
364 ia = ia + 1
365 END DO ! argument loop
366
367 IF ( nfiles == 0 ) nfiles = 1 ! No input files - try a default name
368
369!-------------------------------------------------------------
370! 3. Check originating centre code is valid
371!-------------------------------------------------------------
372
373 IF ( OrigCentre <= 0 .OR. &
374 OrigCentre >= 255 ) THEN
375 WRITE ( *, FMT="(A,I6,A,I3.3)" ) &
376 "WARNING: Originating centre code ", OrigCentre, &
377 " invalid - using default", DefOrigCentre
378 OrigCentre = DefOrigCentre
379 END IF
380
381!-------------------------------------------------------------
382! 4. If GTS header wanted, and not default, get 'cccc' code
383! from BUFR code table for specified orginating centre ID.
384! If not found, fall back to defaults.
385!-------------------------------------------------------------
386
387 IF ( GTShdrType /= NOhdrs .AND. &
388 OrigCentre /= DefOrigCentre ) THEN
389 CALL CT001033 ( OrigCentre, Centre, OrigICAO )
390 IF ( OrigICAO == "UNKN" ) THEN
391 WRITE ( *, FMT="(2(1X,A,I3.3,3A/))" ) &
392 "Warning: Originating centre ", OrigCentre, " (", &
393 TRIM(Centre), ") has no ICAO code", &
394 " - using default ", DefOrigCentre, " (", &
395 DefOrigICAO, ")"
396 OrigICAO = DefOrigICAO
397 OrigCentre = DefOrigCentre
398 END IF
399
400 ELSE
401 OrigICAO = DefOrigICAO
402
403 END IF
404
405!-------------------------------------------------------------
406! 5. Set default time rejection if GTS routing headers to be
407! generated, on the assumption that the output is for NRT
408! GTS distribution.
409!-------------------------------------------------------------
410
411 IF ( GTShdrType /= NOhdrs .AND. &
412 RejTimeDiff == 0 ) RejTimeDiff = DefRejTimeDiff
413
414END SUBROUTINE GetOptions
415!---------------------------------------------------------------------------
416SUBROUTINE BulSeqIO ( BulSeqdsn, & !(in)
417 BulSeqNo, & !(inout)
418 inout ) !(in)
419
420!****s* ropp2bufr/BulSeqNo *
421!
422! NAME
423! BulSeqNo - Read or save a bulletin sequence number
424!
425! ARGUMENTS
426! BulSeqdsn (in) chr Bulletin sequence file
427! BulSeqNo (inout) int Bulletin sequence number (001-999)
428! inout (in) int Flag for input (<=1) or output (>=2)
429!
430! CALLED BY
431! ropp2bufr
432!
433! SYNOPSIS
434! CHARACTER (LEN=100) :: bulseqdsn
435! INTEGER :: bulseqno
436! CALL BulSeqIO ( bulseqdsn, bulseqno )
437!
438! DESCRIPTION
439! Reads (if inout <=1) or writes (if inout >=2) a bulletin
440! sequence number (which should be in the range 001-999) from/to
441! the given file. If the file name is blank, nothing happens.
442! Warning messages are written to stdout if any I/O error
443! occurs (the value of BulSeqNo is unchanged), but otherwise
444! the action is silent. The file name may include a path, and
445! should be accessible for read & write.
446!
447! AUTHOR
448! Met Office, Exeter, UK.
449! Any comments on this software should be given via the GRAS SAF
450! Helpdesk at http://www.grassaf.org
451!
452! COPYRIGHT
453! (c) EUMETSAT. All rights reserved.
454! For further details please refer to the file COPYRIGHT
455! which you should have received as part of this distribution.
456!
457!****
458
459! Argument list parameters
460
461 CHARACTER (LEN=*), INTENT(IN) :: BulSeqdsn
462 INTEGER, INTENT(INOUT) :: BulSeqNo
463 INTEGER, INTENT(IN) :: inout
464
465! Local valitables
466
467 INTEGER :: ierr
468
469!-------------------------------------------------------------
470! 1. Read previous bulletin sequence number...
471!-------------------------------------------------------------
472
473 IF ( inout <= 1 ) THEN
474
475 IF ( BulSeqdsn /= " " ) THEN
476 OPEN ( FILE=BulSeqdsn, &
477 UNIT=BulsUnit, &
478 ACTION="READ", &
479 IOSTAT=ierr )
480 IF ( ierr == 0 ) THEN
481 READ ( UNIT=BulsUnit, &
482 FMT=*, &
483 IOSTAT=ierr ) in
484 IF ( ierr == 0 ) THEN
485 BulSeqNo = in
486 ELSE
487 WRITE ( *, FMT="(A)" ) "WARNING: Invalid last Bulletin Sequence value"
488 END IF
489 ELSE
490 WRITE ( *, FMT="(A)" ) "WARNING: Bulletin Sequence read file open error"
491 WRITE ( *, FMT="(A)" ) " "//TRIM(BulSeqdsn)
492 END IF
493 CLOSE ( UNIT=BulsUnit, &
494 IOSTAT=ierr )
495 END IF
496
497!-------------------------------------------------------------
498! 2. ...or save current bulletin sequence number
499!-------------------------------------------------------------
500
501 ELSE
502 IF ( BulSeqdsn /= " " ) THEN
503 OPEN ( FILE=BulSeqdsn, &
504 UNIT=BulsUnit, &
505 ACTION="WRITE", &
506 IOSTAT=ierr )
507 IF ( ierr == 0 ) THEN
508 WRITE ( UNIT=BulsUnit, &
509 FMT="(I3.3)", &
510 IOSTAT=ierr ) BulSeqNo
511 IF ( ierr /= 0 ) &
512 WRITE ( *, FMT="(A)" ) "WARNING: Failed to write Bulletin Sequence value"
513 ELSE
514 WRITE ( *, FMT="(A)" ) "WARNING: Bulletin Sequence save file open error"
515 WRITE ( *, FMT="(A)" ) " "//TRIM(BulSeqdsn)
516 END IF
517 CLOSE ( UNIT=BulsUnit, &
518 IOSTAT=ierr )
519 END IF
520 END IF
521
522END SUBROUTINE BulSeqIO
523!----------------------------------------------------------------------------
524SUBROUTINE ConvertROPPtoBUFR ( ROdata, & ! (in)
525 CorrOnly, & ! (in)
526 SubCentre, & ! (out)
527 Values, & ! (out)
528 Nvalues ) ! (out)
529!
530!****s* ropp2bufr/ConvertROPPtoBUFR *
531!
532! NAME
533! ConvertROPPtoBUFR - Convert ROPP data to BUFR specification
534!
535! ARGUMENTS
536! ROdata (inout) dtyp RO data - derived type
537! CorrOnly (in) log Flag for corrected Level 1b profile only
538! SubCentre (out) int Originating centre code value
539! Values (out) flt Array(ne) of converted values for BUFR encoder
540! Nvalues (out) int Total no. of values converted
541!
542! MODULES
543! - - ROPP file I/O support
544!
545! CALLS
546! ConvertCodes
547!
548! CALLED BY
549! ropp2bufr
550!
551! SYNOPSIS
552! USE ropp_io_types
553! USE ropp2bufrmod
554! TYPE (ROprof) ROdata
555! INTEGER :: subcentre
556! REAL :: Values(ne)
557! LOGICAL :: corronly
558! CALL ConvertROPPtoBUFR ( ROdata, corronly, &
559! subcentre, values )
560! where
561! ne is the number of elements (data items for BUFR)
562!
563! DESCRIPTION
564! Converts RO data to BUFR units, etc, and returns converted
565! data as a plain array.
566! This procedure is mostly scaling and/or range changing
567! (e.g longitude from 0-360 to +/-180deg, hPa to Pa).
568! This routine also performs gross error checking, so that
569! if data is not valid (not within nominal range of BUFR bit width)
570! that data value is set "missing" in the output array.
571!
572! REFERENCES
573! 1) ROPP interface file format
574! SAF/GRAS/METO/FMT/ROPP/001
575! 2) WMO FM94 (BUFR) Specification for GRAS SAF Processed Radio
576! Occultation Data. SAF/GRAS/UKMO/FMT/BUFR/01
577!
578! AUTHOR
579! Met Office, Exeter, UK.
580! Any comments on this software should be given via the GRAS SAF
581! Helpdesk at http://www.grassaf.org
582!
583! COPYRIGHT
584! (c) EUMETSAT. All rights reserved.
585! For further details please refer to the file COPYRIGHT
586! which you should have received as part of this distribution.
587!
588!****
589
590! Modules
591
592 USE ropp_io_types, ONLY: ROprof, &
593 PCD_occultation
594
595 IMPLICIT NONE
596
597! Fixed parameters
598
599 INTEGER, PARAMETER :: MISSING = -9999999 ! Missing data flag value
600
601 INTEGER, PARAMETER :: ProdType = 2 ! Product type (limb sounding)
602 INTEGER, PARAMETER :: FOstats = 13 ! First-order statistics (rms)
603
604 REAL, PARAMETER :: FreqL1 = 1.5E9 ! L1 frequency: 1.5GHz
605 REAL, PARAMETER :: FreqL2 = 1.2E9 ! L1 frequency: 1.2GHz
606 REAL, PARAMETER :: FreqLc = 0.0 ! Corrected frequency (dummy)
607
608 CHARACTER (LEN=*), PARAMETER :: numeric = "0123456789." ! valid for numerics
609
610! Argument list parameters
611
612 TYPE (ROprof), INTENT(INOUT):: ROdata
613 LOGICAL, INTENT(IN) :: CorrOnly
614 INTEGER, INTENT(OUT) :: SubCentre
615 REAL, INTENT(OUT) :: Values(:)
616 INTEGER, INTENT(OUT) :: Nvalues
617
618! Local parameters
619
620 CHARACTER (LEN=10) :: strnum ! temporary strings for numeric values
621 INTEGER :: Gclass ! GNSS class value
622 INTEGER :: Gcode ! GNSS PRN
623 INTEGER :: Lcode ! LEO code value
624 INTEGER :: Icode ! Instrument code value
625 INTEGER :: Ocode ! Origin. centre code value
626 INTEGER :: Scode ! Sub-centre code value
627 INTEGER :: Bcode ! B/G generator code value
628 INTEGER :: PCD ! PCD bit flags (16-bit)
629 INTEGER :: in ! loop counter for profile arrays
630 INTEGER :: IE ! index offset to Values element
631 INTEGER :: ierr ! I/O error code
632 REAL :: SWver ! Softwre version number
633
634!-------------------------------------------------------------
635! 1. Initialise
636!------------------------------------------------------------
637
638 Values(:) = MISSING
639
640!-------------------------------------------------------------
641! 2. Convert ROPP character codes to BUFR numeric codes.
642!-------------------------------------------------------------
643
644 CALL ConvertCodes ( ROdata, &
645 Gclass, Gcode, &
646 Lcode, Icode, &
647 Ocode, Scode, &
648 Bcode, &
649 1 )
650 SubCentre = Scode
651
652!-------------------------------------------------------------
653! 3. Satellite data introducer
654!-------------------------------------------------------------
655
656 Values(1) = Lcode ! LEO ID
657 Values(2) = Icode ! RO Instrument
658 IF ( BTEST(ROdata%PCD,PCD_occultation) ) THEN
659 Values(3) = Bcode ! B/g gen.centre
660 ELSE
661 Values(3) = Ocode ! Proc.centre
662 END IF
663 Values(4) = ProdType ! Product type
664
665 strnum = ROdata%Software_Version(1:10)
666 DO in = 1, LEN_TRIM(strnum)
667 IF ( INDEX ( numeric, strnum(in:in) ) == 0 ) strnum(in:in) = " "
668 END DO
669 READ ( strnum, FMT=*, IOSTAT=ierr) SWver
670 IF ( ierr /= 0 ) SWver = -9.999
671 Values(5) = SWver * 1E3 ! Software version
672 IF ( Values(5) < 0.0 .OR. &
673 Values(5) > 16382.0 ) &
674 Values(5) = MISSING
675
676! Date/time of start of occultation (or background profile)
677
678 Values(6) = 17. ! Time.sig (start)
679 Values(7) = ROdata%DTocc%Year ! Year
680 Values(8) = ROdata%DTocc%Month ! Month
681 Values(9) = ROdata%DTocc%Day ! Day
682 Values(10) = ROdata%DTocc%Hour ! Hour
683 Values(11) = ROdata%DTocc%Minute ! Minute
684 Values(12) = ROdata%DTocc%Second & ! Seconds & MSecs
685 + ROdata%DTocc%MSec * 1E-3
686 IF ( Values(12) < 0.000 .OR. &
687 Values(12) > 59.999 ) &
688 Values(12) = MISSING
689
690! Summary quality information
691
692 PCD = 0
693 DO in = 0, 15
694 IF ( BTEST(ROdata%PCD, in) ) PCD = IBSET(PCD, 15-in) ! only use 1st 16 bits in swapped bit order
695 END DO
696 Values(13) = REAL(PCD) ! PCD
697 IF ( Values(13) < 0.0 .OR. &
698 Values(13) > 65534.0 ) &
699 Values(13) = MISSING
700
701 Values(14) = REAL(ROdata%Overall_Qual) ! Percent confidence
702 IF ( Values(14) < 0.0 .OR. &
703 Values(14) > 100.0 ) &
704 Values(14) = MISSING
705
706! LEO & GNSS POD
707
708 IF ( ROdata%Lev1a%Npoints > 0 ) THEN
709 Values(15) = REAL(ROdata%Lev1a%R_LEO(1,1)) ! LEO X posn (m)
710 IF ( ABS(Values(15)) > 10737418.23 ) &
711 Values(15) = MISSING
712 Values(16) = REAL(ROdata%Lev1a%R_LEO(1,2)) ! LEO Y posn (m)
713 IF ( ABS(Values(16)) > 10737418.23 ) &
714 Values(16) = MISSING
715 Values(17) = REAL(ROdata%Lev1a%R_LEO(1,3)) ! LEO Z posn (m)
716 IF ( ABS(Values(17)) > 10737418.23 ) &
717 Values(17) = MISSING
718 IF ( ABS(Values(15)) < 1.0 .AND. &
719 ABS(Values(16)) < 1.0 .AND. &
720 ABS(Values(17)) < 1.0 ) &
721 Values(15:17) = MISSING
722 Values(18) = REAL(ROdata%Lev1a%V_LEO(1,1)) ! LEO X vely (m/s)
723 IF ( ABS(Values(18)) > 10737.41823 ) &
724 Values(18) = MISSING
725 Values(19) = REAL(ROdata%Lev1a%V_LEO(1,2)) ! LEO Y vely (m/s)
726 IF ( ABS(Values(19)) > 10737.41823 ) &
727 Values(19) = MISSING
728 Values(20) = REAL(ROdata%Lev1a%V_LEO(1,3)) ! LEO Z vely (m/s)
729 IF ( ABS(Values(20)) > 10737.41823 ) &
730 Values(20) = MISSING
731 IF ( ABS(Values(18)) < 1.0 .AND. &
732 ABS(Values(19)) < 1.0 .AND. &
733 ABS(Values(20)) < 1.0 ) &
734 Values(18:20) = MISSING
735 END IF
736
737 Values(21) = Gclass ! GNSS class
738 Values(22) = Gcode ! GNSS PRN
739
740 IF ( ROdata%Lev1a%Npoints > 0 ) THEN
741 Values(23) = REAL(ROdata%Lev1a%R_GNS(1,1)) ! GNSS X posn (m)
742 IF ( ABS(Values(23)) > 107374182.4 ) &
743 Values(23) = MISSING
744 Values(24) = REAL(ROdata%Lev1a%R_GNS(1,2)) ! GNSS Y posn (m)
745 IF ( ABS(Values(24)) > 107374182.4 ) &
746 Values(24) = MISSING
747 Values(25) = REAL(ROdata%Lev1a%R_GNS(1,3)) ! GNSS Z posn (m)
748 IF ( ABS(Values(25)) > 107374182.4 ) &
749 Values(25) = MISSING
750 IF ( ABS(Values(23)) < 1.0 .AND. &
751 ABS(Values(24)) < 1.0 .AND. &
752 ABS(Values(25)) < 1.0 ) &
753 Values(23:25) = MISSING
754
755 Values(26) = REAL(ROdata%Lev1a%V_GNS(1,1)) ! GNSS X vely (m/s)
756 IF ( ABS(Values(26)) > 10737.41824 ) &
757 Values(26) = MISSING
758 Values(27) = REAL(ROdata%Lev1a%V_GNS(1,2)) ! GNSS Y vely (m/s)
759 IF ( ABS(Values(27)) > 10737.41824 ) &
760 Values(27) = MISSING
761 Values(28) = REAL(ROdata%Lev1a%V_GNS(1,3)) ! GNSS Z vely (m/s)
762 IF ( ABS(Values(28)) > 10737.41824 ) &
763 Values(28) = MISSING
764 IF ( ABS(Values(26)) < 1.0 .AND. &
765 ABS(Values(27)) < 1.0 .AND. &
766 ABS(Values(28)) < 1.0 ) &
767 Values(26:28) = MISSING
768 END IF
769
770! Local Earth parameters
771
772 Values(29) = REAL(ROdata%GeoRef%Time_Offset) ! Time/start (s)
773 IF ( Values(29) < 0.0 .OR. &
774 Values(29) > 240.0 ) &
775 Values(29) = MISSING
776
777 Values(30) = REAL(ROdata%GeoRef%Lat) ! Latitude (deg)
778 IF ( ABS(Values(30)) > 90.0 ) &
779 Values(30) = MISSING
780
781 Values(31) = REAL(ROdata%GeoRef%Lon) ! Longitude (deg)
782 IF ( Values(31) > 180.0 ) &
783 Values(31) = Values(31) - 360.0
784 IF ( ABS(Values(31)) > 180.0 ) &
785 Values(31) = MISSING
786
787 Values(32) = REAL(ROdata%GeoRef%r_CoC(1)) ! CofC X (m)
788 IF ( ABS(Values(32)) > 1000000.0 ) &
789 Values(32) = MISSING
790
791 Values(33) = REAL(ROdata%GeoRef%r_CoC(2)) ! CofC Y (m)
792 IF ( ABS(Values(33)) > 1000000.0 ) &
793 Values(33) = MISSING
794
795 Values(34) = REAL(ROdata%GeoRef%r_CoC(3)) ! CofC Z (m)
796 IF ( ABS(Values(34)) > 1000000.0 ) &
797 Values(34) = MISSING
798
799 Values(35) = REAL(ROdata%GeoRef%RoC) ! Radius value (m)
800 IF ( Values(35) < 6200000.0 .OR. &
801 Values(35) > 6600000.0 ) &
802 Values(35) = MISSING
803
804 Values(36) = REAL(ROdata%GeoRef%Azimuth) ! Line of sight bearing (degT)
805 IF ( Values(36) < 0.0 .OR. &
806 Values(36) >= 360.0 ) &
807 Values(36) = MISSING
808
809 Values(37) = REAL(ROdata%GeoRef%Undulation) ! Geoid undulation (m)
810 IF ( ABS(Values(37)) > 163.82 ) &
811 Values(37) = MISSING
812
813 IE = 37
814
815!-------------------------------------------------------------
816! 4. Level 1b data (bending angle profile)
817!-------------------------------------------------------------
818
819 Values(IE+1) = ROdata%Lev1b%Npoints ! Replication factor
820
821 DO in = 1, ROdata%Lev1b%Npoints
822
823! Coordinates
824
825 Values(IE+2) = REAL(ROdata%Lev1b%Lat_tp(in)) ! Latitude (deg)
826 IF ( ABS(Values(IE+2)) > 90.0 ) &
827 Values(IE+2) = MISSING
828
829 Values(IE+3) = REAL(ROdata%Lev1b%Lon_tp(in)) ! Longitude (deg)
830 IF ( Values(IE+3) > 180.0 ) &
831 Values(IE+3) = Values(IE+3) - 360.0
832 IF ( ABS(Values(IE+3)) > 180.0 ) &
833 Values(IE+3) = MISSING
834
835 Values(IE+4) = REAL(ROdata%Lev1b%Azimuth_tp(in)) ! Line of sight bearing (degT)
836 IF ( Values(IE+4) < 0.0 .OR. &
837 Values(IE+4) >= 360.0 ) &
838 Values(IE+4) = MISSING
839
840! Include L1+L2 or skip them?
841
842 IF ( CorrOnly ) THEN
843 Values(IE+5) = 1 ! Replication factor
844 IE = IE - 12
845 ELSE
846 Values(IE+5) = 3
847
848! L1 data
849
850 Values(IE+6) = FreqL1 ! L1=1.5Ghz
851
852 Values(IE+7) = REAL(ROdata%Lev1b%Impact_L1(in)) ! Impact parameter (m)
853 IF ( Values(IE+7) < 6200000.0 .OR. &
854 Values(IE+7) > 6600000.0 ) &
855 Values(IE+7) = MISSING
856
857 Values(IE+8) = REAL(ROdata%Lev1b%BAngle_L1(in)) ! B/angle (rad)
858 IF ( Values(IE+8) < -1.0E-3 .OR. &
859 Values(IE+8) > 8.288E-2 ) &
860 Values(IE+8) = MISSING
861
862 Values(IE+9) = FOstats ! 1st order stats (rms)
863
864 Values(IE+10) = REAL(ROdata%Lev1b%BAngle_L1_Sigma(in)) ! B/angle error (rad)
865 IF ( Values(IE+10) < 0.0 .OR. &
866 Values(IE+10) > 1.0E-2 ) &
867 Values(IE+10) = MISSING
868 Values(IE+10) = MIN ( Values(IE+10), 0.00948 ) ! allow for BUFR offset
869
870 Values(IE+11) = MISSING ! 1st order stats (off)
871
872! L2 data
873
874 Values(IE+12) = FreqL2 ! L2=1.2Ghz
875
876 Values(IE+13) = REAL(ROdata%Lev1b%Impact_L2(in)) ! Impact parameter (m)
877 IF ( Values(IE+13) < 6200000.0 .OR. &
878 Values(IE+13) > 6600000.0 ) &
879 Values(IE+13) = MISSING
880
881 Values(IE+14) = REAL(ROdata%Lev1b%BAngle_L2(in)) ! B/angle (rad)
882 IF ( Values(IE+14) < -1.0E-3 .OR. &
883 Values(IE+14) > 8.288E-2 ) &
884 Values(IE+14) = MISSING
885
886 Values(IE+15) = FOstats ! 1st order stats (rms)
887
888 Values(IE+16) = REAL(ROdata%Lev1b%BAngle_L2_Sigma(in)) ! B/angle error (rad)
889 IF ( Values(IE+16) < 0.0 .OR. &
890 Values(IE+16) > 1.0E-2 ) &
891 Values(IE+16) = MISSING
892 Values(IE+16) = MIN ( Values(IE+16), 0.00948 ) ! allow for BUFR offset
893
894 Values(IE+17) = MISSING ! 1st order stats (off)
895 END IF
896
897! Corrected bending angle (always encoded)
898
899 Values(IE+18) = FreqLc ! corrected
900
901 Values(IE+19) = REAL(ROdata%Lev1b%Impact(in)) ! Impact parameter (m)
902 IF ( Values(IE+19) < 6200000.0 .OR. &
903 Values(IE+19) > 6600000.0 ) &
904 Values(IE+19) = MISSING
905
906 Values(IE+20) = REAL(ROdata%Lev1b%BAngle(in)) ! B/Ang (rad)
907 IF ( Values(IE+20) < -1.0E-3 .OR. &
908 Values(IE+20) > 8.288E-2 ) &
909 Values(IE+20) = MISSING
910
911 Values(IE+21) = FOstats ! 1st order stats (rms)
912
913 Values(IE+22) = REAL(ROdata%Lev1b%BAngle_Sigma(in)) ! Error in B/Ang (rad)
914 IF ( Values(IE+22) < 0.0 .OR. &
915 Values(IE+22) > 1.0E-2 ) &
916 Values(IE+22) = MISSING
917 Values(IE+22) = MIN ( Values(IE+22), 0.00948 ) ! allow for BUFR offset
918
919 Values(IE+23) = MISSING ! 1st order stats (off)
920
921 Values(IE+24) = REAL(ROdata%Lev1b%Bangle_Qual(in)) ! Percent confidence
922 IF ( Values(IE+24) < 0.0 .OR. &
923 Values(IE+24) > 100.0 ) &
924 Values(IE+24) = MISSING
925
926 IE = IE + 23
927 END DO
928 IE = IE + 1
929
930!-------------------------------------------------------------
931! 5. Level 2a data (derived refractivity profile)
932!-------------------------------------------------------------
933
934 Values(IE+1) = ROdata%Lev2a%Npoints ! Replication factor
935
936 DO in = 1, ROdata%Lev2a%Npoints
937
938 Values(IE+2) = REAL(ROdata%Lev2a%Alt_Refrac(in)) ! Height amsl (m)
939 IF ( Values(IE+2) < -1000.0 .OR. &
940 Values(IE+2) > 100000.0 ) &
941 Values(IE+2) = MISSING
942
943 Values(IE+3) = REAL(ROdata%Lev2a%Refrac(in)) ! Refrac (N-units)
944 IF ( Values(IE+3) < 0.0 .OR. &
945 Values(IE+3) > 524.0 ) &
946 Values(IE+3) = MISSING
947
948 Values(IE+4) = FOstats ! 1st order stats (rms)
949
950 Values(IE+5) = REAL(ROdata%Lev2a%Refrac_Sigma(in)) ! Refrac error (N-units)
951 IF ( Values(IE+5) < 0.0 .OR. &
952 Values(IE+5) > 16.382 ) &
953 Values(IE+5) = MISSING
954
955 Values(IE+6) = MISSING ! 1st order stats (off)
956
957 Values(IE+7) = REAL(ROdata%Lev2a%Refrac_Qual(in)) ! Percent confidence
958 IF ( Values(IE+7) < 0.0 .OR. &
959 Values(IE+7) > 100.0 ) &
960 Values(IE+7) = MISSING
961
962 IE = IE + 6
963 END DO
964 IE = IE + 1
965
966!-------------------------------------------------------------
967! 6. Level 2b data (retrieved P,T,q profile)
968!-------------------------------------------------------------
969
970 Values(IE+1) = ROdata%Lev2b%Npoints ! Replication factor
971
972 DO in = 1, ROdata%Lev2b%Npoints
973
974 Values(IE+2) = REAL(ROdata%Lev2b%Geop(in)) ! Geopot ht (gpm)
975 IF ( Values(IE+2) < -1000.0 .OR. &
976 Values(IE+2) > 100000.0 ) &
977 Values(IE+2) = MISSING
978
979 Values(IE+3) = REAL(ROdata%Lev2b%Press(in)) * 1E2 ! Pressure (Pa)
980 IF ( Values(IE+3) <= 0.0 .OR. & ! Min. 0.1hPa
981 Values(IE+3) > 150000.0 ) &
982 Values(IE+3) = MISSING
983
984 Values(IE+4) = REAL(ROdata%Lev2b%Temp(in)) ! Temperature (K)
985 IF ( Values(IE+4) < 150.0 .OR. &
986 Values(IE+4) > 350.0 ) &
987 Values(IE+4) = MISSING
988
989 Values(IE+5) = REAL(ROdata%Lev2b%SHum(in)) * 1E-3 ! Spec/humidity (Kg/Kg)
990 IF ( Values(IE+5) < 0.0 .OR. &
991 Values(IE+5) > 0.16 ) &
992 Values(IE+5) = MISSING
993
994 Values(IE+6) = FOstats ! 1st order stats (rms)
995
996 Values(IE+7) = REAL(ROdata%Lev2b%Press_Sigma(in)) * 1E2 ! Pressure error (Pa)
997 IF ( Values(IE+7) < 0.0 .OR. &
998 Values(IE+7) > 620.0 ) &
999 Values(IE+7) = MISSING
1000
1001 Values(IE+8) = REAL(ROdata%Lev2b%Temp_Sigma(in)) ! Temperature error (K)
1002 IF ( Values(IE+8) < 0.0 .OR. &
1003 Values(IE+8) > 6.2 ) &
1004 Values(IE+8) = MISSING
1005
1006 Values(IE+9) = REAL(ROdata%Lev2b%SHum_Sigma(in)) * 1E-3 ! S/Hum error (Kg/Kg)
1007 IF ( Values(IE+9) < 0.0 .OR. &
1008 Values(IE+9) > 0.0051 ) &
1009 Values(IE+9) = MISSING
1010
1011 Values(IE+10) = MISSING ! 1st order stats (off)
1012
1013 Values(IE+11) = REAL(ROdata%Lev2b%Meteo_Qual(in)) ! Percent confidence
1014 IF ( Values(IE+11) < 0.0 .OR. &
1015 Values(IE+11) > 100.0 ) &
1016 Values(IE+11) = MISSING
1017
1018 IE = IE + 10
1019 END DO
1020 IE = IE + 1
1021
1022!-------------------------------------------------------------
1023! 7. Level 2c data (retrieved surface params)
1024!-------------------------------------------------------------
1025
1026 Values(IE+1) = 0 ! Vertical sig. (surf)
1027
1028 VALUES(IE+2) = REAL(ROdata%Lev2c%Geop_Sfc) ! Geoptot.Ht. (of surf) (gpm)
1029 IF ( Values(IE+2) < -1000.0 .OR. &
1030 Values(IE+2) > 10000.0 ) &
1031 Values(IE+2) = MISSING
1032
1033 Values(IE+3) = REAL(ROdata%Lev2c%Press_Sfc) * 1E2 ! Surface pressure (Pa)
1034 IF ( Values(IE+3) < 0.0 .OR. &
1035 Values(IE+3) > 150000.0 ) &
1036 Values(IE+3) = MISSING
1037
1038 Values(IE+4) = FOstats ! 1st order stats (rms)
1039
1040 Values(IE+5) = REAL(ROdata%Lev2c%Press_Sfc_Sigma) * 1E2 ! S/press error (Pa)
1041 IF ( Values(IE+5) < 0.0 .OR. &
1042 Values(IE+5) > 620.0 ) &
1043 Values(IE+5) = MISSING
1044
1045 Values(IE+6) = MISSING ! 1st order stats (off)
1046
1047 Values(IE+7) = REAL(ROdata%Lev2c%Press_Sfc_Qual) ! Percent confidence
1048 IF ( Values(IE+7) < 0.0 .OR. &
1049 Values(IE+7) > 100.0 ) &
1050 Values(IE+7) = MISSING
1051
1052 Nvalues = IE + 7 ! Total no. of values
1053
1054END SUBROUTINE ConvertROPPtoBUFR
1055!---------------------------------------------------------------------
1056SUBROUTINE ConvertCodes ( ROdata, & ! (inout)
1057 Gclass, & ! (inout)
1058 Gcode, & ! (inout)
1059 Lcode, & ! (inout)
1060 Icode, & ! (inout)
1061 Ocode, & ! (inout)
1062 Scode, & ! (inout)
1063 Bcode, & ! (inout)
1064 ind ) ! (in)
1065
1066!****s* bufr2ropp/ConvertCodes *
1067!
1068! NAME
1069! ConvertCodes - Convert header codes between ROPP and BUFR
1070!
1071! ARGUMENTS
1072! ROdata (inout) dtyp RO data structure
1073! Gclass (inout) int GNSS code (Satellite Class)
1074! Gcode (inout) int GNSS PRN (Platform Tx ID)
1075! Lcode (inout) int LEO code (Satellite ID)
1076! Icode (inout) int Instrument code (Instrument ID)
1077! Ocode (inout) int Originating (processing) Centre code
1078! Scode (inout) int Sub-centre code
1079! Bcode (inout) int Background generating centre code
1080! ind (in) int ROPP-->BUFR if >0, else BUFR-->ROPP
1081!
1082! MODULES
1083! ropp_io - ROPP file I/O support
1084!
1085! DEPENDENCIES
1086! MetDB BUFR package - BUFR kernel routines
1087!
1088! CALLS
1089! BUFRPATH
1090!
1091! CALLED BY
1092! ConvertBUFRtoROPP
1093! ConvertROPPtoBUFR
1094!
1095! NAMELISTS
1096! roppbufrcodes.nl - in path BUFR_LIBRARY
1097!
1098! SYNOPSIS
1099! USE ropp_io_types
1100! TYPE (roprof) rodata
1101! INTEGER :: gclass,gcode,lcode,icode,ocode,scode,bcode,ind
1102! ind = 1 ! to convert ROPP-->BUFR, ind =-1 for BUFR-->ROPP
1103! CALL convertcodes(rodata,&
1104! glass,gcode,lcode,icode,ocode,scode,bcode,&
1105! ind)
1106!
1107! DESCRIPTION
1108! Converts from character-based codes (as defined for ROPP)
1109! to numeric codes suitable for BUFR encoding, if ind>0, else
1110! vice-versa.
1111! The code conversion is driven by a set of look-up tables, which
1112! are read from a NAMELIST file 'roppbufrcodes.nl' which is
1113! expected in the directory path defined by environment variable
1114! BUFR_LIBRARY. If this file cannot be opened, a warning is issued
1115! and an in-built default set of tables is used instead.
1116!
1117! AUTHOR
1118! Met Office, Exeter, UK.
1119! Any comments on this software should be given via the GRAS SAF
1120! Helpdesk at http://www.grassaf.org
1121!
1122! COPYRIGHT
1123! (c) EUMETSAT. All rights reserved.
1124! For further details please refer to the file COPYRIGHT
1125! which you should have received as part of this distribution.
1126!
1127!****
1128
1129! Modules
1130
1131 USE ropp_io_types
1132
1133 IMPLICIT NONE
1134
1135! Fixed values
1136
1137 INTEGER, PARAMETER :: MISSING = -9999999 ! Missing data flag value
1138
1139! NB: no. of elements given in NAMELIST file parameters must not
1140! exceed these values - increase values below if necessary.
1141
1142 INTEGER, PARAMETER :: ntx = 5 ! Max. no. of GNSS Tx types
1143 INTEGER, PARAMETER :: nrx = 20 ! Max. no. of LEO Rx types
1144 INTEGER, PARAMETER :: noc = 10 ! Max. no. of orig. centre types
1145 INTEGER, PARAMETER :: nbg = 10 ! Max. no. of b/g centre types
1146
1147 CHARACTER (LEN=*), PARAMETER :: NLdsn = "roppbufrcodes.nl" ! NAMELIST filel name
1148 INTEGER, PARAMETER :: NLunit = 1 ! NAMELIST file unit no.
1149
1150! Argument list parameters
1151
1152 TYPE ( ROprof ), INTENT(INOUT) :: Rodata ! ROPP data structure
1153 INTEGER, INTENT(INOUT) :: Gclass ! GNSS class value
1154 INTEGER, INTENT(INOUT) :: Gcode ! GNSS PRN
1155 INTEGER, INTENT(INOUT) :: Lcode ! LEO code value
1156 INTEGER, INTENT(INOUT) :: Icode ! Instrument code value
1157 INTEGER, INTENT(INOUT) :: Ocode ! Origin. centre code value
1158 INTEGER, INTENT(INOUT) :: Scode ! Sub-centre code value
1159 INTEGER, INTENT(INOUT) :: Bcode ! B/G generator code value
1160 INTEGER, INTENT(IN) :: ind ! RO->code if >1 else code->RO
1161
1162! Define arrays for chararacter (ROPP) & numeric (BUFR code) lists.
1163! Set some defaults in case the NAMELISTs can't be read. NAMELIST
1164! values will overwrite these defaults. Include some dummy spares so
1165! that extra ones can be defined in the NAMELIST _without_ having to
1166! change the array sizes (up to the max. values) and rebuilding
1167! the program.
1168
1169 CHARACTER (LEN=1), DIMENSION(ntx) :: GNSlist = &
1170 (/ "U", "G", "R", "E", "U" /)
1171 INTEGER, DIMENSION(ntx) :: GNScode = &
1172 (/ MISSING, 401, 402, 403, MISSING /)
1173
1174 CHARACTER (LEN=4), DIMENSION(nrx) :: LEOlist = &
1175 (/ "UNKN", "OERS", "CHMP", &
1176 "SUNS", "SACC", &
1177 "GRAA", "GRAB", &
1178 "CO01", "CO02", "CO03", &
1179 "CO04", "CO05", "CO06", &
1180 "META", "METB", "METC", &
1181 "TSRX", &
1182 "UNKN", "UNKN", "UNKN" /)
1183 INTEGER, DIMENSION(nrx) :: LEOcode = &
1184 (/ MISSING, 040, 041, &
1185 800, 820, &
1186 722, 723, &
1187 740, 741, 742, &
1188 743, 744, 745, &
1189 004, 003, 005, &
1190 042, &
1191 MISSING, MISSING, MISSING /)
1192 INTEGER, DIMENSION(nrx) :: Inscode = &
1193 (/ MISSING, 102, 102, &
1194 102, 102, &
1195 102, 102, &
1196 102, 102, 102, &
1197 102, 102, 102, &
1198 202, 202, 202, &
1199 103, &
1200 MISSING, MISSING, MISSING /)
1201
1202! List of (BUFR) Originating Centre IDs & their BUFR codes
1203! (Code Table 001033, CCT C-1, or 001035, CCT C-11)
1204! The (Processing) Sub-centre code should be valid for the
1205! associated Originating Centre code (for which Sub-Centre is 0).
1206! (Code Table 001034, CCT C-12)
1207!
1208 CHARACTER (LEN=8), DIMENSION(noc) :: ORGlist = &
1209 (/ "UNKNOWN ", "DMI ", "GFZ ", &
1210 "METO ", "UCAR ", &
1211 "NESDIS ", "EUMETSAT", &
1212 "UNKNOWN ", "UNKNOWN ", "UNKNOWN " /)
1213 INTEGER, DIMENSION(noc) :: ORGcode = &
1214 (/ MISSING, 094, 078, &
1215 074, 060, &
1216 160, 254, &
1217 MISSING, MISSING, MISSING /)
1218 INTEGER, DIMENSION(noc) :: Subcode = &
1219 (/ 000, 000, 173, &
1220 000, 000, &
1221 000, 000, &
1222 000, 000, 000 /)
1223 CHARACTER (LEN=35), DIMENSION(noc) :: ORGname = &
1224 (/ " ", &
1225 "(GRAS SAF) ", &
1226 "GeoForschungsZentrum Potsdam ", &
1227 "Met Office Exeter ", &
1228 "Boulder ", &
1229 "Washington ", &
1230 "Darmstatdt ", &
1231 " ", &
1232 " ", &
1233 " " /)
1234
1235 CHARACTER (LEN=20), DIMENSION(nbg) :: BGDlist = &
1236 (/ "UNKNOWN", "ECMWF ", "DMI ", &
1237 "METO ", "NCEP ", &
1238 "NONE ", &
1239 "UNKNOWN", "UNKNOWN", "UNKNOWN", "UNKNOWN" /)
1240 INTEGER, DIMENSION(nbg) :: BGDcode = &
1241 (/ MISSING, 98, 94, 74, 7, &
1242 MISSING, MISSING, MISSING, MISSING, MISSING /)
1243
1244! Local variables
1245
1246 CHARACTER (LEN=235) :: dir = " " ! Translated BUFR directory (path)
1247 CHARACTER (LEN=255) :: FileSpec ! Full sequence file name
1248 INTEGER :: i, j ! loop counter/indices
1249 INTEGER :: ierr ! I/O error
1250
1251! Namelist parameters
1252
1253 NAMELIST /GNScodes/ GNSlist, GNScode
1254 NAMELIST /LEOcodes/ LEOlist, LEOcode, Inscode
1255 NAMELIST /ORGcodes/ ORGlist, ORGcode, Subcode
1256 NAMELIST /BGDcodes/ BGDlist, BGDcode
1257
1258!---------------------------------------------------
1259! 1. Open codes NAMELIST file & read lists
1260!---------------------------------------------------
1261
1262 CALL BUFRPATH ( dir, ierr )
1263 FileSpec = ADJUSTL(TRIM(dir)//NLdsn)
1264 OPEN ( UNIT=NLunit, FILE=FileSpec, ACTION="READ", IOSTAT=ierr )
1265 IF ( ierr == 0 ) THEN
1266 READ ( UNIT=NLunit, NML=GNScodes, IOSTAT=ierr )
1267 READ ( UNIT=NLunit, NML=LEOcodes, IOSTAT=ierr )
1268 READ ( UNIT=NLunit, NML=ORGcodes, IOSTAT=ierr )
1269 CLOSE ( UNIT=NLunit )
1270 ELSE
1271 WRITE ( *, FMT="(A)" )
1272 WRITE ( *, FMT="(A)" ) "WARNING: ROPP-BUFR codes NAMELIST file"// &
1273 " could not be opened."
1274 WRITE ( *, FMT="(A)" ) " ("//TRIM(FileSpec)//")"
1275 WRITE ( *, FMT="(A)" ) " Using default look-up tables."
1276 WRITE ( *, FMT="(A)" )
1277 END IF
1278
1279!---------------------------------------------------
1280! 2. Look up numeric (BUFR) code from character (ROPP)
1281!---------------------------------------------------
1282
1283 IF ( ind >= 1 ) THEN
1284
1285! Defaults
1286
1287 Lcode = MISSING
1288 Icode = MISSING
1289 Gclass = MISSING
1290 Gcode = MISSING
1291 Ocode = MISSING
1292 Scode = MISSING
1293 Bcode = MISSING
1294
1295! LEO Rx ID code (satellite & hence instrument)
1296
1297 i = nrx
1298 DO WHILE ( i > 0 .AND. &
1299 LEOlist(i) /= ROdata%LEO_id )
1300 i = i - 1
1301 END DO
1302 IF ( i > 0 ) THEN
1303 Lcode = LEOcode(i)
1304 Icode = Inscode(i)
1305 END IF
1306
1307! GNSS Tx ID code (satellite class) & separate PRN
1308
1309 i = ntx
1310 DO WHILE ( i > 0 .AND. &
1311 GNSlist(i) /= ROdata%GNS_id(1:1) )
1312 i = i - 1
1313 END DO
1314 IF ( i > 0 ) Gclass = GNScode(i)
1315 READ ( ROdata%GNS_id(2:4), FMT=*, IOSTAT=ierr ) Gcode
1316 IF ( ierr /= 0 .OR. &
1317 Gcode < 0 .OR. &
1318 Gcode > 32 ) Gcode = MISSING
1319
1320! Originating (processing) centre code
1321! and associated sub-centre code
1322
1323 i = noc
1324 DO WHILE ( i > 0 .AND. &
1325 ORGlist(i)(1:3) /= ROdata%Processing_Centre(1:3) )
1326 i = i - 1
1327 END DO
1328 Ocode = ORGcode(i)
1329 Scode = SUBcode(i)
1330
1331! Look up background generator centre code
1332
1333 i = nbg
1334 DO WHILE ( i > 0 .AND. &
1335 BGDlist(i)(1:3) /= ROdata%BG%Source(1:3) )
1336 i = i - 1
1337 END DO
1338 Bcode = BGDcode(i)
1339
1340!---------------------------------------------------
1341! 3. Look up character (ROPP) code from numeric (BUFR)
1342!---------------------------------------------------
1343
1344 ELSE
1345
1346! Defaults
1347
1348 ROdata%LEO_id = "UNKN"
1349 ROdata%GNS_id = "U999"
1350 ROdata%Processing_Centre = "UNKNOWN"
1351 ROdata%bg%Source = "UNKNOWN"
1352
1353! LEO Rx ID code (Satellite)
1354
1355 i = nrx
1356 DO WHILE ( i > 0 .AND. &
1357 Lcode /= LEOcode(i) )
1358 i = i - 1
1359 END DO
1360 IF ( i > 0 ) ROdata%LEO_id = LEOlist(i)
1361
1362! GNSS Tx ID code (from satellite class) & add PRN
1363
1364 i = ntx
1365 DO WHILE ( i > 0 .AND. &
1366 Gclass /= GNScode(i) )
1367 i = i - 1
1368 END DO
1369 IF ( i > 0 ) ROdata%GNS_id(1:1) = GNSlist(i)
1370 IF ( Gcode < 0 .OR. Gcode > 999 ) Gcode = 999
1371 WRITE ( ROdata%GNS_id(2:4), &
1372 FMT="(I3.3)", &
1373 IOSTAT=ierr ) Gcode
1374
1375! Originating (RO processing) centre code
1376
1377 i = noc
1378 DO WHILE ( i > 0 .AND. &
1379 Ocode /= ORGcode(i) )
1380 i = i - 1
1381 END DO
1382 IF ( i > 0 ) THEN
1383 j = MAX ( LEN_TRIM ( ORGlist(i) ), 4 )
1384 ROdata%Processing_Centre = ORGlist(i)(1:j) &
1385 // " " // ORGname(i)
1386 END IF
1387
1388! Background generating centre code
1389
1390 i = nbg
1391 DO WHILE ( i > 0 .AND. &
1392 Bcode /= BGDcode(i) )
1393 i = i - 1
1394 END DO
1395 IF ( i > 0 ) ROdata%bg%Source = BGDlist(i)
1396
1397 ENDIF
1398
1399END SUBROUTINE ConvertCodes
1400!----------------------------------------------------------------------------
1401SUBROUTINE EncodeBUFR ( BUFRdsn, & ! (in)
1402 BulSeqNo, & ! (in)
1403 OrigICAO, & ! (in)
1404 OrigCentre, & ! (in)
1405 SubCentre, & ! (in)
1406 descr, & ! (inout)
1407 ndescr, & ! (inout)
1408 Values, & ! (in)
1409 Names, & ! (in)
1410 nobs, & ! (in)
1411 GTShdrType, & ! (in)
1412 ierr ) ! (out)
1413!
1414!****s* ropp2bufr/EncodeBUFR *
1415!
1416! NAME
1417! EncodeBUFR - Encode converted RO data to BUFR message & write it out
1418!
1419! ARGUMENTS
1420! BUFRdsn (in) chr Output BUFR file name
1421! BulSeqNo (in) int Bulletin sequence number (001-999)
1422! OrigICAO (in) chr 4-chr ICAO designator for originator centre
1423! OrigCentre (in) int Originator centre BUFR common code value
1424! SubCentre (in) int Processing centre code value
1425! descr (inout) int On entry: array of descriptors for type
1426! On exit : array of expanded descriptors
1427! ndescr (inout) int On entry: no. of initial descriptors in descr
1428! On exit : no. of expanded descriptors in descr
1429! Values (in) flt Array(ne) of converted values for BUFR encoder
1430! Names (in) chr List of character-based names
1431! nobs (in) int No. of observations
1432! GTShdrType (in) int GTS header type indicator
1433! ierr (out) int Exit code
1434!
1435! DEPENDENCIES:
1436! MetDB BUFR package - BUFR kernel routines
1437! gtshdrs - routines to add WMO/GTS routing header/trailer
1438!
1439! CALLS
1440! ENBUFV2
1441! GTSHDR
1442! GTSEND
1443! METDB_CWRITE
1444!
1445! CALLED BY
1446! ropp2bufr
1447!
1448! SYNOPSIS
1449! USE ropp2bufrmod
1450! INTEGER :: bulseqno, origcentre, subcentre
1451! INTEGER :: nobs, ndescr, gtshdrtype, ierr
1452! INTEGER :: descr(nd)
1453! REAL :: values(ne,no)
1454! CHARACTER (LEN=4) :: origicao
1455! CHARACTER (LEN=no*4) :: names
1456! CALL EncodeBUFR ( BUFRdsn, bulseqno, &
1457! origicao, origcentre, subcentre, &
1458! descr, ndescr, &
1459! values, names, nobs, gtshdrtype, ierr )
1460!
1461! DESCRIPTION
1462! Encodes data in array "values" (pre-converted to BUFR
1463! standard) containing "nobs" observations, to a BUFR message,
1464! using the given descriptor sequence in "desc" (of length
1465! "ndescr"). On exit, descr will contain an updated ndesc
1466! expanded descriptor list, so this array should be sized to
1467! the maximum expected expansion.
1468! The data is encoded and shipped out to the file
1469! specified in "BUFRdsn", which is automatically opened on
1470! on the first call. The status of the encoding and file
1471! output is indicated in "ierr" on return.
1472! If any errors in the encoding process occur, a plain
1473! text message is written to (stdout).
1474! An optional GTS routing header is pre-pended (and trailer
1475! bytes appended) if GTShdrType=1. Futher, 4 leading null bytes are
1476! included if GTShdrType=2 for compatibility with X.25 GTS
1477! transmission software, or 8-byte length + 2-byte type are
1478! included if GTShdrType=3, for compatability with GTS transmission
1479! via IP (ftp). No headers are generated at all if GTShdrType is not
1480! 1, 2 or 3.
1481!
1482! AUTHOR
1483! Met Office, Exeter, UK.
1484! Any comments on this software should be given via the GRAS SAF
1485! Helpdesk at http://www.grassaf.org
1486!
1487! COPYRIGHT
1488! (c) EUMETSAT. All rights reserved.
1489! For further details please refer to the file COPYRIGHT
1490! which you should have received as part of this distribution.
1491!
1492!****
1493
1494 IMPLICIT NONE
1495
1496! Fixed values
1497
1498 INTEGER, PARAMETER :: ErrUnit = 6 ! Output stream for error messages
1499
1500! Argument list parameters
1501
1502 CHARACTER (LEN=*), INTENT(IN) :: BUFRdsn ! output BUFR file name
1503 INTEGER, INTENT(IN) :: BulSeqNo ! Bulletin sequence number
1504 CHARACTER (LEN=*), INTENT(IN) :: OrigICAO ! originating centre ICAO code
1505 INTEGER, INTENT(IN) :: OrigCentre ! originating centre code value
1506 INTEGER, INTENT(IN) :: SubCentre ! processing centre code value
1507 INTEGER, INTENT(INOUT) :: descr(:) ! descriptor sequence
1508 INTEGER, INTENT(INOUT) :: ndescr ! no. of descriptors in seq.
1509 REAL, INTENT(IN) :: Values(:) ! data to encode
1510 CHARACTER (LEN=*), INTENT(IN) :: Names ! characters to encode
1511 INTEGER, INTENT(IN) :: nobs ! no. of observations
1512 INTEGER, INTENT(IN) :: GTShdrType ! Code for GTS header generation
1513 INTEGER, INTENT(OUT) :: ierr ! error status:
1514 ! 0 = OK
1515 ! 1 = BUFR encode error
1516 ! 2 = File write error
1517
1518! Local variables
1519
1520 CHARACTER (LEN=50000) :: Message ! BUFR message
1521 INTEGER :: Edition = 3 ! BUFR Edition (3)
1522 INTEGER :: MasterTable = -99 ! Master BUFR Tables (default)
1523 INTEGER :: OCentre ! Coded originating centre and sub-centre
1524 INTEGER :: DataType = 3 ! Data type from Table A (Sounding - satellite)
1525 INTEGER :: DataSubType = 255 ! Data sub-type (dummy)
1526 INTEGER :: VerMasTable = 12 ! Table version number (12)
1527 INTEGER :: VerLocTable = -99 ! Local Table version (default)
1528 INTEGER :: Sect3Type = 1 ! Observed data
1529 INTEGER :: DateTime(5) ! Date & Time of data (yr,mth,day,hr,min)
1530 INTEGER :: lat, lon ! Nominal mean ob. location
1531 INTEGER :: lenh, lenm ! Length of GTS header & BUFR message
1532 INTEGER :: nelem ! No. of elements
1533 INTEGER :: i ! Loop counter
1534 LOGICAL :: compress = .FALSE. ! Compression flag
1535
1536 LOGICAL :: ExtraSect1 = .FALSE. ! Nothing extra
1537 CHARACTER :: CharSect1 = " "
1538
1539 LOGICAL :: ExtraSect2 = .FALSE. ! Nothing extra
1540 CHARACTER :: CharSect2 = " "
1541
1542!-------------------------------------------------------------
1543! 1. Initialise
1544!-------------------------------------------------------------
1545
1546 nelem = SIZE ( Values )
1547 ierr = 0
1548
1549!-------------------------------------------------------------
1550! 2. Code processing centre as sub-centre of originating
1551! centre if valid
1552!-------------------------------------------------------------
1553
1554 OCentre = OrigCentre
1555 IF ( SubCentre > 0 .AND. &
1556 SubCentre <= 254 ) &
1557 OCentre = OCentre + SubCentre * 256
1558
1559!-------------------------------------------------------------
1560! 3. Extract first (or only) observation time for BUFR header
1561! and nominal lat/long for Area (A2) code in GTS header
1562!-------------------------------------------------------------
1563
1564 DateTime(1:5) = NINT(Values(7:11))
1565
1566 lat = NINT(Values(30))
1567 lon = NINT(Values(31))
1568 lon = MOD(lon+360,360) ! limit range to 0-359deg
1569
1570!-------------------------------------------------------------
1571! 4. Generate WMO bulletin GTS routing header if required
1572!-------------------------------------------------------------
1573
1574 Message = " "
1575 lenh = 0
1576 CALL GTSHDR ( GTShdrType, &
1577 BulSeqNo, &
1578 tta, &
1579 lat, lon, &
1580 ii, &
1581 OrigICAO, &
1582 DateTime, &
1583 Message, &
1584 lenh )
1585
1586!-------------------------------------------------------------
1587! 4. Do the encode
1588!-------------------------------------------------------------
1589
1590 CALL ENBUFV2 ( descr, Values, &
1591 ndescr, nelem, nobs, &
1592 Names, DateTime, &
1593 Message(lenh+1:), &
1594 compress, &
1595 lenm, &
1596 Edition, MasterTable, &
1597 OCentre, &
1598 DataType, DataSubType, &
1599 VerMasTable, VerLocTable, &
1600 ExtraSect1, CharSect1, &
1601 ExtraSect2, CharSect2, &
1602 Sect3Type )
1603
1604! ENBUFV2 ought to return ndescr as the no. of expanded descriptors,
1605! but it doesn't - the returned value is the number of data elements
1606! which we already know (nelem). So we scan the descr array to find
1607! the last valid descriptor.
1608
1609 ndescr = SIZE(descr)
1610 DO
1611 IF ( ndescr == 0 ) EXIT
1612 IF ( descr(ndescr) > 0 ) EXIT
1613 ndescr = ndescr - 1
1614 END DO
1615 IF ( DEBUG ) THEN
1616 WRITE ( *, FMT="(A)" ) "Encoding results:"
1617 WRITE ( *, FMT="(A,I7)" ) " No. of expanded BUFR descr. :", ndescr
1618 WRITE ( *, FMT="(A,I7)" ) " Length of BUFR message :", lenm
1619 END IF
1620
1621!-------------------------------------------------------------
1622! 5. If ok, add optional ending to message (and if IP leader,
1623! insert length of message from SOH to ETX in first 8
1624! bytes) & ship it out
1625!-------------------------------------------------------------
1626
1627 IF ( lenm > 3 .AND. &
1628 Message(lenm+lenh-3:lenm+lenh) == "7777" ) THEN
1629 lenm = lenh + lenm + 1
1630 CALL GTSEND ( GTShdrType, &
1631 Message, &
1632 lenm )
1633
1634 IF ( DEBUG .AND. &
1635 GTSHdrType /= NOhdrs ) THEN
1636 WRITE ( *, "(A)", ADVANCE="NO" ) " GTS bulletin header / ARH : "
1637 DO i = 1, lenh-3
1638 IF ( LGE(Message(i:i)," ") ) THEN
1639 WRITE ( *, "(A)", ADVANCE="NO" ) Message(i:i)
1640 ELSE
1641 WRITE ( *, "(A)", ADVANCE="NO" ) "."
1642 END IF
1643 END DO
1644 WRITE ( *, "(A)" )
1645 END IF
1646
1647 WRITE ( *, FMT="(A,I6,A)", ADVANCE="NO" ) "Writing", lenm, " bytes "
1648 IF ( GTSHdrType /= NOhdrs ) &
1649 WRITE ( *, FMT="(A)", ADVANCE="NO" ) "(GTS bulletin) "
1650 WRITE ( *, FMT="(A)" ) "to "//TRIM(BUFRdsn)//"..."
1651 CALL METDB_CWRITE ( BUFRunit, &
1652 Message(1:lenm), &
1653 lenm )
1654 IF ( lenm == 0 ) ierr = 2
1655
1656 IF ( ierr /= 0 ) &
1657 WRITE ( *, FMT="(A)" ) "ERROR: writing to BUFR file "// &
1658 TRIM(BUFRdsn)
1659 ELSE
1660 WRITE ( *, FMT="(A)" ) "ERROR: generating BUFR message"
1661 ierr = 1
1662 lenm = 0
1663 END IF
1664
1665END SUBROUTINE EncodeBUFR
1666!--------------------------------------------------------------------
1667END MODULE ropp2bufrmod
1668!--------------------------------------------------------------------
1669PROGRAM ropp2bufr
1670
1671!****x* ropp2bufr/ropp2bufr *
1672!
1673! NAME
1674! ropp2bufr - Encode a ROPP file to WMO FM-94 (BUFR)
1675!
1676! CALLS
1677! IARGC
1678! BulSeqIO
1679! ConvertROPPtoBUFR
1680! EncodeBUFR
1681! GetOptions
1682! ropp_io_ascend
1683! ropp_io_occid
1684! ropp_io_read
1685! ropp_io_thin
1686! ropp_io_free
1687! IDES
1688! METDB_COPEN
1689! METDB_CWRITE
1690! METDB_CCLOSE
1691! GTSEND
1692! DateTimeNow
1693! DateTimeOffset
1694! JulianDay
1695! To_Lower
1696! FileDelete
1697!
1698! MODULES
1699! ropp2bufrmod - fixed parameter definitions
1700! ropp_io - ROPP I/O file support
1701! ropp_io_types - ROPP data type definitions
1702! DateTimeProgs - Date & Time conversion routines
1703! DateTimeTypes - Date & Time conversion definitions
1704!
1705! INCLUDES
1706! portability.fi - system dependent settings (from BUFR package)
1707! to support EXIT()
1708!
1709! DEPENDENCIES
1710! MetDB BUFR package - BUFR kernel routines
1711! ROPP I/O library - ROPP file I/O support
1712! ROPP Tools library - ROPP utility routines
1713! netCDF library - netCDF file support
1714! udunits library - Units conversion routines
1715!
1716! ENVIRONMENT VARIABLES
1717! BUFR_LIBRARY - path for run-time files
1718!
1719! COMPLETION CODES
1720! 0 = OK
1721! -1 = Occultation rejected as too old for GTS
1722! 1 = I/O error
1723! 2 = Memory allocation failure
1724!
1725! SYNOPSIS
1726! > export BUFR_LIBRARY=bufr_directory_path
1727! > ropp2bufr ropp_file [ropp_file...] [-o bufr_file]
1728! [-c orig_code] [-g[n]] [-s seq_file]
1729! [-p thin_file] [-t time]
1730! [-u] [-l] [m] [-h|?] [-v] [-d]
1731! INPUTS
1732! ropp_file is the input file(s). This file must be in ROPP V1.0
1733! (TEXT or netCDF) or CLIMAP V2.2 (TEXT) RO format
1734! (See Refs.1,2)
1735! OUTPUT
1736! bufr_file is the output file, which will contain one encoded
1737! BUFR message (See Ref.3)
1738! The output file name is optional, and if not specified,
1739! is generated from the occulation ID.
1740!
1741! OPTIONS
1742! Option switches can be in any order and are case-insensitive;
1743! any space(s) between a switch and its (madatory) argument is
1744! optional.
1745! -o specifies the BUFR output file name
1746! -c specifies the originating centre code value
1747! -g specifies that GTS routing headers/trailers are required
1748! -gx speciifes that GTS headers include 4 leading null bytes
1749! (required for some X.25 implimentations for GTS)
1750! -gi speciifes that GTS headers include 10-byte leading size/type
1751! (required for some IP (FTP) implimentations for GTS)
1752! -s specifies a bulletin sequence number file
1753! -p specifies a thinning control file or max. no. of levels
1754! -t specifies a time (age) rejection threshold
1755! -u leave profiles unordered - disables the default re-ordering
1756! of output profiles to ascending.
1757! NB: using -u, profiles thinned using one of the interpolation methods
1758! will retain the order of the fixed levels in the control file; other
1759! methods will retain the ordering of the input profiles.
1760! -l to skip encoding L1+L2 data (bending angle, Level 1b), if present
1761! -m to skip encoding met. data (geophysical, Level 2b,c), if present
1762! -d to output additional diagnostics
1763! -h or ? to output summary help
1764! -v to output program version ID
1765!
1766! DEFAULTS
1767! Input file name : ropp.nc (netDCF)
1768! Output file name : <occid>.bufr
1769! Originating centre code : 74 (Bracknell)
1770! GTS routing headers : not generated
1771! Bulletin sequence : initialised at 001
1772! Time threshold : 00:00 (no cut-off) unless one of
1773! -g options present, when 23:50
1774! Encode : all available Level 1b, 2b & 2c data
1775! Thinning : none
1776!
1777! DESCRIPTION
1778! A BUFR encoder for Radio Occultation data.
1779! Reads from a ROPP v1.0 (TEXT or netCDF) or CLIMAP V2.2 (TEXT)
1780! formatted file and encodes data therein to one BUFR message.
1781! Various options are provided to control the generation of
1782! routing headers and rejection based on the age of the data
1783! and to skip encoding certain profile subsets.
1784! BUFR tables and other run-time files are found via the environment
1785! variable 'BUFR_LIBRARY'.
1786!
1787! REFERENCES
1788! 1) Format Definition for Radio Occultation Files -
1789! CLIMAP Format Version 2.2a
1790! 2) ROPP interface file format
1791! SAF/GRAS/METO/FMT/ROPP/001
1792! 3) WMO FM94 (BUFR) Specification for GRAS SAF Processed Radio
1793! Occultation Data.
1794! SAF/GRAS/METO/FMT/BUFR/001
1795! 4) Monodimensional data thinning for GPS radio occultations
1796! SAF/GRAS/METO/ALG/ROPP/001
1797!
1798! SEE ALSO
1799! ropp2bufr(1), bufr2ropp(1), decbufr(1)
1800!
1801! AUTHOR
1802! Met Office, Exeter, UK.
1803! Any comments on this software should be given via the GRAS SAF
1804! Helpdesk at http://www.grassaf.org
1805!
1806! COPYRIGHT
1807! (c) EUMETSAT. All rights reserved.
1808! For further details please refer to the file COPYRIGHT
1809! which you should have received as part of this distribution.
1810!
1811!****
1812
1813! Modules
1814
1815 USE ROPP2BUFRmod
1816 USE ropp_io_types, ONLY: ROprof
1817 USE ropp_io, ONLY: ropp_io_nrec, &
1818 ropp_io_occid, &
1819 ropp_io_read, &
1820 ropp_io_thin, &
1821 ropp_io_free
1822 USE DateTimeProgs, ONLY: DateTimeNow, &
1823 DateTimeOffset
1824 USE DateTimeTypes, ONLY: DTtype, &
1825 DateFmt, &
1826 TimeFmt, &
1827 MonthName, &
1828 IdxMinute, &
1829 NHourPerDay, &
1830 NMinPerHour, &
1831 JD2000
1832 USE ropp_utils, ONLY: File_Delete
1833
1834! Include files
1835
1836 INCLUDE "portability.fi"
1837
1838! Fixed values
1839
1840 CHARACTER (LEN=*), PARAMETER :: seqtype = "GPSRO" ! GPS RO sub-sequence ID
1841 CHARACTER (LEN=*), PARAMETER :: Fmt1 = &
1842 "(A,I2.2,':',I2.2,'UT ',I2.2,'-',A3,'-',I4)"
1843 CHARACTER (LEN=3), PARAMETER :: Month(0:12) = &
1844 (/ "???", "Jan", "Feb", "Mar", "Apr", "May", "Jun", &
1845 "Jul", "Aug", "Sep", "Oct", "Nov", "Dec" /)
1846! Local variables
1847
1848 CHARACTER (LEN=10) :: LastMsg ! Last 'message' for IP
1849
1850 CHARACTER (LEN=256), &
1851 DIMENSION(:), &
1852 ALLOCATABLE :: ROPPdsn ! Name(s) of input ROPP file(s)
1853 CHARACTER (LEN=256) :: BUFRdsn ! Output (BUFR) file name
1854 CHARACTER (LEN=256) :: BulSeqdsn ! bulletin sequence file name
1855 CHARACTER (LEN=256) :: Thindsn ! thinning control file name
1856 CHARACTER (LEN=4) :: OrigICAO ! Originating centre ICAO code
1857 INTEGER :: nfiles ! No. of file names on command line
1858 INTEGER :: OrigCentre ! Originating centre BUFR code
1859 INTEGER :: GTShdrType ! Code for GTS header generation
1860 INTEGER :: RejTimeDiff ! reject obs older than this
1861 LOGICAL :: CorrOnly ! Flag for Corrected only
1862 LOGICAL :: nomet ! Flag for no met. data
1863
1864 CHARACTER (LEN=100) :: Names = " " ! Names list (not used)
1865
1866 REAL, ALLOCATABLE :: Values(:) ! Data for BUFR
1867 INTEGER, ALLOCATABLE :: Descr(:) ! Descriptor sequence
1868
1869 INTEGER :: ndescr ! Number of descriptors in sequence
1870 INTEGER :: nelem ! No. of elements
1871 INTEGER :: nvalues ! No. of elements after thinning
1872 INTEGER :: minextra = 2000 ! Min. expansion elements for Decsr
1873 INTEGER :: nextra ! Extra expansion elements for Descr
1874 INTEGER :: nobs = 1 ! No. of observations
1875 INTEGER :: BulSeqNo = 0 ! Bulletin Sequence No.
1876 INTEGER :: SubCentre ! Processing centre ID as code value
1877 INTEGER :: ierr, status ! File error & return status codes
1878 INTEGER :: nmsg = 0 ! Count of BUFR messages
1879 INTEGER :: LenMSG ! Length of BUFR messages
1880 INTEGER :: nfreq = 0 ! No. of Level 1b frequencies
1881 INTEGER :: nvalid = 0 ! No. of valid L1 b/angles
1882 INTEGER :: JulDay ! Date as Julian Day no.
1883 INTEGER :: in, iprof, ifile ! Loop counters
1884 LOGICAL :: exists ! File present flag
1885 LOGICAL :: first = .TRUE. ! First profile flag
1886 LOGICAL :: unordered ! Enable ordering of profiles to ascending
1887
1888 INTEGER :: IDES ! convert descriptor function
1889
1890 TYPE(ROprof) :: ROdata ! ROPP data structure
1891 INTEGER :: nprofs ! No. of profiles in i/p file
1892 INTEGER :: tprofs = 0 ! Total profiles in all files
1893
1894 TYPE (DTtype) :: DateTime ! Date & Time structure
1895 CHARACTER (LEN=11) :: DateStr ! Date string for run time
1896 CHARACTER (LEN=15) :: TimeStr ! Time string for run time
1897 CHARACTER (LEN=10) :: NumStr ! Number string
1898 INTEGER :: MinRej ! Rejection threshold (minutes since 00:00UT 1-Jan-2000)
1899 INTEGER :: MinObs ! Ob time (minutes since 00:00UT 1-Jan-2000)
1900
1901!--------------------------------------------------------------
1902! 1. Begin
1903!--------------------------------------------------------------
1904
1905 CALL DateTimeNow ( "UT", DateTime )
1906 WRITE ( TimeStr, FMT=TimeFmt ) DateTime%Hour, &
1907 DateTime%Minute
1908 WRITE ( DateStr, FMT=DateFmt ) DateTime%Day, &
1909 DateTime%MonthName(1:3), &
1910 DateTime%Year
1911 WRITE ( *, FMT="(/A/A/)" ) REPEAT(" ",13)// &
1912 "===== ROPP BUFR Encoder =====", &
1913 REPEAT(" ",19)//TimeStr(1:5)//" "//ADJUSTL(DateStr)
1914
1915!--------------------------------------------------------------
1916! 2. Get file names & options from command line
1917!--------------------------------------------------------------
1918
1919 nfiles = MAX ( IARGC(), 1 )
1920 ALLOCATE ( ROPPdsn(nfiles) )
1921 CALL GetOptions ( ROPPdsn, &
1922 nfiles, &
1923 BUFRdsn, &
1924 BulSeqdsn, &
1925 Thindsn, &
1926 OrigICAO, &
1927 OrigCentre, &
1928 GTShdrType, &
1929 RejTimeDiff, &
1930 CorrOnly, &
1931 nomet, &
1932 unordered )
1933
1934!--------------------------------------------------------------
1935! 3. If time rejection on, set time rejection threshold in
1936! minutes since 00:00UT 1-Jan-2000 for specified period
1937! back from 'now' (NB Julian Day element of DateTime
1938! increments at midday, not, midnight, so we need to
1939! compensate)
1940!--------------------------------------------------------------
1941
1942 IF ( RejTimeDiff > 0 ) THEN
1943 CALL DateTimeOffset ( DateTime, -RejTimeDiff, IdxMinute )
1944 IF ( DateTime%Hour >= 12 ) DateTime%JulDay = DateTime%JulDay - 1
1945 MinRej = ( ( DateTime%JulDay - JD2000 ) * nHourPerDay &
1946 + DateTime%Hour ) * nMinPerHour &
1947 + DateTime%Minute
1948 IF ( DEBUG ) THEN
1949 WRITE ( TimeStr, FMT=TimeFmt ) DateTime%Hour, &
1950 DateTime%Minute
1951 WRITE ( DateStr, FMT=DateFmt ) DateTime%Day, &
1952 DateTime%MonthName(1:3), &
1953 DateTime%Year
1954 WRITE ( *, FMT="(A)" ) "Rejecting occultations older than "// &
1955 TimeStr(1:5)//"UT "//ADJUSTL(DateStr)
1956 END IF
1957 ELSE
1958 MinRej = 0
1959 END IF
1960
1961!--------------------------------------------------------------
1962! 4. If GTS headers to be generated, read the last used
1963! bulletin sequence number
1964!--------------------------------------------------------------
1965
1966 IF ( GTShdrType /= NOhdrs ) &
1967 CALL BulSeqIO ( BulSeqdsn, &
1968 BulseqNo, &
1969 Input )
1970
1971!--------------------------------------------------------------
1972! 5. Loop over input files
1973!--------------------------------------------------------------
1974
1975 DO ifile = 1, nfiles
1976
1977 INQUIRE ( FILE=ROPPdsn(ifile), EXIST=exists )
1978 IF ( .NOT. exists ) THEN
1979 WRITE ( *, FMT="(A/)" ) "*** ROPP input file " // &
1980 TRIM(ROPPdsn(ifile)) // &
1981 " not found"
1982 CYCLE
1983 ENDIF
1984
1985 WRITE ( *, FMT="(A)" ) "Reading ROPP data from " // &
1986 TRIM(ROPPdsn(ifile))
1987
1988 nprofs = ropp_io_nrec ( ROPPdsn(ifile) )
1989 IF ( nprofs < 0 ) nprofs = 1 ! assume 1 profile for text type
1990 tprofs = tprofs + nprofs
1991
1992!--------------------------------------------------------------
1993! 6. Loop over occultations from current file
1994! (If a read error, skip to next file)
1995!--------------------------------------------------------------
1996
1997 DO iprof = 1, nprofs
1998
1999 CALL ropp_io_read ( ROdata, &
2000 file=ROPPdsn(ifile), &
2001 rec=iprof, &
2002 ierr=status )
2003
2004 IF ( status /= 0 ) THEN
2005 WRITE ( *, FMT="(A)" ) "*** Failed to read file"
2006 EXIT
2007 END IF
2008
2009!--------------------------------------------------------------
2010! 7. On first profile, open output file for BUFR (default name
2011! from first occultation ID)
2012!--------------------------------------------------------------
2013
2014 CALL ropp_io_occid ( ROdata )
2015 IF ( first ) THEN
2016 IF ( BUFRdsn == " " ) THEN
2017 BUFRdsn = TRIM(ROdata%Occ_id) // ".bufr"
2018 CALL To_Lower ( BUFRdsn )
2019 END IF
2020 CALL METDB_COPEN ( BUFRunit, &
2021 TRIM(BUFRdsn), &
2022 Output, &
2023 ierr )
2024 IF ( ierr /= 0 ) THEN
2025 WRITE ( *, FMT="(A)" ) "*** Failed to open BUFR output file "// &
2026 TRIM(BUFRdsn)
2027 CALL EXIT(ErrIO)
2028 END IF
2029 first = .FALSE.
2030 END IF
2031
2032 WRITE ( *, FMT="(A,I4)" ) "Encoding ROPP profile", iprof
2033 IF ( ROdata%DTocc%Month < 1 .OR. &
2034 ROdata%DTocc%Month > 12 ) ROdata%DTocc%Month = 0
2035 WRITE ( TimeStr, FMT=TimeFmt ) ROdata%DTocc%Hour, &
2036 ROdata%DTocc%Minute
2037 WRITE ( DateStr, FMT=DateFmt ) ROdata%DTocc%Day, &
2038 MonthName(ROdata%DTocc%Month)(1:3), &
2039 ROdata%DTocc%Year
2040 WRITE ( *, FMT="(A)" ) "Occultation Ident"//REPEAT(" ",14)// &
2041 ": "//TRIM(ROdata%Occ_ID)
2042 WRITE ( *, FMT="(A)" ) "Processing RO profile for"//REPEAT(" ",6)// &
2043 ": "//TimeStr(1:5)//"UT "//ADJUSTL(DateStr)
2044
2045!--------------------------------------------------------------
2046! 7.1 If GTS time rejection on, skip if occultation time
2047! is too old
2048!--------------------------------------------------------------
2049
2050 IF ( MinRej > 0 ) THEN
2051 CALL JulianDay ( ROdata%DTocc%Year, &
2052 ROdata%DTocc%Month, &
2053 ROdata%DTocc%Day, &
2054 JulDay, 1 )
2055 MinObs = ( ( JulDay - JD2000 ) * nHourPerDay &
2056 + ROdata%DTocc%Hour ) * nMinPerHour &
2057 + ROdata%DTocc%Minute
2058 IF ( MinObs < MinRej ) THEN
2059 WRITE ( *, FMT="(A)" ) "WARNING: Occultation is too old for GTS "// &
2060 "- not encoded."
2061 CYCLE
2062 END IF
2063 END IF
2064
2065!--------------------------------------------------------------
2066! 7.2 Use (at most) one Level 1a data for nominal POD
2067! Only encode Level 1b L1+L2 data if:
2068! a) 'Corrected only' option not taken and
2069! b) there is at least one valid L1 bending angle value present
2070!--------------------------------------------------------------
2071
2072 ROdata%Lev1a%Npoints = MIN ( 1, ROdata%Lev1a%Npoints )
2073
2074 IF ( .NOT. CorrOnly ) THEN
2075 nvalid = 0
2076 DO in = 1, ROdata%Lev1b%Npoints
2077 IF ( ROdata%Lev1b%BAngle_L1(in) > 0.0 .AND. &
2078 ROdata%Lev1b%BAngle_L1(in) < 0.082 ) THEN
2079 nvalid = nvalid + 1
2080 END IF
2081 END DO
2082 IF ( nvalid < 1 ) CorrOnly = .TRUE.
2083 END IF
2084
2085 IF ( ROdata%Lev1b%Npoints > 0 ) THEN
2086 IF ( CorrOnly ) THEN
2087 nfreq = 1
2088 ELSE
2089 nfreq = 3
2090 END IF
2091 END IF
2092
2093!--------------------------------------------------------------
2094! 7.3 Only encode 'Met' data if:
2095! a) 'No Met' option not taken and
2096! b) there is at least one valid temperature value present.
2097! Level 2c (Surface) data is always encoded, but show as '0'
2098! if not valid.
2099! Ignore any level 2d data
2100!--------------------------------------------------------------
2101
2102 nvalid = 0
2103 DO in = 1, ROdata%Lev2b%Npoints
2104 IF ( ROdata%Lev2b%Temp(in) > 150.0 .AND. &
2105 ROdata%Lev2b%Temp(in) < 350.0 ) THEN
2106 nvalid = nvalid + 1
2107 END IF
2108 END DO
2109 IF ( nvalid < 1 ) nomet = .TRUE.
2110
2111 IF ( nomet ) THEN
2112 IF ( ROdata%Lev2b%Npoints > 0 ) THEN
2113 ROdata%Lev2b%Npoints = 0
2114 ROdata%Lev2c%Npoints = 0
2115 END IF
2116 END IF
2117
2118 IF ( ROdata%Lev2c%Geop_Sfc < -1000.0 .OR. &
2119 ROdata%Lev2c%Geop_Sfc > 10000.0 ) &
2120 ROdata%Lev2c%Npoints = 0
2121
2122 ROdata%Lev2d%Npoints = 0
2123
2124! Skip this profile if no valid bending angles, refractivity,
2125! met. or surface met. present
2126
2127 IF ( ROdata%Lev1b%Npoints <= 0 .AND. &
2128 ROdata%Lev2a%Npoints <= 0 .AND. &
2129 ROdata%Lev2b%Npoints <= 0 .AND. &
2130 ROdata%Lev2c%Npoints <= 0 ) THEN
2131 WRITE ( *, FMT="(A)" ) "WARNING: No. of L1b,2a,2b,2c samples" // &
2132 " all zero - skipping this profile"
2133 CYCLE
2134 END IF
2135
2136!--------------------------------------------------------------
2137! 7.4 Thin BA, N & T,q,p profiles as required; ensure all
2138! profiles to be encoded are in ascending height order
2139!--------------------------------------------------------------
2140
2141 CALL ropp_io_thin ( ROdata, &
2142 Thindsn, &
2143 DEBUG )
2144 IF ( .NOT. unordered ) THEN
2145 IF ( DEBUG ) WRITE ( *, "(A)" ) "Ensuring all profiles are in ascending height order..."
2146 CALL ropp_io_ascend ( ROdata )
2147 END IF
2148
2149!--------------------------------------------------------------
2150! 7.5 Calculate total number of BUFR elements for this profile
2151! and allocate working array for BUFR-interface data values
2152!--------------------------------------------------------------
2153
2154! No. of BUFR elements expected
2155
2156 nelem = 37 & ! Header
2157 + 1 + ROdata%Lev1b%Npoints * ( 5 + nfreq * 6 ) & ! Level 1b
2158 + 1 + ROdata%Lev2a%Npoints * 6 & ! Level 2a
2159 + 1 + ROdata%Lev2b%Npoints * 10 & ! Level 2b
2160 + 7 ! Level 2c
2161
2162 ALLOCATE ( Values(1:nelem), STAT=status )
2163 IF ( status /= 0 ) THEN
2164 WRITE ( *, FMT="(A)" ) "ERROR: Failed to allocate memory for Values array"
2165 CALL EXIT(ErrMem)
2166 END IF
2167 Values(:) = 0.0
2168
2169!--------------------------------------------------------------
2170! 7.6 Convert RO data to BUFR array
2171!--------------------------------------------------------------
2172
2173 CALL ConvertROPPtoBUFR ( ROdata, &
2174 CorrOnly, &
2175 SubCentre, &
2176 Values, &
2177 nvalues )
2178
2179!--------------------------------------------------------------
2180! 7.7 Allocate working array for descriptors, based on thinned
2181! number of data values, and allowing headroom for expansion.
2182!--------------------------------------------------------------
2183
2184 nextra = MAX(minextra,(nvalues*5/10))
2185 ALLOCATE ( Descr(1:nvalues+nextra), STAT=status )
2186 IF ( status /= 0 ) THEN
2187 WRITE ( *, FMT="(A)" ) "ERROR: Failed to allocate memory for Descr array"
2188 CALL EXIT(ErrMem)
2189 END IF
2190 Descr(:) = 0
2191
2192 IF ( DEBUG ) THEN
2193 WRITE ( *, FMT="(A)" ) "Encoding the following data:"
2194 IF ( ROdata%GeoRef%Lon > 180.0 ) &
2195 ROdata%GeoRef%Lon = ROdata%GeoRef%Lon - 360.0
2196 WRITE ( *, FMT="(A,2F9.2)" ) " Nominal occ lat/lon location :", &
2197 ROdata%GeoRef%Lat, ROdata%GeoRef%Lon
2198 WRITE ( *, FMT="(A,I7)" ) " No. of orbit state vectors :", &
2199 ROdata%Lev1a%Npoints
2200 WRITE ( *, FMT="(A,I7)" ) " No. of bending angle samples :", &
2201 ROdata%Lev1b%Npoints
2202 IF ( ROdata%Lev1b%Npoints > 0 ) THEN
2203 WRITE ( *, FMT="(A)", ADVANCE="NO" ) &
2204 " Bending angles to encode : "
2205 IF ( CorrOnly ) THEN
2206 WRITE ( *, FMT="(A)" ) "Corrected only"
2207 ELSE
2208 WRITE ( *, FMT="(A)" ) "L1+L2+Corrected"
2209 END IF
2210 END IF
2211 WRITE ( *, FMT="(A,I7)" ) " No. of refractivity samples :", &
2212 ROdata%Lev2a%Npoints
2213 WRITE ( *, FMT="(A,I7)" ) " No. of geophysical samples :", &
2214 ROdata%Lev2b%Npoints
2215 WRITE ( *, FMT="(A,I7)" ) " No. of surface geo. samples :", &
2216 ROdata%Lev2c%Npoints
2217 WRITE ( *, FMT="(A,I7)" ) " No. of model coeff. levels :", &
2218 ROdata%Lev2d%Npoints
2219
2220 IF ( nvalues == nelem ) THEN
2221 WRITE ( *, FMT="(A,I7)" ) " Total no. of BUFR elements :", &
2222 nelem
2223 ELSE
2224 WRITE ( *, FMT="(A,I7)" ) " Thinned no. of BUFR elements :", &
2225 nvalues
2226 END IF
2227 WRITE ( *, FMT="(A,I7)") " Allocated Descriptor space :", &
2228 nvalues+nextra
2229 END IF
2230
2231!--------------------------------------------------------------
2232! 7.8 Encode this occultation & write it to output BUFR file
2233!--------------------------------------------------------------
2234
2235 Descr(1) = IDES(ROdescr)
2236 ndescr = 1
2237 BulSeqNo = MOD ( BulSeqNo, 999 ) + 1 ! increment in range 001-999
2238 CALL EncodeBUFR ( BUFRdsn, &
2239 BulSeqNo, &
2240 OrigICAO, &
2241 OrigCentre, &
2242 SubCentre, &
2243 Descr, &
2244 ndescr, &
2245 Values, &
2246 Names, &
2247 nobs, &
2248 GTShdrType, &
2249 ierr )
2250 IF ( ierr == 0 ) nmsg = nmsg + 1
2251
2252 IF ( ALLOCATED ( Values ) ) DEALLOCATE ( Values )
2253 IF ( ALLOCATED ( Descr ) ) DEALLOCATE ( Descr )
2254
2255 WRITE ( *, * )
2256 END DO ! end of profiles loop
2257
2258!--------------------------------------------------------------
2259! 7.9 Free memory ready for next file
2260!--------------------------------------------------------------
2261
2262 CALL ropp_io_free ( ROdata )
2263
2264 END DO ! end of file loop
2265
2266!--------------------------------------------------------------
2267! 8. Generate & output end-of-file dummy bulletin for IP
2268! if required.
2269! Close output file. Delete it if no messages were written
2270!--------------------------------------------------------------
2271
2272 IF ( GTShdrType == IPhdrs .AND. &
2273 nmsg > 0 ) THEN
2274 LenMsg = 0
2275 CALL GTSEND ( GTShdrType, &
2276 LastMsg, &
2277 LenMsg )
2278
2279 WRITE ( *, FMT="(A,I6,A/)" ) "Writing", LenMsg, &
2280 " bytes (for EOF) to "// &
2281 TRIM(BUFRdsn)//"..."
2282 CALL METDB_CWRITE ( BUFRunit, &
2283 LastMsg(1:LenMsg), &
2284 LenMsg )
2285 ENDIF
2286
2287 CALL METDB_CCLOSE ( BUFRunit )
2288
2289 IF ( nmsg == 0 ) THEN
2290 CALL file_delete ( BUFRdsn, ierr )
2291 END IF
2292
2293
2294!--------------------------------------------------------------
2295! 9. If GTS headers were generated, save last used bulletin
2296! sequence number
2297!--------------------------------------------------------------
2298
2299 IF ( GTShdrType /= NOhdrs ) &
2300 CALL BulSeqIO ( BulSeqdsn, &
2301 BulseqNo, &
2302 Output )
2303
2304!--------------------------------------------------------------
2305! 10. Tidy up & finish
2306!--------------------------------------------------------------
2307
2308 IF ( nmsg == 0 ) THEN
2309 WRITE ( *, FMT="(A)" ) "WARNING: No profiles were encoded "// &
2310 "or written to the BUFR file"
2311 ELSE IF ( nmsg < tprofs ) THEN
2312 WRITE ( *, FMT="(A)" ) "WARNING: Some profiles were not encoded "// &
2313 "or written to the BUFR file"
2314 END IF
2315
2316 IF ( nmsg > 0 ) THEN
2317 WRITE ( Numstr, FMT="(I10)" ) nmsg
2318 WRITE ( *, FMT="(A)", ADVANCE="NO" ) "Generated " // &
2319 TRIM(ADJUSTL(Numstr))
2320 IF ( GTShdrType == NOhdrs ) THEN
2321 WRITE ( *, FMT="(A)", ADVANCE="NO" ) " BUFR messages"
2322 ELSE
2323 WRITE ( *, FMT="(A)", ADVANCE="NO" ) " GTS bulletins"
2324 END IF
2325 WRITE ( *, FMT="(A)" ) " to " // TRIM(BUFRdsn)
2326 END IF
2327
2328 IF ( ALLOCATED(ROPPdsn) ) DEALLOCATE (ROPPdsn)
2329 WRITE ( *, * )
2330 CALL EXIT(ErrOK)
2331
2332END PROGRAM ropp2bufr