72 CHARACTER*128 BORT_STR
84 CALL status(lunit,lun,il,im)
91 CALL parstr(str,tgs,maxtg,ntg,
' ',.true.)
97 CALL parutg(lun,1,tgs(1),nnod,kon,roid)
100 IF(ioid.LE.0) ioid = 1
103 DO WHILE((ii.LE.10).AND.(tgs(1)(ii:ii).NE.
'#'))
104 ctag(ii:ii)=tgs(1)(ii:ii)
119 DO WHILE (n+1.LE.nval(lun))
122 IF(
itp(node).EQ.1)
THEN
123 CALL usrtpl(lun,n,matx(n,ncol))
124 ELSEIF(ctag.EQ.
tag(node))
THEN
126 IF(itagct.EQ.ioid)
THEN
127 IF(
itp(node).NE.3)
GOTO 904
136 catx(n,ncol)=chr(1:nchr)
147 CALL getlens(
mbay(1,lun),3,len0,len1,len2,len3,l4,l5)
148 mbyte = len0 + len1 + len2 + len3 + 4
153 DO WHILE(nsubs.LT.nsub(lun))
155 CALL upb(nbyt,16,
mbay(1,lun),ibit)
160 IF(nsubs.NE.nsub(lun))
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'
166 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
179 DO WHILE (n+1.LE.nval(lun))
184 IF(
itp(node).EQ.1)
THEN
185 CALL upbb(ival,nbit,mbit,
mbay(1,lun))
187 ELSEIF(ctag.EQ.
tag(node))
THEN
189 IF(itagct.EQ.ioid)
THEN
190 IF(
itp(node).NE.3)
GOTO 904
194 CALL pkc(
' ',1,
mbay(1,lun),ibit)
196 CALL pkc(chr,nchr,
mbay(1,lun),mbit)
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'
210 errstr =
'(' // ctag //
' MAY NOT BE IN THE BUFR TABLE(?))'
212 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
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'//
230904
WRITE(bort_str,
'("BUFRLIB: WRITLC - MNEMONIC ",A," DOES NOT '//
231 .
'REPRESENT A CHARACTER ELEMENT (TYP=",A,")")') ctag,
typ(node)
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)
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
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,...
function iupbs3(MBAY, S3MNEM)
This function returns a specified value from within Section 3 of a BUFR message.
This module contains array and variable declarations used to store BUFR messages internally for multi...
integer, dimension(:,:), allocatable mbay
Current BUFR message for each internal I/O stream.
This module contains array and variable declarations used to store the internal jump/link table.
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
character *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
This module declares and initializes the MXLCC variable.
integer mxlcc
Maximum length (in bytes) of a character string that can be written into a data subset of a compresse...
subroutine parstr(STR, TAGS, MTAG, NTAG, SEP, LIMIT80)
THIS SUBROUTINE PARSES A STRING CONTAINING ONE OR MORE SUBSTRINGS INTO AN ARRAY OF SUBSTRINGS.
subroutine parutg(LUN, IO, UTG, NOD, KON, VAL)
THIS SUBROUTINE PARSES A USER-SPECIFIED TAG (MNEMONIC) (UTG) THAT REPRESENTS A VALUE EITHER BEING DEC...
subroutine pkc(CHR, NCHR, IBAY, IBIT)
This subroutine encodes a character string within a specified number of bits of an integer array,...
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
subroutine upb(NVAL, NBITS, IBAY, IBIT)
THIS SUBROUTINE UNPACKS AND RETURNS A BINARY INTEGER CONTAINED WITHIN NBITS BITS OF IBAY,...
subroutine upbb(NVAL, NBITS, IBIT, IBAY)
THIS SUBROUTINE UNPACKS AND RETURNS A BINARY INTEGER CONTAINED WITHIN NBITS BITS OF IBAY,...
subroutine usrtpl(LUN, INVN, NBMP)
THIS SUBROUTINE STORES THE SUBSET TEMPLATE INTO INTERNAL SUBSET ARRAYS IN MODULE USRINT FOR CASES OF ...
subroutine writlc(LUNIT, CHR, STR)
This subroutine writes a long character string (greater than 8 bytes) to a data subset.