NCEPLIBS-bufr 11.7.1
rdmtbf.f
Go to the documentation of this file.
1C> @file
2C> @brief Read master Code/Flag table information from local file system
3
4C> This subroutine reads master Code/Flag table information from two
5C> separate ASCII files (one standard and one local) and then merges the
6C> output into a single set of arrays.
7C>
8C> <p>Each of the two ASCII files must already be individually sorted
9C> in ascending order with respect to the FXY numbers.
10C>
11C> @author J. Ator
12C> @date 2017-10-17
13C>
14C> @param[in] LUNSTF -- integer: Fortran logical unit number for
15C> ASCII file containing standard Code/Flag table
16C> information
17C> @param[in] LUNLTF -- integer: Fortran logical unit number for
18C> ASCII file containing local Code/Flag table
19C> information
20C>
21C> <b>Program history log:</b>
22C> | Date | Programmer | Comments |
23C> | -----|------------|----------|
24C> | 2017-10-17 | J. Ator | Original author |
25C>
26 SUBROUTINE rdmtbf ( LUNSTF, LUNLTF )
27
28 character*160 stline, ltline
29 character*128 bort_str
30 character*6 cmatch, adn30
31
32C-----------------------------------------------------------------------
33C-----------------------------------------------------------------------
34
35C Call WRDLEN to initialize some important information about the
36C local machine, just in case it hasn't already been called.
37
38 CALL wrdlen
39
40C Initialize the internal memory structure, including allocating
41C space for it in case this hasn't already been done.
42
43 CALL inittbf
44
45C Read and parse the header lines of both files.
46
47 CALL gettbh ( lunstf, lunltf, 'F', imt, imtv, iogce, iltv )
48
49C Read through the remainder of both files, merging the
50C contents into a unified internal memory structure.
51
52 CALL getntbe ( lunstf, isfxyn, stline, iers )
53 CALL getntbe ( lunltf, ilfxyn, ltline, ierl )
54 DO WHILE ( ( iers .EQ. 0 ) .OR. ( ierl .EQ. 0 ) )
55 IF ( ( iers .EQ. 0 ) .AND. ( ierl .EQ. 0 ) ) THEN
56 IF ( isfxyn .EQ. ilfxyn ) THEN
57 cmatch = adn30( isfxyn, 6 )
58 GOTO 900
59 ELSE IF ( isfxyn .LT. ilfxyn ) THEN
60 CALL sntbfe ( lunstf, isfxyn, stline )
61 CALL getntbe ( lunstf, isfxyn, stline, iers )
62 ELSE
63 CALL sntbfe ( lunltf, ilfxyn, ltline )
64 CALL getntbe ( lunltf, ilfxyn, ltline, ierl )
65 ENDIF
66 ELSE IF ( iers .EQ. 0 ) THEN
67 CALL sntbfe ( lunstf, isfxyn, stline )
68 CALL getntbe ( lunstf, isfxyn, stline, iers )
69 ELSE IF ( ierl .EQ. 0 ) THEN
70 CALL sntbfe ( lunltf, ilfxyn, ltline )
71 CALL getntbe ( lunltf, ilfxyn, ltline, ierl )
72 ENDIF
73 ENDDO
74
75C Sort the contents of the internal memory structure.
76
77 CALL sorttbf
78
79 RETURN
80 900 WRITE(bort_str,'("BUFRLIB: RDMTBF - STANDARD AND LOCAL'//
81 . ' CODE/FLAG TABLE FILES BOTH CONTAIN SAME FXY NUMBER: ",5A)')
82 . cmatch(1:1), '-', cmatch(2:3), '-', cmatch(4:6)
83 CALL bort(bort_str)
84 END
character *(*) function adn30(IDN, L30)
This function converts an FXY value from its bit-wise (integer) representation to its 5 or 6 characte...
Definition: adn30.f:29
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
Definition: bort.f:23
void inittbf(void)
This subroutine initializes the internal memory structure for storage of master Code/Flag table entri...
Definition: inittbf.c:22
void sorttbf(void)
This subroutine sorts the entries within the internal memory structure for storage of master Code/Fla...
Definition: sorttbf.c:20
subroutine getntbe(LUNT, IFXYN, LINE, IRET)
This subroutine reads the first line of the next entry from the specified ASCII master table B,...
Definition: getntbe.f:31
subroutine gettbh(LUNS, LUNL, TAB, IMT, IMTV, IOGCE, ILTV)
This subroutine reads the header lines from two separate ASCII files (one standard and one local) con...
Definition: gettbh.f:41
subroutine rdmtbf(LUNSTF, LUNLTF)
This subroutine reads master Code/Flag table information from two separate ASCII files (one standard ...
Definition: rdmtbf.f:27
subroutine sntbfe(LUNT, IFXYN, LINE)
This subroutine stores the first line of an entry that was previously read from an ASCII master Code/...
Definition: sntbfe.f:26
subroutine wrdlen
This subroutine figures out some important information about the local machine on which the BUFRLIB s...
Definition: wrdlen.F:36