63 SUBROUTINE rdmtbd ( LUNSTD, LUNLTD, MXMTBD, MXELEM,
64 . IMT, IMTV, IOGCE, ILTV,
65 . NMTBD, IMFXYN, CMMNEM, CMDSC, CMSEQ,
66 . NMELEM, IEFXYN, CEELEM )
68 character*200 stline, ltline
69 character*128 bort_str
70 character*120 ceelem(mxmtbd,mxelem)
71 character*6 cmatch,
adn30
73 character cmseq(120,*)
76 integer imfxyn(*), nmelem(*),
77 . iefxyn(mxmtbd,mxelem)
89 CALL gettbh ( lunstd, lunltd,
'D', imt, imtv, iogce, iltv )
95 CALL getntbe ( lunstd, isfxyn, stline, iers )
96 CALL getntbe ( lunltd, ilfxyn, ltline, ierl )
97 DO WHILE ( ( iers .EQ. 0 ) .OR. ( ierl .EQ. 0 ) )
98 IF ( ( iers .EQ. 0 ) .AND. ( ierl .EQ. 0 ) )
THEN
99 IF ( isfxyn .EQ. ilfxyn )
THEN
100 cmatch =
adn30( isfxyn, 6 )
102 ELSE IF ( isfxyn .LT. ilfxyn )
THEN
103 CALL sntbde ( lunstd, isfxyn, stline, mxmtbd, mxelem,
104 . nmtbd, imfxyn, cmmnem, cmdsc, cmseq,
105 . nmelem, iefxyn, ceelem )
106 CALL getntbe ( lunstd, isfxyn, stline, iers )
108 CALL sntbde ( lunltd, ilfxyn, ltline, mxmtbd, mxelem,
109 . nmtbd, imfxyn, cmmnem, cmdsc, cmseq,
110 . nmelem, iefxyn, ceelem )
111 CALL getntbe ( lunltd, ilfxyn, ltline, ierl )
113 ELSE IF ( iers .EQ. 0 )
THEN
114 CALL sntbde ( lunstd, isfxyn, stline, mxmtbd, mxelem,
115 . nmtbd, imfxyn, cmmnem, cmdsc, cmseq,
116 . nmelem, iefxyn, ceelem )
117 CALL getntbe ( lunstd, isfxyn, stline, iers )
118 ELSE IF ( ierl .EQ. 0 )
THEN
119 CALL sntbde ( lunltd, ilfxyn, ltline, mxmtbd, mxelem,
120 . nmtbd, imfxyn, cmmnem, cmdsc, cmseq,
121 . nmelem, iefxyn, ceelem )
122 CALL getntbe ( lunltd, ilfxyn, ltline, ierl )
127 900
WRITE(bort_str,
'("BUFRLIB: RDMTBD - STANDARD AND LOCAL'//
128 .
' TABLE D FILES BOTH CONTAIN SAME FXY NUMBER: ",5A)')
129 . cmatch(1:1),
'-', cmatch(2:3),
'-', cmatch(4:6)
character *(*) function adn30(IDN, L30)
This function converts an FXY value from its bit-wise (integer) representation to its 5 or 6 characte...
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
subroutine getntbe(LUNT, IFXYN, LINE, IRET)
This subroutine reads the first line of the next entry from the specified ASCII master table B,...
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...
subroutine rdmtbd(LUNSTD, LUNLTD, MXMTBD, MXELEM, IMT, IMTV, IOGCE, ILTV, NMTBD, IMFXYN, CMMNEM, CMDSC, CMSEQ, NMELEM, IEFXYN, CEELEM)
This subroutine reads master Table D information from two separate ASCII files (one standard and one ...
subroutine sntbde(LUNT, IFXYN, LINE, MXMTBD, MXELEM, NMTBD, IMFXYN, CMMNEM, CMDSC, CMSEQ, NMELEM, IEFXYN, CEELEM)
This subroutine stores the first line of an entry that was previously read from an ASCII master Table...
subroutine wrdlen
This subroutine figures out some important information about the local machine on which the BUFRLIB s...