49 SUBROUTINE rdmemm(IMSG,SUBSET,JDATE,IRET)
58 CHARACTER*128 BORT_STR,ERRSTR
75 IF(imsg.EQ.0 .OR.imsg.GT.
msgp(0))
THEN
78 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
80 errstr =
'BUFRLIB: RDMEMM - REQUESTED MEMORY MESSAGE '//
81 .
'NUMBER {FIRST (INPUT) ARGUMENT} IS 0, RETURN WITH '//
84 WRITE ( unit=errstr, fmt=
'(A,I6,A,I6,A)' )
85 .
'BUFRLIB: RDMEMM - REQ. MEMORY MESSAGE #', imsg,
86 .
' {= 1ST (INPUT) ARG.} > # OF MESSAGES IN MEMORY (',
87 .
msgp(0),
'), RETURN WITH IRET = -1'
90 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
104 DO WHILE ((.NOT.known).AND.(jj.GE.1))
105 IF (
ipmsgs(jj).LE.imsg)
THEN
111 IF (.NOT.known)
GOTO 902
115 IF (jj.NE.
ldxts)
THEN
120 CALL errwrt(
'+++++++++++++++++++++++++++++++++++++++++++++')
121 WRITE ( unit=errstr, fmt=
'(A,I3,A,I3,A,I6)' )
122 .
'BUFRLIB: RDMEMM - RESETTING TO USE DX TABLE #', jj,
123 .
' INSTEAD OF DX TABLE #',
ldxts,
124 .
' FOR REQUESTED MESSAGE #', imsg
126 CALL errwrt(
'+++++++++++++++++++++++++++++++++++++++++++++')
156 IF(imsg.LT.
msgp(0)) lptr =
msgp(imsg+1)-iptr
167 CALL cktaba(lun,subset,jdate,jret)
174900
CALL bort(
'BUFRLIB: RDMEMM - INPUT BUFR FILE IS CLOSED, IT '//
175 .
'MUST BE OPEN FOR INPUT')
176901
CALL bort(
'BUFRLIB: RDMEMM - INPUT BUFR FILE IS OPEN FOR '//
177 .
'OUTPUT, IT MUST BE OPEN FOR INPUT')
178902
WRITE(bort_str,
'("BUFRLIB: RDMEMM - UNKNOWN DX TABLE FOR '//
179 .
'REQUESTED MESSAGE #",I5)') imsg
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
subroutine cktaba(LUN, SUBSET, JDATE, IRET)
THIS SUBROUTINE PARSES THE TABLE A MNEMONIC AND THE DATE OUT OF SECTION 1 OF A BUFR MESSAGE PREVIOUSL...
subroutine dxinit(LUN, IOI)
THIS SUBROUTINE INITIALIZES THE INTERNAL ARRAYS (IN MODULE TABABD) HOLDING THE DICTIONARY TABLE.
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
subroutine makestab
THIS SUBROUTINE CONSTRUCTS AN INTERNAL JUMP/LINK TABLE WITHIN MODULE TABLES, USING THE INFORMATION WI...
This module contains array and variable declarations used to store BUFR messages internally for multi...
integer, dimension(:,:), allocatable mbay
Current BUFR message for each internal I/O stream.
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, dimension(:), allocatable ifdxts
Pointers to the beginning of each DX BUFR table within mdx.
integer mlast
Number of array elements filled within msgs (up to a maximum of MAXMEM).
integer, dimension(:), allocatable icdxts
Number of consecutive messages within mdx which constitute each DX BUFR table, beginning with the cor...
integer, dimension(:), allocatable ipdxm
Pointers to the beginning of each message within mdx.
integer ndxm
Number of DX BUFR table messages stored within mdx (up to a maximum of MXDXM).
integer, dimension(:), allocatable mdx
DX BUFR table messages read from one or more BUFR files, for use in decoding the messages in msgs.
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 ipmsgs
Pointers to first message within msgs for which each DX BUFR table applies.
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).
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 status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
subroutine stbfdx(LUN, MESG)
THIS SUBROUTINE COPIES A BUFR TABLE (DICTIONARY) MESSAGE FROM THE INPUT ARRAY MESG INTO THE INTERNAL ...
subroutine wtstat(LUNIT, LUN, IL, IM)
This subroutine can be used to connect or disconnect a specified Fortran logical unit number to/from ...