NCEPLIBS-bufr 11.7.1
writlc.f
Go to the documentation of this file.
1C> @file
2C> @brief Write a long character string (greater than 8 bytes) to
3C> a data subset.
4
5C> This subroutine writes a long character string (greater than 8 bytes)
6C> to a data subset.
7C>
8C> <p>The data subset should have already been written into a BUFR
9C> message via a previous call to one of the
10C> [subset-writing subroutines](@ref hierarchy), before calling this
11C> subroutine to write any long character strings into the same subset.
12C>
13C> @authors J. Woollen
14C> @authors J. Ator
15C> @date 2003-11-04
16C>
17C> @param[in] LUNIT -- integer: Fortran logical unit number for BUFR file
18C> @param[in] CHR -- character*(*): Value corresponding to STR
19C> @param[in] STR -- character*(*): Table B mnemonic of long character
20C> string to be written, possibly supplemented
21C> with an ordinal occurrence notation
22C>
23C> <p>If there is more than one occurrence of STR within the data subset
24C> definition, then each occurrence can be written via a separate call
25C> to this subroutine, and by appending the ordinal number of the
26C> occurrence to STR in each case. For example, if there are 5
27C> occurrences of mnemonic LSTID within a given data subset definition,
28C> then 5 separate calls should be made to this subroutine, once each
29C> with STR set to 'LSTID#1', 'LSTID#2', 'LSTID#3', 'LSTID#4' and
30C> 'LSTID#5'. However, the first notation is superfluous, because
31C> omitting the ordinal number always defaults to the first occurrence
32C> of a particular string, so a user could just specify 'LSTID'
33C> instead of 'LSTID#1'.
34C>
35C> @remarks
36C> - Character strings which are 8 bytes or less in length can be
37C> written by converting the string into a real*8 value within the
38C> application program, and then using the real*8 USR array within a
39C> call to one of the BUFRLIB
40C> [values-writing subroutines](@ref hierarchy)
41C> prior to calling one of the
42C> [subset-writing subroutines](@ref hierarchy)
43C> for the data subset.
44C>
45C> <b>Program history log:</b>
46C> | Date | Programmer | Comments |
47C> | -----|------------|----------|
48C> | 2003-11-04 | J. Woollen | Original author |
49C> | 2004-08-09 | J. Ator | Maximum message length increased from 20,000 to 50,000 bytes |
50C> | 2005-11-29 | J. Ator | Use getlens() |
51C> | 2007-01-19 | J. Ator | Replaced call to parseq with call to parstr() |
52C> | 2009-03-23 | J. Ator | Added '#' option for more than one occurrence of STR |
53C> | 2009-08-11 | J. Woollen | Added COMMON COMPRS along with logic to write long strings into compressed subsets |
54C> | 2012-12-07 | J. Ator | Allow str mnemonic length of up to 14 chars when used with '#' occurrence code |
55C> | 2014-10-22 | J. Ator | No longer abort if no subset available for writing; just print a warning message |
56C> | 2014-12-10 | J. Ator | USE modules instead of COMMON blocks |
57C> | 2020-09-09 | J. Ator | No longer abort if STR not available within subset definition; instead, just print a warning message |
58C>
59 SUBROUTINE writlc(LUNIT,CHR,STR)
60
61 USE modv_mxlcc
62
63 USE moda_usrint
64 USE moda_msgcwd
65 USE moda_bitbuf
66 USE moda_tables
67 USE moda_comprs
68
69 COMMON /quiet / iprt
70
71 CHARACTER*(*) CHR,STR
72 CHARACTER*128 BORT_STR
73 CHARACTER*128 ERRSTR
74 CHARACTER*10 CTAG
75 CHARACTER*14 TGS(10)
76
77 DATA maxtg /10/
78
79C-----------------------------------------------------------------------
80C-----------------------------------------------------------------------
81
82C Check the file status.
83
84 CALL status(lunit,lun,il,im)
85 IF(il.EQ.0) GOTO 900
86 IF(il.LT.0) GOTO 901
87 IF(im.EQ.0) GOTO 902
88
89C Check for tags (mnemonics) in input string (there can only be one)
90
91 CALL parstr(str,tgs,maxtg,ntg,' ',.true.)
92 IF(ntg.GT.1) GOTO 903
93
94C Check if a specific occurrence of the input string was requested;
95C if not, then the default is to write the first occurrence.
96
97 CALL parutg(lun,1,tgs(1),nnod,kon,roid)
98 IF(kon.EQ.6) THEN
99 ioid=nint(roid)
100 IF(ioid.LE.0) ioid = 1
101 ctag = ' '
102 ii = 1
103 DO WHILE((ii.LE.10).AND.(tgs(1)(ii:ii).NE.'#'))
104 ctag(ii:ii)=tgs(1)(ii:ii)
105 ii = ii + 1
106 ENDDO
107 ELSE
108 ioid = 1
109 ctag = tgs(1)(1:10)
110 ENDIF
111
112 IF(iupbs3(mbay(1,lun),'ICMP').GT.0) THEN
113
114C The message is compressed.
115
116 n = 1
117 itagct = 0
118 CALL usrtpl(lun,n,n)
119 DO WHILE (n+1.LE.nval(lun))
120 n = n+1
121 node = inv(n,lun)
122 IF(itp(node).EQ.1) THEN
123 CALL usrtpl(lun,n,matx(n,ncol))
124 ELSEIF(ctag.EQ.tag(node)) THEN
125 itagct = itagct + 1
126 IF(itagct.EQ.ioid) THEN
127 IF(itp(node).NE.3) GOTO 904
128 catx(n,ncol)=' '
129
130C The following statement enforces a limit of MXLCC
131C characters per long character string when writing
132C compressed messages. This limit keeps the array
133C CATX to a reasonable dimensioned size.
134
135 nchr=min(mxlcc,ibt(node)/8)
136 catx(n,ncol)=chr(1:nchr)
137 CALL usrtpl(lun,1,1)
138 GOTO 100
139 ENDIF
140 ENDIF
141 ENDDO
142 ELSE
143
144C The message is not compressed. Locate the beginning of the
145C data (Section 4) in the message.
146
147 CALL getlens(mbay(1,lun),3,len0,len1,len2,len3,l4,l5)
148 mbyte = len0 + len1 + len2 + len3 + 4
149 nsubs = 1
150
151C Find the most recently written subset in the message.
152
153 DO WHILE(nsubs.LT.nsub(lun))
154 ibit = mbyte*8
155 CALL upb(nbyt,16,mbay(1,lun),ibit)
156 mbyte = mbyte + nbyt
157 nsubs = nsubs + 1
158 ENDDO
159
160 IF(nsubs.NE.nsub(lun)) THEN
161 IF(iprt.GE.0) THEN
162 CALL errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
163 errstr = 'BUFRLIB: WRITLC - COULDN''T WRITE VALUE FOR ' // ctag
164 . // ' INTO SUBSET, BECAUSE NO SUBSET WAS OPEN FOR WRITING'
165 CALL errwrt(errstr)
166 CALL errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
167 CALL errwrt(' ')
168 ENDIF
169 GOTO 100
170 ENDIF
171
172C Locate and write the long character string within this subset.
173
174 itagct = 0
175 mbit = mbyte*8 + 16
176 nbit = 0
177 n = 1
178 CALL usrtpl(lun,n,n)
179 DO WHILE (n+1.LE.nval(lun))
180 n = n+1
181 node = inv(n,lun)
182 mbit = mbit+nbit
183 nbit = ibt(node)
184 IF(itp(node).EQ.1) THEN
185 CALL upbb(ival,nbit,mbit,mbay(1,lun))
186 CALL usrtpl(lun,n,ival)
187 ELSEIF(ctag.EQ.tag(node)) THEN
188 itagct = itagct + 1
189 IF(itagct.EQ.ioid) THEN
190 IF(itp(node).NE.3) GOTO 904
191 nchr = nbit/8
192 ibit = mbit
193 DO j=1,nchr
194 CALL pkc(' ',1,mbay(1,lun),ibit)
195 ENDDO
196 CALL pkc(chr,nchr,mbay(1,lun),mbit)
197 CALL usrtpl(lun,1,1)
198 GOTO 100
199 ENDIF
200 ENDIF
201 ENDDO
202 ENDIF
203
204 IF(iprt.GE.0) THEN
205 CALL errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
206 errstr = 'BUFRLIB: WRITLC - COULDN''T WRITE VALUE FOR ' // ctag
207 . // ' INTO SUBSET, BECAUSE IT WASN''T FOUND IN THE SUBSET'
208 . // ' DEFINITION'
209 CALL errwrt(errstr)
210 errstr = '(' // ctag // ' MAY NOT BE IN THE BUFR TABLE(?))'
211 CALL errwrt(errstr)
212 CALL errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
213 CALL errwrt(' ')
214 ENDIF
215
216C EXITS
217C -----
218
219100 RETURN
220900 CALL bort('BUFRLIB: WRITLC - OUTPUT BUFR FILE IS CLOSED, IT '//
221 . 'MUST BE OPEN FOR OUTPUT')
222901 CALL bort('BUFRLIB: WRITLC - OUTPUT BUFR FILE IS OPEN FOR '//
223 . 'INPUT, IT MUST BE OPEN FOR OUTPUT')
224902 CALL bort('BUFRLIB: WRITLC - A MESSAGE MUST BE OPEN IN OUTPUT '//
225 . 'BUFR FILE, NONE ARE')
226903 WRITE(bort_str,'("BUFRLIB: WRITLC - THERE CANNOT BE MORE THAN '//
227 . ' ONE MNEMONIC IN THE INPUT STRING (",A,") (HERE THERE ARE",I4'//
228 . ',")")') str,ntg
229 CALL bort(bort_str)
230904 WRITE(bort_str,'("BUFRLIB: WRITLC - MNEMONIC ",A," DOES NOT '//
231 . 'REPRESENT A CHARACTER ELEMENT (TYP=",A,")")') ctag,typ(node)
232 CALL bort(bort_str)
233905 WRITE(bort_str,'("BUFRLIB: WRITLC - THE MOST RECENTLY WRITTEN '//
234 . .NE.' SUBSET NO. (",I3,") IN MSG THE STORED VALUE FOR THE NO.'//
235 . ' OF SUBSETS (",I3,") IN MSG")') nsubs,nsub(lun)
236 CALL bort(bort_str)
237 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 getlens(MBAY, LL, LEN0, LEN1, LEN2, LEN3, LEN4, LEN5)
This subroutine reads the lengths of all of the individual sections of a given BUFR message,...
Definition: getlens.f:40
function iupbs3(MBAY, S3MNEM)
This function returns a specified value from within Section 3 of a BUFR message.
Definition: iupbs3.f:35
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 *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
Definition: moda_tables.F:133
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
Definition: moda_tables.F:138
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
Definition: moda_tables.F:132
This module declares and initializes the MXLCC variable.
Definition: modv_MXLCC.f:13
integer mxlcc
Maximum length (in bytes) of a character string that can be written into a data subset of a compresse...
Definition: modv_MXLCC.f:20
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 pkc(CHR, NCHR, IBAY, IBIT)
This subroutine encodes a character string within a specified number of bits of an integer array,...
Definition: pkc.f:41
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 upb(NVAL, NBITS, IBAY, IBIT)
THIS SUBROUTINE UNPACKS AND RETURNS A BINARY INTEGER CONTAINED WITHIN NBITS BITS OF IBAY,...
Definition: upb.f:50
subroutine upbb(NVAL, NBITS, IBIT, IBAY)
THIS SUBROUTINE UNPACKS AND RETURNS A BINARY INTEGER CONTAINED WITHIN NBITS BITS OF IBAY,...
Definition: upbb.f:43
subroutine usrtpl(LUN, INVN, NBMP)
THIS SUBROUTINE STORES THE SUBSET TEMPLATE INTO INTERNAL SUBSET ARRAYS IN MODULE USRINT FOR CASES OF ...
Definition: usrtpl.f:52
subroutine writlc(LUNIT, CHR, STR)
This subroutine writes a long character string (greater than 8 bytes) to a data subset.
Definition: writlc.f:60