NCEPLIBS-bufr 11.7.1
reads3.f
Go to the documentation of this file.
1C> @file
2C> @author ATOR @date 2009-03-23
3
4C> THIS SUBROUTINE READS THE SECTION 3 DESCRIPTORS FROM THE
5C> BUFR MESSAGE IN MBAY(1,LUN). IT THEN USES THE BUFR MASTER TABLES
6C> TO GENERATE THE NECESSARY INFORMATION FOR THESE DESCRIPTORS WITHIN
7C> THE INTERNAL BUFR TABLE ARRAYS.
8C>
9C> PROGRAM HISTORY LOG:
10C> 2009-03-23 J. ATOR -- ORIGINAL AUTHOR
11C> 2014-12-10 J. ATOR -- USE MODULES INSTEAD OF COMMON BLOCKS
12C> 2017-10-13 J. ATOR -- REMOVE FUNCTIONALITY TO CHECK WHETHER NEW
13C> MASTER TABLES NEED TO BE READ (THIS
14C> FUNCTIONALITY IS NOW PART OF FUNCTION
15C> IREADMT)
16
17C>
18C> USAGE: CALL READS3 ( LUN )
19C> INPUT ARGUMENT LIST:
20C> LUN - INTEGER: I/O STREAM INDEX INTO INTERNAL MEMORY ARRAYS
21C>
22C> REMARKS:
23C> THIS ROUTINE CALLS: ADN30 BORT DXINIT ERRWRT
24C> IFXY IGETNTBI IGETTDI IREADMT
25C> MAKESTAB STNTBIA STSEQ UPDS3
26C> THIS ROUTINE IS CALLED BY: READERME READMG
27C> Normally not called by any application
28C> programs.
29C>
30 SUBROUTINE reads3 ( LUN )
31
32 USE moda_sc3bfr
33 USE moda_bitbuf
34 USE moda_dscach
35
36 COMMON /quiet/ iprt
37
38 dimension ids3(maxnc)
39 character*6 cds3(maxnc),numb,adn30
40
41 character*55 cseq
42
43 character*128 errstr
44
45 logical incach
46
47 SAVE irepct
48
49C-----------------------------------------------------------------------
50C-----------------------------------------------------------------------
51
52C* Check whether the appropriate BUFR master table information has
53C* already been read into internal memory for this message.
54
55 IF ( ireadmt( lun ) .EQ. 1 ) THEN
56
57C* NO (i.e. we just had to read in new master table information
58C* for this message), so reset some corresponding values in
59C* other parts of the library.
60
61 CALL dxinit ( lun, 0 )
62 itmp = igettdi( 0 )
63 irepct = 0
64 ncnem = 0
65 ENDIF
66
67C* Unpack the list of Section 3 descriptors from the message.
68
69 CALL upds3 ( mbay(1,lun), maxnc, cds3, ncds3 )
70 DO ii = 1, ncds3
71 ids3(ii) = ifxy( cds3(ii) )
72 ENDDO
73
74C* Is the list of Section 3 descriptors already in the cache?
75
76C* The cache is a performance-enhancing device which saves
77C* time when the same descriptor sequences are encountered
78C* over and over within the calling program. Time is saved
79C* because the below calls to subroutines STSEQ and MAKESTAB
80C* are bypassed whenever a list is already in the cache.
81
82 incach = .false.
83 IF ( ncnem .GT. 0 ) THEN
84 ii = 1
85 DO WHILE ( (.NOT.incach) .AND. (ii.LE.ncnem) )
86 IF ( ncds3 .EQ. ndc(ii) ) THEN
87 jj = 1
88 incach = .true.
89 DO WHILE ( (incach) .AND. (jj.LE.ncds3) )
90 IF ( ids3(jj) .EQ. idcach(ii,jj) ) THEN
91 jj = jj + 1
92 ELSE
93 incach = .false.
94 ENDIF
95 ENDDO
96 IF (incach) THEN
97
98C* The list is already in the cache, so store the
99C* corresponding Table A mnemonic into MODULE SC3BFR
100C* and return.
101
102 IF ( iprt .GE. 2 ) THEN
103 CALL errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
104 errstr = 'BUFRLIB: READS3 - RE-USED CACHE LIST FOR ' // cnem(ii)
105 CALL errwrt(errstr)
106 CALL errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
107 CALL errwrt(' ')
108 ENDIF
109 tamnem(lun) = cnem(ii)
110 RETURN
111 ENDIF
112 ENDIF
113 ii = ii + 1
114 ENDDO
115 ENDIF
116
117C* Get the next available index within the internal Table A.
118
119 n = igetntbi ( lun, 'A' )
120
121C* Generate a Table A mnemonic and sequence description.
122
123 WRITE ( tamnem(lun), '(A5,I3.3)') 'MSTTB', n
124 cseq = 'TABLE A MNEMONIC ' // tamnem(lun)
125
126C* Store the Table A mnemonic and sequence into the cache.
127
128 ncnem = ncnem + 1
129 IF ( ncnem .GT. mxcnem ) GOTO 900
130 cnem(ncnem) = tamnem(lun)
131 ndc(ncnem) = ncds3
132 DO jj = 1, ncds3
133 idcach(ncnem,jj) = ids3(jj)
134 ENDDO
135 IF ( iprt .GE. 2 ) THEN
136 CALL errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
137 errstr = 'BUFRLIB: READS3 - STORED CACHE LIST FOR ' //
138 . cnem(ncnem)
139 CALL errwrt(errstr)
140 CALL errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
141 CALL errwrt(' ')
142 ENDIF
143
144C* Get an FXY value to use with this Table A mnemonic.
145
146 idn = igettdi( lun )
147 numb = adn30( idn, 6 )
148
149C* Store all of the information for this mnemonic within the
150C* internal Table A.
151
152 CALL stntbia ( n, lun, numb, tamnem(lun), cseq )
153
154C* Store all of the information for this sequence within the
155C* internal Tables B and D.
156
157 CALL stseq ( lun, irepct, idn, tamnem(lun), cseq, ids3, ncds3 )
158
159C* Update the jump/link table.
160
161 CALL makestab
162
163 RETURN
164900 CALL bort('BUFRLIB: READS3 - MXCNEM OVERFLOW')
165 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
subroutine dxinit(LUN, IOI)
THIS SUBROUTINE INITIALIZES THE INTERNAL ARRAYS (IN MODULE TABABD) HOLDING THE DICTIONARY TABLE.
Definition: dxinit.f:41
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
Definition: errwrt.f:42
function ifxy(ADSC)
This function converts an FXY value from its 6 character representation to its bit-wise (integer) rep...
Definition: ifxy.f:43
function igetntbi(LUN, CTB)
This function returns the next available index for storing an entry within a specified internal DX BU...
Definition: igetntbi.f:28
function igettdi(IFLAG)
DEPENDING ON THE VALUE OF THE INPUT FLAG, THIS FUNCTION EITHER RETURNS THE NEXT USABLE SCRATCH TABLE ...
Definition: igettdi.f:31
integer function ireadmt(LUN)
This function checks the most recent BUFR message that was read via a call to one of the message-read...
Definition: ireadmt.f:43
subroutine makestab
THIS SUBROUTINE CONSTRUCTS AN INTERNAL JUMP/LINK TABLE WITHIN MODULE TABLES, USING THE INFORMATION WI...
Definition: makestab.f:75
This module contains array and variable declarations used to store BUFR messages internally for multi...
Definition: moda_bitbuf.F:10
integer, dimension(:,:), allocatable mbay
Current BUFR message for each internal I/O stream.
Definition: moda_bitbuf.F:26
This module contains array and variable declarations for the internal Table A mnemonic cache that is ...
Definition: moda_dscach.F:15
integer, dimension(mxcnem, maxnc) idcach
Bit-wise representations of the child descriptors for the corresponding Table A mnemonic in cnem.
Definition: moda_dscach.F:39
integer ncnem
Number of entries in the internal Table A mnemonic cache (up to a maximum of MXCNEM).
Definition: moda_dscach.F:36
character *8, dimension(mxcnem) cnem
Table A mnemonics.
Definition: moda_dscach.F:37
integer, dimension(mxcnem) ndc
Number of child descriptors for the corresponding Table A mnemonic in cnem.
Definition: moda_dscach.F:38
subroutine reads3(LUN)
THIS SUBROUTINE READS THE SECTION 3 DESCRIPTORS FROM THE BUFR MESSAGE IN MBAY(1,LUN).
Definition: reads3.f:31
subroutine stntbia(N, LUN, NUMB, NEMO, CELSQ)
THIS SUBROUTINE STORES A NEW ENTRY WITHIN INTERNAL BUFR TABLE A.
Definition: stntbia.f:28
void stseq(f77int *lun, f77int *irepct, f77int *idn, char nemo[8], char cseq[55], f77int cdesc[], f77int *ncdesc)
Given the bit-wise (integer) representation of a WMO-standard Table D descriptor, this subroutine use...
Definition: stseq.c:48
subroutine upds3(MBAY, LCDS3, CDS3, NDS3)
This subroutine returns the sequence of data descriptors contained within Section 3 of a BUFR message...
Definition: upds3.f:35