127 RECURSIVE SUBROUTINE ufbseq(LUNIN,USR,I1,I2,IRET,STR)
141 CHARACTER*156 bort_str
143 CHARACTER*10 tags(mtag)
146 DATA ifirst1/0/,ifirst2/0/
148 SAVE ifirst1, ifirst2
159 CALL x84(lunin,my_lunin,1)
162 CALL ufbseq(my_lunin,usr,my_i1,my_i2,iret,str)
163 CALL x48(iret,iret,1)
175 CALL status(lunit,lun,il,im)
179 io = min(max(0,il),1)
180 IF(lunit.NE.lunin) io = 0
184 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
185 errstr = .LE.
'BUFRLIB: UFBSEQ - 3rd ARG. (INPUT) IS 0, ' //
186 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
189 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
194 IF(iprt.EQ.-1) ifirst1 = 1
195 IF(io.EQ.0 .OR. ifirst1.EQ.0 .OR. iprt.GE.1)
THEN
196 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
197 errstr = .LE.
'BUFRLIB: UFBSEQ - 4th ARG. (INPUT) IS 0, ' //
198 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
201 IF(iprt.EQ.0 .AND. io.EQ.1)
THEN
202 errstr =
'Note: Only the first occurrence of this WARNING ' //
203 .
'message is printed, there may be more. To output all ' //
206 errstr =
'modify your application program to add ' //
207 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
208 .
'to a BUFRLIB routine.'
211 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
221 CALL parstr(str,tags,mtag,ntag,
' ',.true.)
222 IF(ntag.LT.1)
GOTO 902
223 IF(ntag.GT.1)
GOTO 903
226 IF(
inode(lun).NE.
inv(1,lun))
GOTO 906
245 IF(str.EQ.
tag(node))
THEN
246 IF(
typ(node).EQ.
'SEQ'.OR.
typ(node).EQ.
'RPC')
THEN
249 IF(ins1.EQ.0)
GOTO 200
250 IF(
typ(node).EQ.
'RPC'.AND.
val(ins1,lun).EQ.0.)
THEN
255 IF(ins2.EQ.0) ins2 = 10e5
257 DO WHILE(
link(nods).EQ.0.AND.
jmpb(nods).GT.0)
260 IF(
link(nods).EQ.0)
THEN
262 ELSEIF(
link(nods).GT.0)
THEN
265 ins2 = min(ins2,insx)
266 ELSEIF(
typ(node).EQ.
'SUB')
THEN
275 IF(ityp.GT.1) nseq = nseq+1
277 IF(nseq.GT.i1)
GOTO 908
288 IF(ins1.GT.
nval(lun))
GOTO 200
290 IF(
typ(node).EQ.
'RPC'.AND.
val(ins1,lun).EQ.0.)
THEN
293 ELSEIF(io.EQ.0.AND.iret+1.GT.i2)
THEN
295 CALL errwrt(
'++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
296 WRITE ( unit=errstr, fmt=
'(A,I5,A,A,A)' )
297 .
'BUFRLIB: UFBSEQ - INCOMPLETE READ; ONLY THE FIRST ', i2,
298 .
' (=4TH INPUT ARG.) ''LEVELS'' OF INPUT MNEMONIC ', tags(1),
301 CALL errwrt(
'++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
306 ELSEIF(ins1.EQ.0)
THEN
307 IF(io.EQ.1.AND.iret.LT.i2)
GOTO 910
312 IF(ins1.EQ. 0)
GOTO 200
313 IF(iret.EQ.i2)
GOTO 200
323 DO WHILE(
itp(
inv(j,lun)).LT.2)
326 IF(io.EQ.0) usr(i,iret) =
val(j,lun )
327 IF(io.EQ.1)
val(j,lun ) = usr(i,iret)
341 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
342 errstr =
'BUFRLIB: UFBSEQ - NO SPECIFIED VALUES READ IN, ' //
343 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
346 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
350 IF(iprt.EQ.-1) ifirst2 = 1
351 IF(ifirst2.EQ.0 .OR. iprt.GE.1)
THEN
352 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
353 errstr =
'BUFRLIB: UFBSEQ - NO SPECIFIED VALUES WRITTEN OUT, ' //
354 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
357 CALL errwrt(
'MAY NOT BE IN THE BUFR TABLE(?)')
359 errstr =
'Note: Only the first occurrence of this WARNING ' //
360 .
'message is printed, there may be more. To output all ' //
363 errstr =
'modify your application program to add ' //
364 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
365 .
'to a BUFRLIB routine.'
368 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
379 900
CALL bort(
'BUFRLIB: UFBSEQ - BUFR FILE IS CLOSED, IT MUST BE'//
381 901
CALL bort(
'BUFRLIB: UFBSEQ - A MESSAGE MUST BE OPEN IN BUFR '//
383 902
WRITE(bort_str,
'("BUFRLIB: UFBSEQ - THE INPUT STRING (",A,") '//
384 .
'DOES NOT CONTAIN ANY MNEMONICS!!")') str
386 903
WRITE(bort_str,
'("BUFRLIB: UFBSEQ - THERE CANNOT BE MORE THAN '//
387 .
'ONE MNEMONIC IN THE INPUT STRING (",A,") (HERE THERE ARE ",I3'//
390 904
WRITE(bort_str,
'("BUFRLIB: UFBSEQ - THIRD ARGUMENT (INPUT) MUST'//
391 . .GT.
' BE ZERO (HERE IT IS",I4,") - INPUT MNEMONIC IS ",A)')
394 905
WRITE(bort_str,
'("BUFRLIB: UFBSEQ - FOURTH ARGUMENT (INPUT) '//
395 . .GT.
'MUST BE ZERO (HERE IT IS",I4,") - INPUT MNEMONIC IS ",A)')
398 906
CALL bort(
'BUFRLIB: UFBSEQ - LOCATION OF INTERNAL TABLE FOR '//
399 .
'BUFR FILE DOES NOT AGREE WITH EXPECTED LOCATION IN INTERNAL '//
401 907
WRITE(bort_str,
'("BUFRLIB: UFBSEQ - INPUT MNEMONIC ",A," MUST '//
402 .
'BE A SEQUENCE (HERE IT IS TYPE """,A,""")")') tags(1),
typ(node)
404 908
WRITE(bort_str,
'("BUFRLIB: UFBSEQ - INPUT SEQ. MNEM. ",A,'//
405 . .GT.
'" CONSISTS OF",I4," TABLE B MNEM., THE MAX. SPECIFIED IN'//
406 .
' (INPUT) ARGUMENT 3 (",I3,")")') tags(1),nseq,i1
408 910
WRITE(bort_str,
'("BUFRLIB: UFBSEQ - NO. OF ''LEVELS'' WRITTEN '//
409 . .LT.
'(",I5,") NO. REQUESTED (",I5,") - INCOMPLETE WRITE '//
410 .
'(INPUT MNEMONIC IS ",A,")")') iret,i2,tags(1)
412 911
WRITE(bort_str,.GE.
'("BUFRLIB: UFBSEQ - VARIABLE INS1 MUST BE '//
413 .
'ZERO, HERE IT IS",I4," - INPUT MNEMONIC IS ",A)') ins1,tags(1)
subroutine bort(STR)
Log one error message and abort application program.
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
function invtag(NODE, LUN, INV1, INV2)
This function looks for a specified mnemonic within the portion of the current subset buffer bounded ...
function invwin(NODE, LUN, INV1, INV2)
This function looks for a specified node within the portion of the current subset buffer bounded by t...
This module contains declarations for arrays used to store information about the current BUFR message...
integer, dimension(:), allocatable inode
Table A mnemonic for type of BUFR message.
This module contains array and variable declarations used to store the internal jump/link table.
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
character *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
integer, dimension(:), allocatable jmpb
Jump backward indices corresponding to tag and typ:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
integer, dimension(:), allocatable link
Link indices corresponding to tag, typ and jmpb:
This module contains declarations for arrays used to store data values and associated metadata for th...
integer, dimension(:), allocatable nval
Number of data values in BUFR data subset.
real *8, dimension(:,:), allocatable, target val
Data values.
integer, dimension(:,:), allocatable, target inv
Inventory pointer which links each data value to its corresponding node in the internal jump/link tab...
This module declares and initializes the BMISS variable.
real *8, public bmiss
Current placeholder value to represent "missing" data when reading from or writing to BUFR files; thi...
This module declares and initializes the IM8B variable.
logical, public im8b
Status indicator to keep track of whether all future calls to BUFRLIB subroutines and functions from ...
subroutine parstr(STR, TAGS, MTAG, NTAG, SEP, LIMIT80)
Parse a string containing one or more substrings into an array of substrings.
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
recursive subroutine ufbseq(LUNIN, USR, I1, I2, IRET, STR)
This subroutine reads or writes an entire sequence of data values from or to the BUFR data subset tha...
subroutine x48(IIN4, IOUT8, NVAL)
Encode one or more 4-byte integer values as 8-byte integer values.
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.