49 SUBROUTINE datebf(LUNIT,MEAR,MMON,MDAY,MOUR,IDATE)
62 IF ( .NOT.
ALLOCATED(mgwa) )
THEN
63 CALL openbf(lunit,
'FIRST',lunit)
71 CALL status(lunit,lun,jl,jm)
73 CALL openbf(lunit,
'INX',lunit)
781
CALL rdmsgw(lunit,mgwa,ier)
80 IF(
idxmsg(mgwa).EQ.1)
GOTO 1
82 idate =
igetdate(mgwa,mear,mmon,mday,mour)
84100
IF(iprt.GE.1 .AND. idate.EQ.-1)
THEN
85 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
86 errstr =
'BUFRLIB: DATEBF - SECTION 1 DATE COULD NOT BE '//
87 .
'LOCATED - RETURN WITH IDATE = -1'
89 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
99 . (
'BUFRLIB: DATEBF - 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 datebf(LUNIT, MEAR, MMON, MDAY, MOUR, IDATE)
This subroutine reads and returns the Section 1 date-time from the first data message of a BUFR file,...
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.
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 ...