51 SUBROUTINE ufbmex(LUNIT,LUNDX,INEW,IRET,MESG)
58 CHARACTER*128 bort_str,errstr
68 CALL
openbf(lunit,
'IN',lundx)
95 1 CALL
rdmsgw(lunit,mgwa,ier)
96 IF(ier.EQ.-1) goto 100
97 IF(ier.EQ.-2) goto 900
100 mesg(nmsg) =
iupbs01(mgwa,
'MTYP')
101 IF(nmsg .GT.maxmsg) iflg = 1
103 IF(lmem+mlast.GT.maxmem) iflg = 2
108 msgs(mlast+i) = mgwa(i)
124 100
IF(iflg.EQ.1)
THEN
130 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
131 WRITE ( unit=errstr, fmt=
'(A,A,I8,A)' )
132 .
'BUFRLIB: UFBMEX - THE NO. OF MESSAGES REQUIRED TO STORE ',
133 .
'ALL MESSAGES INTERNALLY EXCEEDS MAXIMUM (', maxmsg,
134 .
') - INCOMPLETE READ'
136 WRITE ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
137 .
'>>>UFBMEX STORED ', msgp(0),
' MESSAGES OUT OF ', nmsg,
'<<<'
139 WRITE ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
140 .
'>>>UFBMEX STORED ', mlast0,
' BYTES OUT OF ', mlast,
'<<<'
142 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
154 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
155 WRITE ( unit=errstr, fmt=
'(A,A,I8,A)' )
156 .
'BUFRLIB: UFBMEX - THE NO. OF BYTES REQUIRED TO STORE ',
157 .
'ALL MESSAGES INTERNALLY EXCEEDS MAXIMUM (', maxmem,
158 .
') - INCOMPLETE READ'
160 WRITE ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
161 .
'>>>UFBMEX STORED ', mlast0,
' BYTES OUT OF ', mlast,
'<<<'
163 WRITE ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
164 .
'>>>UFBMEX STORED ', msgp(0),
' MESSAGES OUT OF ', nmsg,
'<<<'
166 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
175 IF(munit.NE.0) CALL
closbf(lunit)
176 IF(munit.EQ.0) munit = lunit
184 900
WRITE(bort_str,
'("BUFRLIB: UFBMEX - ERROR READING MESSAGE '//
185 .
'NUMBER",I5," INTO MEMORY FROM UNIT",I3)') nmsg+1,lunit
subroutine ufbmex(LUNIT, LUNDX, INEW, IRET, MESG)
This subroutine connects a new system file to the BUFRLIB software for input operations, then reads the entire file contents into internal arrays so that any of the individual BUFR messages can later be accessed from memory, instead of having to read them one at a time sequentially from the system file.
function nmwrd(MBAY)
GIVEN AN INTEGER ARRAY CONTAINING SECTION ZERO FROM A BUFR MESSAGE, THIS FUNCTION DETERMINES A COUNT ...
subroutine closbf(LUNIT)
This subroutine closes the connection between logical unit LUNIT and the BUFRLIB software.
subroutine openbf(LUNIT, IO, LUNDX)
This subroutine connects a new file to the BUFRLIB software for input or output operations.
subroutine rdmsgw(LUNIT, MESG, IRET)
THIS SUBROUTINE READS THE NEXT BUFR MESSAGE FROM LOGICAL UNIT LUNIT AS AN ARRAY OF INTEGER WORDS...
This module contains array and variable declarations used to store the contents of one or more BUFR f...
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
function iupbs01(MBAY, S01MNEM)
This function returns a specified value from within Section 0 or Section 1 of a BUFR message...