NCEPLIBS-bufr 11.7.1
readlc.f
Go to the documentation of this file.
1C> @file
2C> @brief Read a long character string (greater than 8 bytes) from
3C> a data subset.
4
5C> This subroutine reads a long character string (greater than 8 bytes)
6C> from a data subset.
7C>
8C> <p>The data subset should have already been read into internal arrays
9C> via a previous call to one of the
10C> [subset-reading subroutines](@ref hierarchy).
11C>
12C> @authors J. Woollen
13C> @authors J. Ator
14C> @date 2003-11-04
15C>
16C> @param[in] LUNIT -- integer: Fortran logical unit number for BUFR file
17C> @param[out] CHR -- character*(*): Value corresponding to STR
18C> @param[in] STR -- character*(*): Table B mnemonic of long character
19C> string to be retrieved, possibly supplemented
20C> with an ordinal occurrence notation
21C>
22C> <p>If there is more than one occurrence of STR within the data subset
23C> definition, then each occurrence can be retrieved via a separate call
24C> to this subroutine, and by appending the ordinal number of the
25C> occurrence to STR in each case. For example, if there are 5
26C> occurrences of mnemonic LSTID within a given data subset definition,
27C> then 5 separate calls should be made to this subroutine, once each
28C> with STR set to 'LSTID#1', 'LSTID#2', 'LSTID#3', 'LSTID#4' and
29C> 'LSTID#5'. However, the first notation is superfluous, because
30C> omitting the ordinal number always defaults to the first occurrence
31C> of a particular string, so a user could just specify 'LSTID'
32C> instead of 'LSTID#1'.
33C>
34C> @remarks
35C> - Character strings which are 8 bytes or less in length can be read
36C> using the real*8 USR array within a call to one of the BUFRLIB
37C> [values-reading subroutines](@ref hierarchy) and then converting the
38C> corresponding real*8 value to character format within the
39C> application program.
40C> - If STR is not found within the data subset definition, then CHR is
41C> returned with all bits set to 1, which is the standard WMO BUFR value
42C> for "missing" data. Any CHR value returned by this subroutine can be
43C> checked for equivalence to this "missing" value via a call to
44C> function icbfms().
45C>
46C> <b>Program history log:</b>
47C> | Date | Programmer | Comments |
48C> | -----|------------|----------|
49C> | 2003-11-04 | J. Woollen | Original author |
50C> | 2004-08-09 | J. Ator | Maximum message length increased from 20,000 to 50,000 bytes |
51C> | 2007-01-19 | J. Ator | Replaced call to parseq with call to parstr() |
52C> | 2009-03-23 | J. Ator | Added capability for compressed messages; added check for overflow of chr; added '#' option for more than one occurrence of STR |
53C> | 2009-04-21 | J. Ator | Use errwrt() |
54C> | 2012-12-07 | J. Ator | Allow str mnemonic length of up to 14 chars when used with '#' occurrence code |
55C> | 2014-12-10 | J. Ator | Use modules instead of COMMON blocks |
56C> | 2020-09-09 | J. Ator | Set CHR to "missing" instead of all blanks if STR isn't found in subset |
57C>
58 SUBROUTINE readlc(LUNIT,CHR,STR)
59
60 USE moda_usrint
61 USE moda_usrbit
62 USE moda_unptyp
63 USE moda_bitbuf
64 USE moda_tables
65 USE moda_rlccmn
66
67 COMMON /quiet / iprt
68
69 CHARACTER*(*) CHR,STR
70 CHARACTER*128 BORT_STR,ERRSTR
71 CHARACTER*10 CTAG
72 CHARACTER*14 TGS(10)
73
74 DATA maxtg /10/
75
76C-----------------------------------------------------------------------
77C-----------------------------------------------------------------------
78
79 chr = ' '
80 lchr=len(chr)
81
82C CHECK THE FILE STATUS
83C ---------------------
84
85 CALL status(lunit,lun,il,im)
86 IF(il.EQ.0) GOTO 900
87 IF(il.GT.0) GOTO 901
88 IF(im.EQ.0) GOTO 902
89
90C CHECK FOR TAGS (MNEMONICS) IN INPUT STRING (THERE CAN ONLY BE ONE)
91C ------------------------------------------------------------------
92
93 CALL parstr(str,tgs,maxtg,ntg,' ',.true.)
94 IF(ntg.GT.1) GOTO 903
95
96C Check if a specific occurrence of the input string was requested;
97C if not, then the default is to return the first occurrence.
98
99 CALL parutg(lun,0,tgs(1),nnod,kon,roid)
100 IF(kon.EQ.6) THEN
101 ioid=nint(roid)
102 IF(ioid.LE.0) ioid = 1
103 ctag = ' '
104 ii = 1
105 DO WHILE((ii.LE.10).AND.(tgs(1)(ii:ii).NE.'#'))
106 ctag(ii:ii)=tgs(1)(ii:ii)
107 ii = ii + 1
108 ENDDO
109 ELSE
110 ioid = 1
111 ctag = tgs(1)(1:10)
112 ENDIF
113
114C LOCATE AND DECODE THE LONG CHARACTER STRING
115C -------------------------------------------
116
117 IF(msgunp(lun).EQ.0.OR.msgunp(lun).EQ.1) THEN
118
119C The message is uncompressed
120
121 itagct = 0
122 DO n=1,nval(lun)
123 nod = inv(n,lun)
124 IF(ctag.EQ.tag(nod)) THEN
125 itagct = itagct + 1
126 IF(itagct.EQ.ioid) THEN
127 IF(itp(nod).NE.3) GOTO 904
128 nchr = nbit(n)/8
129 IF(nchr.GT.lchr) GOTO 905
130 kbit = mbit(n)
131 CALL upc(chr,nchr,mbay(1,lun),kbit,.true.)
132 GOTO 100
133 ENDIF
134 ENDIF
135 ENDDO
136 ELSEIF(msgunp(lun).EQ.2) THEN
137
138C The message is compressed
139
140 IF(nrst.GT.0) THEN
141 itagct = 0
142 DO ii=1,nrst
143 IF(ctag.EQ.crtag(ii)) THEN
144 itagct = itagct + 1
145 IF(itagct.EQ.ioid) THEN
146 nchr = irnch(ii)
147 IF(nchr.GT.lchr) GOTO 905
148 kbit = irbit(ii)
149 CALL upc(chr,nchr,mbay(1,lun),kbit,.true.)
150 GOTO 100
151 ENDIF
152 ENDIF
153 ENDDO
154 ENDIF
155 ELSE
156 GOTO 906
157 ENDIF
158
159C If we made it here, then we couldn't find the requested string.
160
161 IF(iprt.GE.0) THEN
162 CALL errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
163 errstr = 'BUFRLIB: READLC - MNEMONIC ' // tgs(1) //
164 . ' NOT LOCATED IN REPORT SUBSET - RETURN WITH MISSING' //
165 . ' STRING FOR CHARACTER DATA ELEMENT'
166 CALL errwrt(errstr)
167 CALL errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
168 CALL errwrt(' ')
169 ENDIF
170 DO ii=1,lchr
171 CALL ipkm(chr(ii:ii),1,255)
172 ENDDO
173
174C EXITS
175C -----
176
177100 RETURN
178900 CALL bort('BUFRLIB: READLC - INPUT BUFR FILE IS CLOSED, IT MUST'//
179 . ' BE OPEN FOR INPUT')
180901 CALL bort('BUFRLIB: READLC - INPUT BUFR FILE IS OPEN FOR '//
181 . 'OUTPUT, IT MUST BE OPEN FOR INPUT')
182902 CALL bort('BUFRLIB: READLC - A MESSAGE MUST BE OPEN IN INPUT '//
183 . 'BUFR FILE, NONE ARE')
184903 WRITE(bort_str,'("BUFRLIB: READLC - THERE CANNOT BE MORE THAN '//
185 . 'ONE MNEMONIC IN THE INPUT STRING (",A,") (HERE THERE ARE ",'//
186 . 'I3,")")') str,ntg
187 CALL bort(bort_str)
188904 WRITE(bort_str,'("BUFRLIB: READLC - MNEMONIC ",A," DOES NOT '//
189 . 'REPRESENT A CHARACTER ELEMENT (ITP=",I2,")")') tgs(1),itp(nod)
190 CALL bort(bort_str)
191905 WRITE(bort_str,'("BUFRLIB: READLC - MNEMONIC ",A," IS A '//
192 . 'CHARACTER STRING OF LENGTH",I4," BUT SPACE WAS PROVIDED '//
193 . 'FOR ONLY",I4, " CHARACTERS")') tgs(1),nchr,lchr
194 CALL bort(bort_str)
195906 WRITE(bort_str,'("BUFRLIB: READLC - MESSAGE UNPACK TYPE",I3,'//
196 . '" IS NOT RECOGNIZED")') msgunp
197 CALL bort(bort_str)
198 END
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
Definition: bort.f:23
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
Definition: errwrt.f:42
subroutine ipkm(CBAY, NBYT, N)
This subroutine encodes an integer value within a specified number of bytes of a character string,...
Definition: ipkm.f:28
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 used to store the internal jump/link table.
Definition: moda_tables.F:13
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
Definition: moda_tables.F:141
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
Definition: moda_tables.F:132
subroutine parstr(STR, TAGS, MTAG, NTAG, SEP, LIMIT80)
THIS SUBROUTINE PARSES A STRING CONTAINING ONE OR MORE SUBSTRINGS INTO AN ARRAY OF SUBSTRINGS.
Definition: parstr.f:38
subroutine parutg(LUN, IO, UTG, NOD, KON, VAL)
THIS SUBROUTINE PARSES A USER-SPECIFIED TAG (MNEMONIC) (UTG) THAT REPRESENTS A VALUE EITHER BEING DEC...
Definition: parutg.f:121
subroutine readlc(LUNIT, CHR, STR)
This subroutine reads a long character string (greater than 8 bytes) from a data subset.
Definition: readlc.f:59
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
Definition: status.f:56
subroutine upc(CHR, NCHR, IBAY, IBIT, CNVNULL)
THIS SUBROUTINE UNPACKS AND RETURNS A CHARACTER STRING OF LENGTH NCHR CONTAINED WITHIN NCHR BYTES OF ...
Definition: upc.f:50