43 RECURSIVE SUBROUTINE ufdump(LUNIT,LUPRT)
62 CHARACTER*20 lchr,pmiss
64 CHARACTER*10 nemo,nemo2,tagrfe
70 CHARACTER*1 cdmf,tab,you
71 equivalence(rval,cval)
73 LOGICAL track,found,rdrv
84 CHARACTER*10 seqnam(mxseq)
88 CHARACTER*10 lsnemo(mxls)
91 DATA pmiss /
' MISSING'/
103 CALL x84(lunit,my_lunit,1)
104 CALL x84(luprt,my_luprt,1)
105 CALL ufdump(my_lunit,my_luprt)
113 lcfmeang = len(cfmeang)
124 CALL status(lunit,lun,il,im)
128 IF(
inode(lun).NE.
inv(1,lun))
GOTO 903
130 WRITE(luout,fmt=
'(/,2A,/)')
'MESSAGE TYPE ',
tag(
inode(lun))
139 IF(cdmf.EQ.
'Y' .AND.
nsub(lun).EQ.1) itmp =
ireadmt(lun)
142 IF(luprt.EQ.0 .AND. mod(nv,20).EQ.0)
THEN
147 print*,
'(<enter> for MORE, q <enter> to QUIT)'
157 print*,
'==> You have chosen to stop the dumping of this subset'
168 IF(ityp.GE.1.AND.ityp.LE.3)
THEN
169 CALL nemtab(lun,nemo,idn,tab,n)
171 numb =
tabb(n,lun)(1:6)
172 desc =
tabb(n,lun)(16:70)
173 unit =
tabb(n,lun)(71:94)
178 IF((ityp.EQ.0).OR.(ityp.EQ.1))
THEN
182 IF((type.EQ.
'REP').OR.(type.EQ.
'DRP').OR.
183 . (type.EQ.
'DRB').OR.(type.EQ.
'DRS'))
THEN
188 IF(nseq.GT.mxseq)
GOTO 904
189 IF(type.EQ.
'REP')
THEN
190 numrep(nseq) =
irf(node)
192 numrep(nseq) = nint(rval)
194 CALL strsuc(nemo,nemo2,lnm2)
195 fmt =
'(11X,A,I6,1X,A)'
196 WRITE(luout,fmt) nemo2(1:lnm2), numrep(nseq),
'REPLICATIONS'
200 IF(numrep(nseq).GT.1)
THEN
213 ELSEIF( ((type.EQ.
'SEQ').OR.(type.EQ.
'RPC').OR.(type.EQ.
'RPS'))
214 . .AND. (nseq.GT.0) )
THEN
220 CALL strsuc(nemo,nemo2,lnm2)
221 DO WHILE ((ii.GE.1).AND.(.NOT.track))
222 IF(nemo2(1:lnm2).EQ.seqnam(ii)(2:lsqnam(ii)-1))
THEN
227 fmt =
'(4X,A,2X,A,2X,A,I6,2X,A)'
228 WRITE(luout,fmt)
'++++++', nemo2(1:lnm2),
229 .
'REPLICATION #', idxrep(ii),
'++++++'
230 IF(idxrep(ii).LT.numrep(ii))
THEN
234 idxrep(ii) = idxrep(ii)+1
247 ELSEIF(ityp.EQ.2)
THEN
256 DO WHILE ((jj.LE.
nnrv).AND.(.NOT.rdrv))
259 desc =
'New reference value for ' // nemo
271 tagrfe =
tag(
inv(nrfe,lun))
273 DO WHILE((jj.GE.1).AND.(desc(jj:jj).EQ.
' '))
276 IF(jj.LE.33) desc(jj+1:jj+15) =
' for ' // tagrfe
281 IF(
ibfms(rval).NE.0)
THEN
285 fmt =
'(A6,2X,A10,2X,A20,2X,A24,6X,A48)'
286 WRITE(luout,fmt) numb,nemo,pmiss,unit,desc
288 fmt =
'(A6,2X,A10,2X,F20.00,2X,A24,6X,A48)'
293 WRITE(fmt(19:20),
'(I2)') max(1,
isc(node))
294 IF(unit(1:4).EQ.
'FLAG')
THEN
299 CALL upftbv(lunit,nemo,rval,mxfv,ifv,nifv)
305 WRITE(fmtf,
'(A2,I1,A4)')
'(I', isz,
',A1)'
306 IF((ipt+isz).LE.24)
THEN
307 WRITE(unit(ipt:ipt+isz),fmtf) ifv(ii),
','
310 unit(12:23) =
'MANY BITS ON'
314 unit(ipt-1:ipt-1) =
')'
318 WRITE(luout,fmt) numb,nemo,rval,unit,desc
320 IF( (unit(1:4).EQ.
'FLAG' .OR. unit(1:4).EQ.
'CODE') .AND.
321 . (cdmf.EQ.
'Y') )
THEN
326 IF(unit(1:4).EQ.
'CODE')
THEN
328 ifv(nifv) = nint(rval)
332 CALL srchtbf_c(idn,ifv(ii),icfdp(1),mxcfdp,-1,
333 . cfmeang,lcfmeang,lcfmg,iersf)
335 WRITE(luout,fmt) ifv(ii),
' = ',cfmeang(1:lcfmg)
336 ELSEIF(iersf.LT.0)
THEN
337 WRITE(luout,fmt) ifv(ii),
' = ',
338 .
'***THIS IS AN ILLEGAL/UNDEFINED VALUE***'
349 DO WHILE((jj.LT.iersf).AND.(ierft.LT.0))
351 CALL numtbd(lun,icfdp(jj),nemod,tab,ierbd)
352 IF((ierbd.GT.0).AND.(tab.EQ.
'B'))
THEN
353 CALL fstag(lun,nemod,-1,nv,nout,ierft)
357 ifvd = nint(
val(nout,lun))
358 IF(jj.GT.1) icfdp(1) = icfdp(jj)
359 CALL srchtbf_c(idn,ifv(ii),icfdp(1),mxcfdp,ifvd,
360 . cfmeang,lcfmeang,lcfmg,iersf)
362 WRITE(luout,fmt) ifv(ii),
' = ',
370 ELSEIF(ityp.EQ.3)
THEN
376 IF(
ibfms(rval).NE.0)
THEN
378 ELSE IF(nchr.LE.8)
THEN
387 DO WHILE((ii.LE.nls).AND.(.NOT.found))
388 IF(nemo.EQ.lsnemo(ii))
THEN
397 IF(nls.GT.mxls)
GOTO 905
402 CALL strsuc(nemo,nemo3,lnm3)
403 lsct(ii) = lsct(ii) + 1
404 WRITE(fmtf,
'(A,I1,A)')
'(2A,I',
isize(lsct(ii)),
')'
405 WRITE(nemo3,fmtf) nemo(1:lnm3),
'#', lsct(ii)
408 CALL readlc(lunit,lchr2,nemo3)
409 IF (
icbfms(lchr2,nchr).NE.0)
THEN
416 IF ( nchr.LE.20 .OR. lchr.EQ.pmiss )
THEN
418 fmt =
'(A6,2X,A10,2X,A20,2X,"(",I2,")",A24,2X,A48)'
419 WRITE(luout,fmt) numb,nemo,lchr,nchr,unit,desc
421 fmt =
'(A6,2X,A10,2X,A,2X,"(",I3,")",A23,2X,A48)'
422 WRITE(luout,fmt) numb,nemo,lchr2(1:nchr),nchr,unit,desc
429 3
FORMAT(/
' >>> END OF SUBSET <<< '/)
435 900
CALL bort(
'BUFRLIB: UFDUMP - INPUT BUFR FILE IS CLOSED, IT '//
436 .
'MUST BE OPEN FOR INPUT')
437 901
CALL bort(
'BUFRLIB: UFDUMP - INPUT BUFR FILE IS OPEN FOR '//
438 .
'OUTPUT, IT MUST BE OPEN FOR INPUT')
439 902
CALL bort(
'BUFRLIB: UFDUMP - A MESSAGE MUST BE OPEN IN INPUT '//
440 .
'BUFR FILE, NONE ARE')
441 903
CALL bort(
'BUFRLIB: UFDUMP - LOCATION OF INTERNAL TABLE FOR '//
442 .
'INPUT BUFR FILE DOES NOT AGREE WITH EXPECTED LOCATION IN '//
443 .
'INTERNAL SUBSET ARRAY')
444 904
CALL bort(
'BUFRLIB: UFDUMP - MXSEQ OVERFLOW')
445 905
CALL bort(
'BUFRLIB: UFDUMP - MXLS OVERFLOW')
subroutine bort(STR)
Log one error message and abort application program.
subroutine fstag(LUN, UTAG, NUTAG, NIN, NOUT, IRET)
This subroutine finds the (NUTAG)th occurrence of mnemonic UTAG within the current overall subset def...
integer function ibfms(R8VAL)
Test whether a real*8 data value is "missing".
recursive function icbfms(STR, LSTR)
This function provides a handy way to check whether a character string returned from a previous call ...
integer function ireadmt(LUN)
Check whether master BUFR tables need to be read from the local file system.
integer function isize(NUM)
This function computes and returns the number of characters needed to encode the input integer NUM as...
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
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.
integer, dimension(:), allocatable nsub
Current subset pointer within message.
This module contains array and variable declarations for use with any 2-03-YYY (change reference valu...
integer nnrv
Number of entries in the jump/link table which contain new reference values (up to a maximum of MXNRV...
integer, dimension(:), allocatable inodnrv
Entries within jump/link table which contain new reference values.
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
character *128, dimension(:,:), allocatable tabb
Table B entries for each internal I/O stream.
This module contains array and variable declarations used to store the internal jump/link table.
integer, dimension(:), allocatable irf
Reference values corresponding to tag and typ:
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
character *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
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...
integer, dimension(:,:), allocatable nrfelm
Referenced data value, for data values which refer to a previous data value in the BUFR data subset v...
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 nemtab(LUN, NEMO, IDN, TAB, IRET)
Get information about a descriptor, based on the mnemonic.
subroutine numtbd(LUN, IDN, NEMO, TAB, IRET)
Search for a Table B or Table D descriptor within the internal DX BUFR tables.
recursive subroutine readlc(LUNIT, CHR, STR)
Read a long character string (greater than 8 bytes) from a data subset.
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
subroutine strsuc(str1, str2, lens)
This subroutine removes leading and trailing blanks from a character string.
recursive subroutine ufdump(LUNIT, LUPRT)
This subroutine prints a verbose listing of the contents of a data subset, including all data values ...
recursive subroutine upftbv(LUNIT, NEMO, VAL, MXIB, IBIT, NIB)
Given a Table B mnemonic with flag table units and a corresponding numerical data value,...
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.