NCEPLIBS-bufr 11.7.1
cpdxmm.f
Go to the documentation of this file.
1C> @file
2C> Read embedded DX BUFR table into internal arrays.
3
4C> This subroutine reads an entire DX BUFR table from a specified
5C> file into internal arrays.
6C>
7C> @author J. Ator
8C> @date 2009-03-23
9C>
10C> @param[in] LUNIT -- integer: Fortran logical unit number for BUFR
11C> file
12C>
13C> <b>Program history log:</b>
14C> | Date | Programmer | Comments |
15C> | -----|------------|----------|
16C> | 2009-03-23 | J. Ator | Original author |
17C> | 2012-09-15 | J. Woollen | Modified for C/I/O/BUFR interface; replace Fortran BACKSPACE with C backbufr() |
18C> | 2014-12-10 | J. Ator | Use modules instead of COMMON blocks |
19C>
20 SUBROUTINE cpdxmm( LUNIT )
21
22 USE modv_mxdxts
23
24 USE moda_mgwa
25 USE moda_msgmem
26
27 COMMON /quiet/ iprt
28
29 character*128 errstr
30
31 LOGICAL DONE
32
33C-----------------------------------------------------------------------
34C-----------------------------------------------------------------------
35
36 IF ( ndxts .GE. mxdxts ) GOTO 900
37
38 ict = 0
39 done = .false.
40 CALL status(lunit,lun,il,im)
41
42C Read a complete dictionary table from LUNIT, as a set of one or
43C more DX dictionary messages.
44
45 DO WHILE ( .NOT. done )
46 CALL rdmsgw ( lunit, mgwa, ier )
47 IF ( ier .EQ. -1 ) THEN
48
49C Don't abort for an end-of-file condition, since it may be
50C possible for a file to end with dictionary messages.
51C Instead, backspace the file pointer and let the calling
52C routine diagnose the end-of-file condition and deal with
53C it as it sees fit.
54
55 CALL backbufr(lun)
56 done = .true.
57 ELSE IF ( ier .EQ. -2 ) THEN
58 GOTO 901
59 ELSE IF ( idxmsg(mgwa) .NE. 1 ) THEN
60
61C This is a non-DX dictionary message. Assume we've reached
62C the end of the dictionary table, and backspace LUNIT so that
63C the next read (e.g. in the calling routine) will get this
64C same message.
65
66 CALL backbufr(lun)
67 done = .true.
68 ELSE IF ( iupbs3(mgwa,'NSUB') .EQ. 0 ) THEN
69
70C This is a DX dictionary message, but it doesn't contain any
71C actual dictionary information. Assume we've reached the end
72C of the dictionary table.
73
74 done = .true.
75 ELSE
76
77C Store this message into MODULE MSGMEM.
78
79 ict = ict + 1
80 IF ( ( ndxm + ict ) .GT. mxdxm ) GOTO 902
81 ipdxm(ndxm+ict) = ldxm + 1
82 lmem = nmwrd(mgwa)
83 IF ( ( ldxm + lmem ) .GT. mxdxw ) GOTO 903
84 DO j = 1, lmem
85 mdx(ldxm+j) = mgwa(j)
86 ENDDO
87 ldxm = ldxm + lmem
88 ENDIF
89 ENDDO
90
91C Update the table information within MODULE MSGMEM.
92
93 IF ( ict .GT. 0 ) THEN
94 ifdxts(ndxts+1) = ndxm + 1
95 icdxts(ndxts+1) = ict
96 ipmsgs(ndxts+1) = msgp(0) + 1
97 ndxm = ndxm + ict
98 ndxts = ndxts + 1
99 IF ( iprt .GE. 2 ) THEN
100 CALL errwrt('+++++++++++++++++++++++++++++++++++++++++++++')
101 WRITE ( unit=errstr, fmt='(A,I3,A,I3,A)')
102 . 'BUFRLIB: CPDXMM - STORED NEW DX TABLE #', ndxts,
103 . ' CONSISTING OF ', ict, ' MESSAGES'
104 CALL errwrt(errstr)
105 CALL errwrt('+++++++++++++++++++++++++++++++++++++++++++++')
106 CALL errwrt(' ')
107 ENDIF
108 ENDIF
109
110 RETURN
111 900 CALL bort('BUFRLIB: CPDXMM - MXDXTS OVERFLOW')
112 901 CALL bort('BUFRLIB: CPDXMM - UNEXPECTED READ ERROR')
113 902 CALL bort('BUFRLIB: CPDXMM - MXDXM OVERFLOW')
114 903 CALL bort('BUFRLIB: CPDXMM - MXDXW OVERFLOW')
115 END
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
Definition: bort.f:23
subroutine cpdxmm(LUNIT)
This subroutine reads an entire DX BUFR table from a specified file into internal arrays.
Definition: cpdxmm.f:21
void backbufr(f77int *nfile)
This subroutine backspaces a BUFR file by one BUFR message.
Definition: cread.c:84
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
Definition: errwrt.f:42
function idxmsg(MESG)
This function determines whether a given BUFR message contains DX BUFR tables information that was ge...
Definition: idxmsg.f:24
function iupbs3(MBAY, S3MNEM)
This function returns a specified value from within Section 3 of a BUFR message.
Definition: iupbs3.f:35
This module contains array and variable declarations used to store the contents of one or more BUFR f...
Definition: moda_msgmem.F:14
integer ldxm
Number of array elements filled within mdx (up to a maximum of MXDXW).
Definition: moda_msgmem.F:73
integer, dimension(:), allocatable ifdxts
Pointers to the beginning of each DX BUFR table within mdx.
Definition: moda_msgmem.F:83
integer, dimension(:), allocatable icdxts
Number of consecutive messages within mdx which constitute each DX BUFR table, beginning with the cor...
Definition: moda_msgmem.F:84
integer, dimension(:), allocatable ipdxm
Pointers to the beginning of each message within mdx.
Definition: moda_msgmem.F:82
integer ndxm
Number of DX BUFR table messages stored within mdx (up to a maximum of MXDXM).
Definition: moda_msgmem.F:74
integer, dimension(:), allocatable mdx
DX BUFR table messages read from one or more BUFR files, for use in decoding the messages in msgs.
Definition: moda_msgmem.F:81
integer, dimension(:), allocatable ipmsgs
Pointers to first message within msgs for which each DX BUFR table applies.
Definition: moda_msgmem.F:85
integer, dimension(:), allocatable msgp
Pointers to the beginning of each message within msgs (up to a maximum of MAXMSG, and where array ele...
Definition: moda_msgmem.F:79
integer ndxts
Number of DX BUFR tables represented by the messages within mdx (up to a maximum of MXDXTS).
Definition: moda_msgmem.F:76
This module declares and initializes the MXDXTS variable.
Definition: modv_MXDXTS.f:13
integer mxdxts
Maximum number of dictionary tables that can be stored for use with BUFR messages in internal memory.
Definition: modv_MXDXTS.f:19
function nmwrd(MBAY)
GIVEN AN INTEGER ARRAY CONTAINING SECTION ZERO FROM A BUFR MESSAGE, THIS FUNCTION DETERMINES A COUNT ...
Definition: nmwrd.f:28
subroutine rdmsgw(LUNIT, MESG, IRET)
THIS SUBROUTINE READS THE NEXT BUFR MESSAGE FROM LOGICAL UNIT LUNIT AS AN ARRAY OF INTEGER WORDS.
Definition: rdmsgw.f:38
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
Definition: status.f:56