65 SUBROUTINE ufbmem(LUNIT,INEW,IRET,IUNIT)
75 CHARACTER*128 BORT_STR,ERRSTR
83 CALL openbf(lunit,
'IN',lunit)
108 CALL status(lunit,lun,il,im)
1201
CALL rdmsgw(lunit,mgwa,ier)
121 IF(ier.EQ.-1)
GOTO 100
122 IF(ier.EQ.-2)
GOTO 900
124 IF(
idxmsg(mgwa).EQ.1)
THEN
135 IF(nmsg .GT.
maxmsg) iflg = 1
158100
IF(iflg.EQ.1)
THEN
164 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
165 WRITE ( unit=errstr, fmt=
'(A,A,I8,A)' )
166 .
'BUFRLIB: UFBMEM - THE NO. OF MESSAGES REQUIRED TO STORE ',
167 .
'ALL MESSAGES INTERNALLY EXCEEDS MAXIMUM (',
maxmsg,
168 .
') - INCOMPLETE READ'
170 WRITE ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
171 .
'>>>UFBMEM STORED ',
msgp(0),
' MESSAGES OUT OF ', nmsg,
'<<<'
173 WRITE ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
174 .
'>>>UFBMEM STORED ', mlast0,
' BYTES OUT OF ',
mlast,
'<<<'
176 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
188 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
189 WRITE ( unit=errstr, fmt=
'(A,A,I8,A)' )
190 .
'BUFRLIB: UFBMEM - THE NO. OF BYTES REQUIRED TO STORE ',
191 .
'ALL MESSAGES INTERNALLY EXCEEDS MAXIMUM (',
maxmem,
192 .
') - INCOMPLETE READ'
194 WRITE ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
195 .
'>>>UFBMEM STORED ', mlast0,
' BYTES OUT OF ',
mlast,
'<<<'
197 WRITE ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
198 .
'>>>UFBMEM STORED ',
msgp(0),
' MESSAGES OUT OF ', nmsg,
'<<<'
200 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
218900
WRITE(bort_str,
'("BUFRLIB: UFBMEM - ERROR READING MESSAGE '//
219 .
'NUMBER",I5," INTO MEMORY FROM UNIT",I3)') nmsg+1,lunit
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
subroutine closbf(LUNIT)
This subroutine closes the connection between logical unit LUNIT and the BUFRLIB software.
subroutine cpdxmm(LUNIT)
This subroutine reads an entire DX BUFR table from a specified file into internal arrays.
void cewind(f77int *nfile)
This subroutine rewinds a BUFR file back to its beginning.
void backbufr(f77int *nfile)
This subroutine backspaces a BUFR file by one BUFR message.
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
function idxmsg(MESG)
This function determines whether a given BUFR message contains DX BUFR tables information that was ge...
This module contains array and variable declarations used to store the contents of one or more BUFR f...
integer, dimension(:), allocatable msgs
BUFR messages read from one or more BUFR files.
integer ldxm
Number of array elements filled within mdx (up to a maximum of MXDXW).
integer mlast
Number of array elements filled within msgs (up to a maximum of MAXMEM).
integer ndxm
Number of DX BUFR table messages stored within mdx (up to a maximum of MXDXM).
integer munit
Fortran logical unit number for use in accessing contents of BUFR files within internal memory.
integer ldxts
Number of DX BUFR table that is currently in scope, depending on which BUFR message within msgs is cu...
integer, dimension(:), allocatable msgp
Pointers to the beginning of each message within msgs (up to a maximum of MAXMSG, and where array ele...
integer ndxts
Number of DX BUFR tables represented by the messages within mdx (up to a maximum of MXDXTS).
This module declares and initializes the MAXMEM variable.
integer maxmem
Maximum number of bytes that can be used to store BUFR messages within internal memory.
This module declares and initializes the MAXMSG variable.
integer maxmsg
Maximum number of BUFR messages that can be stored within internal memory.
function nmwrd(MBAY)
GIVEN AN INTEGER ARRAY CONTAINING SECTION ZERO FROM A BUFR MESSAGE, THIS FUNCTION DETERMINES A COUNT ...
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.
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
subroutine ufbmem(LUNIT, INEW, IRET, IUNIT)
This subroutine connects a new system file to the BUFRLIB software for input operations,...