NCEPLIBS-bufr  12.0.0
rdmtbf.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Read master Code/Flag table information from local file system.
3 C>
4 C> @author J. Ator @date 2017-10-17
5 
6 C> This subroutine reads master Code/Flag table information from two
7 C> separate ASCII files (one standard and one local) and then merges the
8 C> output into a single set of arrays.
9 C>
10 C> Each of the two ASCII files must already be individually sorted
11 C> in ascending order with respect to the FXY numbers.
12 C>
13 C> @param[in] LUNSTF -- integer: Fortran logical unit number for
14 C> ASCII file containing standard Code/Flag table
15 C> information
16 C> @param[in] LUNLTF -- integer: Fortran logical unit number for
17 C> ASCII file containing local Code/Flag table
18 C> information
19 C>
20 C> @author J. Ator @date 2017-10-17
21  SUBROUTINE rdmtbf ( LUNSTF, LUNLTF )
22 
23  use bufrlib
24 
25  CHARACTER*160 STLINE, LTLINE
26  CHARACTER*128 BORT_STR
27  CHARACTER*6 CMATCH, ADN30
28 
29 C-----------------------------------------------------------------------
30 C-----------------------------------------------------------------------
31 
32 C Call WRDLEN to initialize some important information about the
33 C local machine, just in case it hasn't already been called.
34 
35  CALL wrdlen
36 
37 C Initialize the internal memory structure, including allocating
38 C space for it in case this hasn't already been done.
39 
40  CALL inittbf_c
41 
42 C Read and parse the header lines of both files.
43 
44  CALL gettbh ( lunstf, lunltf, 'F', imt, imtv, iogce, iltv )
45 
46 C Read through the remainder of both files, merging the
47 C contents into a unified internal memory structure.
48 
49  CALL getntbe ( lunstf, isfxyn, stline, iers )
50  CALL getntbe ( lunltf, ilfxyn, ltline, ierl )
51  DO WHILE ( ( iers .EQ. 0 ) .OR. ( ierl .EQ. 0 ) )
52  IF ( ( iers .EQ. 0 ) .AND. ( ierl .EQ. 0 ) ) THEN
53  IF ( isfxyn .EQ. ilfxyn ) THEN
54  cmatch = adn30( isfxyn, 6 )
55  GOTO 900
56  ELSE IF ( isfxyn .LT. ilfxyn ) THEN
57  CALL sntbfe ( lunstf, isfxyn )
58  CALL getntbe ( lunstf, isfxyn, stline, iers )
59  ELSE
60  CALL sntbfe ( lunltf, ilfxyn )
61  CALL getntbe ( lunltf, ilfxyn, ltline, ierl )
62  ENDIF
63  ELSE IF ( iers .EQ. 0 ) THEN
64  CALL sntbfe ( lunstf, isfxyn )
65  CALL getntbe ( lunstf, isfxyn, stline, iers )
66  ELSE IF ( ierl .EQ. 0 ) THEN
67  CALL sntbfe ( lunltf, ilfxyn )
68  CALL getntbe ( lunltf, ilfxyn, ltline, ierl )
69  ENDIF
70  ENDDO
71 
72 C Sort the contents of the internal memory structure.
73 
74  CALL sorttbf_c
75 
76  RETURN
77  900 WRITE(bort_str,'("BUFRLIB: RDMTBF - STANDARD AND LOCAL'//
78  . ' CODE/FLAG TABLE FILES BOTH CONTAIN SAME FXY NUMBER: ",5A)')
79  . cmatch(1:1), '-', cmatch(2:3), '-', cmatch(4:6)
80  CALL bort(bort_str)
81  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
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:26
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:36
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
Definition: bufrlib.F90:11
subroutine rdmtbf(LUNSTF, LUNLTF)
This subroutine reads master Code/Flag table information from two separate ASCII files (one standard ...
Definition: rdmtbf.f:22
subroutine sntbfe(LUNT, IFXYN)
Store a master Code/Flag table entry into internal memory.
Definition: sntbfe.f:18
subroutine wrdlen
Determine important information about the local machine.
Definition: wrdlen.F:25