114 COMMON /usrstr/ nnod,ncon,nods(20),nodc(10),vals(10),kons(10)
118 CHARACTER*128 bort_str,errstr
119 CHARACTER*10 tgs(100)
120 CHARACTER*8 subset,cval
121 equivalence(cval,rval)
122 REAL*8 tab(i1,i2),rval,
ups
127 mps(node) = 2**(ibt(node))-1
132 IF(msgp(0).EQ.0) goto 100
143 CALL
parstr(str,tgs,maxtg,ntg,
' ',.true.)
148 IF(tgs(i).EQ.
'IREC') irec = i
149 IF(tgs(i).EQ.
'ISUB') isub = i
150 IF(tgs(i).EQ.
'ITBL') itbl = i
156 CALL
status(munit,lun,il,im)
159 CALL
rdmemm(imsg,subset,jdate,mret)
160 IF(mret.LT.0) goto 900
163 IF(irec.GT.0) nods(irec) = 0
164 IF(isub.GT.0) nods(isub) = 0
165 IF(itbl.GT.0) nods(itbl) = 0
170 DO WHILE (nsub(lun).LT.msub(lun))
171 IF(iret+1.GT.i2) goto 99
175 nods(i) = abs(nods(i))
179 mbit = mbyt(lun)*8+16
183 20
IF(n+1.LE.nval(lun))
THEN
188 IF(itp(node).EQ.1)
THEN
189 CALL
upbb(ival,nbit,mbit,mbay(1,lun))
193 IF(nods(i).EQ.node)
THEN
194 IF(itp(node).EQ.1)
THEN
195 CALL
upbb(ival,nbit,mbit,mbay(1,lun))
197 ELSEIF(itp(node).EQ.2)
THEN
198 CALL
upbb(ival,nbit,mbit,mbay(1,lun))
199 IF(ival.LT.mps(node)) tab(i,iret) =
ups(ival,node)
200 ELSEIF(itp(node).EQ.3)
THEN
203 CALL
upc(cval,nbit/8,mbay(1,lun),kbit,.true.)
211 IF(nods(i).GT.0) goto 20
219 CALL
upb(nbyt,16,mbay(1,lun),ibit)
220 mbyt(lun) = mbyt(lun) + nbyt
221 nsub(lun) = nsub(lun) + 1
222 IF(irec.GT.0) tab(irec,iret) = nmsg(lun)
223 IF(isub.GT.0) tab(isub,iret) = nsub(lun)
224 IF(itbl.GT.0) tab(itbl,iret) = ldxts
234 99 CALL
rdmemm(0,subset,jdate,mret)
237 CALL
rdmemm(imsg,subset,jdate,mret)
238 IF(mret.LT.0) goto 900
239 nrep = nrep+
nmsub(munit)
242 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
243 WRITE ( unit=errstr, fmt=
'(A,A,I8,A,A)' )
244 .
'BUFRLIB: UFBTAM - THE NO. OF DATA SUBSETS IN MEMORY ',
245 . .GT.
'IS LIMIT OF ', i2,
' IN THE 3RD ARG. (INPUT) - ',
248 WRITE ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
249 .
'>>>UFBTAM STORED ', iret,
' REPORTS OUT OF ', nrep,
'<<<'
251 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
258 200 CALL
rdmemm(0,subset,jdate,mret)
264 900
WRITE(bort_str,
'("BUFRLIB: UFBTAM - HIT END-OF-FILE READING '//
265 .
'MESSAGE NUMBER",I5," IN INTERNAL MEMORY")') imsg
subroutine upbb(NVAL, NBITS, IBIT, IBAY)
THIS SUBROUTINE UNPACKS AND RETURNS A BINARY INTEGER CONTAINED WITHIN NBITS BITS OF IBAY...
subroutine upb(NVAL, NBITS, IBAY, IBIT)
THIS SUBROUTINE UNPACKS AND RETURNS A BINARY INTEGER CONTAINED WITHIN NBITS BITS OF IBAY...
subroutine parstr(STR, TAGS, MTAG, NTAG, SEP, LIMIT80)
THIS SUBROUTINE PARSES A STRING CONTAINING ONE OR MORE SUBSTRINGS INTO AN ARRAY OF SUBSTRINGS...
subroutine usrtpl(LUN, INVN, NBMP)
THIS SUBROUTINE STORES THE SUBSET TEMPLATE INTO INTERNAL SUBSET ARRAYS IN MODULE USRINT FOR CASES OF ...
This module declares and initializes the BMISS variable.
This module contains array and variable declarations used to store the contents of one or more BUFR f...
subroutine upc(CHR, NCHR, IBAY, IBIT, CNVNULL)
THIS SUBROUTINE UNPACKS AND RETURNS A CHARACTER STRING OF LENGTH NCHR CONTAINED WITHIN NCHR BYTES OF ...
subroutine rdmemm(IMSG, SUBSET, JDATE, IRET)
This subroutine reads a specified BUFR message from internal arrays in memory, so that it is now in s...
subroutine string(STR, LUN, I1, IO)
THIS SUBROUTINE CHECKS TO SEE IF A USER-SPECIFIED CHARACTER STRING IS IN THE STRING CACHE (ARRAYS IN ...
This module contains array and variable declarations used to store the internal jump/link table...
subroutine ufbtam(TAB, I1, I2, IRET, STR)
THIS SUBROUTINE READS SPECIFIED VALUES INTO INTERNAL ARRAYS FROM ALL DATA SUBSETS IN BUFR MESSAGES ST...
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
function nmsub(LUNIT)
This function returns the total number of data subsets available within the BUFR message that was mos...
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
This module contains array and variable declarations used to store BUFR messages internally for multi...
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...