86 dimension jdate(5),jdump(5)
107 CALL status(lunit,lun,jl,jm)
109 call openbf(lunit,
'INX',lunit)
1141
CALL rdmsgw(lunit,mgwa,ier)
115 IF(ier.LT.0)
GOTO 200
116 IF(
idxmsg(mgwa).EQ.1)
GOTO 1
122 IF(
iupbs3(mgwa,
'NSUB').NE.0)
GOTO 200
124 igd =
igetdate(mgwa,jdate(1),jdate(2),jdate(3),jdate(4))
125 jdate(5) =
iupbs01(mgwa,
'MINU')
131 CALL rdmsgw(lunit,mgwa,ier)
132 IF(ier.LT.0)
GOTO 200
134 IF(
iupbs3(mgwa,
'NSUB').NE.0)
GOTO 200
136 igd =
igetdate(mgwa,jdump(1),jdump(2),jdump(3),jdump(4))
137 jdump(5) =
iupbs01(mgwa,
'MINU')
142200
IF(iprt.GE.1 .AND. (jdate(1).EQ.-1.OR.jdump(1).EQ.-1))
THEN
143 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
144 IF(jdate(1).EQ.-1)
THEN
145 errstr =
'BUFRLIB: DUMPBF - FIRST EMPTY BUFR MESSAGE '//
146 .
'SECTION 1 DATE COULD NOT BE LOCATED - RETURN WITH '//
150 IF(jdump(1).EQ.-1)
THEN
151 errstr =
'BUFRLIB: DUMPBF - SECOND EMPTY BUFR MESSAGE '//
152 .
'SECTION 1 DATE COULD NOT BE LOCATED - RETURN WITH '//
156 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
165 . (
'BUFRLIB: DUMPBF - INPUT BUFR FILE IS OPEN, IT MUST BE CLOSED')
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 dumpbf(LUNIT, JDATE, JDUMP)
THIS SUBROUTINE RETURNS THE SECTION 1 DATE IN THE FIRST TWO NON-DICTIONARY BUFR MESSAGES IN LOGICAL U...
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...
function igetdate(MBAY, IYR, IMO, IDY, IHR)
This function returns the date-time from within Section 1 of a BUFR message.
function iupbs01(MBAY, S01MNEM)
This function returns a specified value from within Section 0 or Section 1 of a BUFR message.
function iupbs3(MBAY, S3MNEM)
This function returns a specified value from within Section 3 of a BUFR message.
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 wrdlen
This subroutine figures out some important information about the local machine on which the BUFRLIB s...