70 SUBROUTINE ufbget(LUNIT,TAB,I1,IRET,STR)
79 COMMON /usrstr/ nnod,ncon,nods(20),nodc(10),ivls(10),kons(10)
83 equivalence(cval,rval)
85 real*8 rval,tab(i1),
ups
99 CALL status(lunit,lun,il,im)
107 IF(nsub(lun).EQ.msub(lun))
THEN
122 mbit(n) =
mbyt(lun)*8 + 16
128 mbit(n) = mbit(n-1)+nbit(n-1)
129 IF(node.EQ.nods(nnod))
THEN
132 ELSEIF(
itp(node).EQ.1)
THEN
133 CALL upb8(ival,nbit(n),mbit(n),
mbay(1,lun))
134 nbmp=ival;
CALL usrtpl(lun,n,nbmp)
145 invn =
invwin(node,lun,1,nval(lun))
147 CALL upb8(ival,nbit(invn),mbit(invn),
mbay(1,lun))
148 IF(
itp(node).EQ.1)
THEN
150 ELSEIF(
itp(node).EQ.2)
THEN
151 IF(ival.LT.2_8**(
ibt(node))-1) tab(i) =
ups(ival,node)
152 ELSEIF(
itp(node).EQ.3)
THEN
155 CALL upc(cval,nbit(invn)/8,
mbay(1,lun),kbit,.true.)
167900
CALL bort(
'BUFRLIB: UFBGET - INPUT BUFR FILE IS CLOSED, IT MUST'//
168 .
' BE OPEN FOR INPUT')
169901
CALL bort(
'BUFRLIB: UFBGET - INPUT BUFR FILE IS OPEN FOR OUTPUT'//
170 .
', IT MUST BE OPEN FOR INPUT')
171902
CALL bort(
'BUFRLIB: UFBGET - A MESSAGE MUST BE OPEN IN INPUT '//
172 .
'BUFR FILE, NONE ARE')
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
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 array and variable declarations used to store BUFR messages internally for multi...
integer, dimension(:), allocatable mbyt
Length (in bytes) of current BUFR message for each internal I/O stream.
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 status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
subroutine string(STR, LUN, I1, IO)
THIS SUBROUTINE CHECKS TO SEE IF A USER-SPECIFIED CHARACTER STRING IS IN THE STRING CACHE (ARRAYS IN ...
subroutine ufbget(LUNIT, TAB, I1, IRET, STR)
THIS SUBROUTINE UNPACKS AND RETURNS THE VALUES FOR ONE- DIMENSIONAL DESCRIPTORS IN THE INPUT STRING W...
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...
subroutine usrtpl(LUN, INVN, NBMP)
THIS SUBROUTINE STORES THE SUBSET TEMPLATE INTO INTERNAL SUBSET ARRAYS IN MODULE USRINT FOR CASES OF ...