68 equivalence(cval,rval)
91 CALL upb8(ival(n),nbit(n),mbit(n),
mbay(1,lun))
100 IF(
itp(node).EQ.1)
THEN
105 ELSEIF(
itp(node).EQ.2)
THEN
109 IF (ival(n).LT.2_8**
ibt(node)-1)
THEN
110 val(n,lun) =
ups(ival(n),node)
114 ELSEIF(
itp(node).EQ.3)
THEN
124 nbt = min(8,nbit(n)/8)
125 CALL upc(cval,nbt,
mbay(1,lun),kbit,.true.)
126 IF (nbit(n).LE.64 .AND.
icbfms(cval,nbt).NE.0)
THEN
134 ibit = nbit(nval(lun))+mbit(nval(lun))
integer function icbfms(STR, LSTR)
This function provides a handy way to check whether a character string returned from a previous call ...
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:
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
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...
subroutine rcstpl(LUN, IRET)
THIS SUBROUTINE STORES THE SUBSET TEMPLATE INTO INTERNAL SUBSET ARRAYS IN MODULES USRINT AND USRBIT.
subroutine rdtree(LUN, IRET)
THIS SUBROUTINE UNPACKS THE NEXT SUBSET FROM THE INTERNAL UNCOMPRESSED MESSAGE BUFFER (ARRAY MBAY IN ...
subroutine upb8(nval, nbits, ibit, ibay)
THIS SUBROUTINE UNPACKS AND RETURNS AN 8-BYTE INTEGER CONTAINED WITHIN NBITS BITS OF IBAY,...
subroutine upc(CHR, NCHR, IBAY, IBIT, CNVNULL)
THIS SUBROUTINE UNPACKS AND RETURNS A CHARACTER STRING OF LENGTH NCHR CONTAINED WITHIN NCHR BYTES OF ...
real *8 function ups(IVAL, NODE)
THIS FUNCTION UNPACKS A REAL*8 USER VALUE FROM A PACKED BUFR INTEGER BY APPLYING THE PROPER SCALE AND...