NCEPLIBS-bufr  12.0.0
msgwrt.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Finalize a BUFR message for output and write the message to
3 C> a BUFR file.
4 C>
5 C> @author J. Woollen @date 1994-01-06
6 
7 C> Perform final checks and updates on a BUFR message
8 C> before writing it to a specified Fortran logical unit.
9 C>
10 C> These final checks and updates include:
11 C> - Standardizing the BUFR message, if requested via a previous call
12 C> subroutine stdmsg()
13 C> - Converting the BUFR message from edition 3 to edition 4, if
14 C> requested via a previous call to subroutine pkvs01()
15 C> - Storing any customized values into Section 0 or Section 1 of the
16 C> BUFR message, if requested via one or more previous calls to
17 C> subroutine pkvs01()
18 C> - Storing a tank receipt time into Section 1 of the BUFR message,
19 C> if requested via a previous call to subroutine strcpt()
20 C> - For edition 3 BUFR messages, ensuring each section of the message
21 C> contains an even number of bytes
22 C> - Storing '7777' into the last four bytes of the BUFR message, and
23 C> storing the final message length in Section 0
24 C> - Appending zeroed-out bytes after the end of the BUFR message, up
25 C> to the next machine word boundary
26 C> - Encapsulating the BUFR message with IEEE Fortran control words,
27 C> if requested via a previous call to subroutine setblock()
28 C> - Storing a copy of the final message into internal arrays for
29 C> possible later retrival via subroutine writsa()
30 C>
31 C> @param[in] LUNIT -- integer: Fortran logical unit number for BUFR
32 C> file
33 C> @param[in] MESG -- integer(*): BUFR message
34 C> @param[in] MGBYT -- integer: Size (in bytes) of BUFR message
35 C>
36 C> @author J. Woollen @date 1994-01-06
37  SUBROUTINE msgwrt(LUNIT,MESG,MGBYT)
38 
39  use bufrlib
40 
41  USE modv_mxmsgl
42 
43  USE moda_nulbfr
44  USE moda_bufrmg
45  USE moda_mgwa
46  USE moda_mgwb
47  USE moda_s01cm
48 
49  COMMON /quiet / iprt
50  COMMON /msgstd/ csmf
51  COMMON /tnkrcp/ itryr,itrmo,itrdy,itrhr,itrmi,ctrt
52 
53  CHARACTER*128 ERRSTR
54 
55  CHARACTER*4 BUFR,SEVN
56  CHARACTER*1 CSMF
57  CHARACTER*1 CTRT
58  dimension mesg(*)
59  dimension iec0(2)
60 
61  DATA bufr/'BUFR'/
62  DATA sevn/'7777'/
63 
64 C-----------------------------------------------------------------------
65 C-----------------------------------------------------------------------
66 
67 C MAKE A LOCAL COPY OF THE INPUT MESSAGE FOR USE WITHIN THIS
68 C SUBROUTINE, SINCE CALLS TO ANY OR ALL OF THE SUBROUTINES STNDRD,
69 C CNVED4, PKBS1, ATRCPT, ETC. MAY END UP MODIFYING THE MESSAGE
70 C BEFORE IT FINALLY GETS WRITTEN OUT TO LUNIT.
71 
72  mbyt = mgbyt
73 
74  iec0(1) = mesg(1)
75  iec0(2) = mesg(2)
76  ibit = 32
77  CALL pkb(mbyt,24,iec0,ibit)
78 
79  DO ii = 1, nmwrd(iec0)
80  mgwa(ii) = mesg(ii)
81  ENDDO
82 
83 C OVERWRITE ANY VALUES WITHIN SECTION 0 OR SECTION 1 THAT WERE
84 C REQUESTED VIA PREVIOUS CALLS TO BUFR ARCHIVE LIBRARY SUBROUTINE
85 C PKVS01. IF A REQUEST WAS MADE TO CHANGE THE BUFR EDITION NUMBER
86 C TO 4, THEN ACTUALLY CONVERT THE MESSAGE AS WELL.
87 
88  IF(ns01v.GT.0) THEN
89  DO i=1,ns01v
90  IF(cmnem(i).EQ.'BEN') THEN
91  IF(ivmnem(i).EQ.4) THEN
92 
93 C INSTALL SECTION 0 BYTE COUNT FOR USE BY SUBROUTINE CNVED4.
94 
95  ibit = 32
96  CALL pkb(mbyt,24,mgwa,ibit)
97 
98  CALL cnved4(mgwa,mxmsgld4,mgwb)
99 
100 C COMPUTE MBYT FOR THE NEW EDITION 4 MESSAGE.
101 
102  mbyt = iupbs01(mgwb,'LENM')
103 
104 C COPY THE MGWB ARRAY BACK INTO MGWA.
105 
106  DO ii = 1, nmwrd(mgwb)
107  mgwa(ii) = mgwb(ii)
108  ENDDO
109  ENDIF
110  ELSE
111 
112 C OVERWRITE THE REQUESTED VALUE.
113 
114  CALL pkbs1(ivmnem(i),mgwa,cmnem(i))
115  ENDIF
116  ENDDO
117  ENDIF
118 
119 C "STANDARDIZE" THE MESSAGE IF REQUESTED VIA COMMON /MSGSTD/.
120 C HOWEVER, WE DO NOT WANT TO DO THIS IF THE MESSAGE CONTAINS BUFR
121 C TABLE (DX) INFORMATION, IN WHICH CASE IT IS ALREADY "STANDARD".
122 
123  IF ( ( csmf.EQ.'Y' ) .AND. ( idxmsg(mgwa).NE.1 ) ) THEN
124 
125 C INSTALL SECTION 0 BYTE COUNT AND SECTION 5 '7777' INTO THE
126 C ORIGINAL MESSAGE. THIS IS NECESSARY BECAUSE SUBROUTINE STNDRD
127 C REQUIRES A COMPLETE AND WELL-FORMED BUFR MESSAGE AS ITS INPUT.
128 
129  ibit = 32
130  CALL pkb(mbyt,24,mgwa,ibit)
131  ibit = (mbyt-4)*8
132  CALL pkc(sevn,4,mgwa,ibit)
133 
134  CALL stndrd(lunit,mgwa,mxmsgld4,mgwb)
135 
136 C COMPUTE MBYT FOR THE NEW "STANDARDIZED" MESSAGE.
137 
138  mbyt = iupbs01(mgwb,'LENM')
139 
140 C COPY THE MGWB ARRAY BACK INTO MGWA.
141 
142  DO ii = 1, nmwrd(mgwb)
143  mgwa(ii) = mgwb(ii)
144  ENDDO
145  ENDIF
146 
147 C APPEND THE TANK RECEIPT TIME TO SECTION 1 IF REQUESTED VIA
148 C COMMON /TNKRCP/, UNLESS THE MESSAGE CONTAINS BUFR TABLE (DX)
149 C INFORMATION.
150 
151  IF ( ( ctrt.EQ.'Y' ) .AND. ( idxmsg(mgwa).NE.1 ) ) THEN
152 
153 C INSTALL SECTION 0 BYTE COUNT FOR USE BY SUBROUTINE ATRCPT.
154 
155  ibit = 32
156  CALL pkb(mbyt,24,mgwa,ibit)
157 
158  CALL atrcpt(mgwa,mxmsgld4,mgwb)
159 
160 C COMPUTE MBYT FOR THE REVISED MESSAGE.
161 
162  mbyt = iupbs01(mgwb,'LENM')
163 
164 C COPY THE MGWB ARRAY BACK INTO MGWA.
165 
166  DO ii = 1, nmwrd(mgwb)
167  mgwa(ii) = mgwb(ii)
168  ENDDO
169  ENDIF
170 
171 C GET THE SECTION LENGTHS.
172 
173  CALL getlens(mgwa,4,len0,len1,len2,len3,len4,l5)
174 
175 C DEPENDING ON THE EDITION NUMBER OF THE MESSAGE, WE NEED TO ENSURE
176 C THAT EACH SECTION WITHIN THE MESSAGE HAS AN EVEN NUMBER OF BYTES.
177 
178  IF(iupbs01(mgwa,'BEN').LT.4) THEN
179  IF(mod(len1,2).NE.0) GOTO 901
180  IF(mod(len2,2).NE.0) GOTO 902
181  IF(mod(len3,2).NE.0) GOTO 903
182  IF(mod(len4,2).NE.0) THEN
183 
184 C PAD SECTION 4 WITH AN ADDITIONAL BYTE
185 C THAT IS ZEROED OUT.
186 
187  iad4 = len0+len1+len2+len3
188  iad5 = iad4+len4
189  ibit = iad4*8
190  len4 = len4+1
191  CALL pkb(len4,24,mgwa,ibit)
192  ibit = iad5*8
193  CALL pkb(0,8,mgwa,ibit)
194  mbyt = mbyt+1
195  ENDIF
196  ENDIF
197 
198 C WRITE SECTION 0 BYTE COUNT AND SECTION 5
199 C ----------------------------------------
200 
201  ibit = 0
202  CALL pkc(bufr, 4,mgwa,ibit)
203  CALL pkb(mbyt,24,mgwa,ibit)
204 
205  kbit = (mbyt-4)*8
206  CALL pkc(sevn, 4,mgwa,kbit)
207 
208 C ZERO OUT THE EXTRA BYTES WHICH WILL BE WRITTEN
209 C ----------------------------------------------
210 
211 C I.E. SINCE THE BUFR MESSAGE IS STORED WITHIN THE INTEGER ARRAY
212 C MGWA(*) (RATHER THAN WITHIN A CHARACTER ARRAY), WE NEED TO MAKE
213 C SURE THAT THE "7777" IS FOLLOWED BY ZEROED-OUT BYTES UP TO THE
214 C BOUNDARY OF THE LAST MACHINE WORD THAT WILL BE WRITTEN OUT.
215 
216  CALL padmsg(mgwa,mxmsgld4,npbyt)
217 
218 C WRITE THE MESSAGE PLUS PADDING TO A WORD BOUNDARY IF NULL(LUN) = 0
219 C ------------------------------------------------------------------
220 
221  mwrd = nmwrd(mgwa)
222  CALL status(lunit,lun,il,im)
223  IF(null(lun).EQ.0) THEN
224  CALL blocks(mgwa,mwrd)
225  CALL cwrbufr_c(lun,mgwa,mwrd)
226  ENDIF
227 
228  IF(iprt.GE.2) THEN
229  CALL errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
230  WRITE ( unit=errstr, fmt='(A,I4,A,I7)')
231  . 'BUFRLIB: MSGWRT: LUNIT =', lunit, ', BYTES =', mbyt+npbyt
232  CALL errwrt(errstr)
233  CALL errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
234  CALL errwrt(' ')
235  ENDIF
236 
237 C SAVE A MEMORY COPY OF THIS MESSAGE, UNLESS IT'S A DX MESSAGE
238 C ------------------------------------------------------------
239 
240  IF(idxmsg(mgwa).NE.1) THEN
241 
242 C STORE A COPY OF THIS MESSAGE WITHIN MODULE BUFRMG,
243 C FOR POSSIBLE LATER RETRIEVAL DURING A FUTURE CALL TO
244 C SUBROUTINE WRITSA.
245 
246  msglen(lun) = mwrd
247  DO i=1,msglen(lun)
248  msgtxt(i,lun) = mgwa(i)
249  ENDDO
250  ENDIF
251 
252 C EXITS
253 C -----
254 
255  RETURN
256 901 CALL bort
257  . ('BUFRLIB: MSGWRT - LENGTH OF SECTION 1 IS NOT A MULTIPLE OF 2')
258 902 CALL bort
259  . ('BUFRLIB: MSGWRT - LENGTH OF SECTION 2 IS NOT A MULTIPLE OF 2')
260 903 CALL bort
261  . ('BUFRLIB: MSGWRT - LENGTH OF SECTION 3 IS NOT A MULTIPLE OF 2')
262  END
recursive subroutine atrcpt(MSGIN, LMSGOT, MSGOT)
This subroutine reads an input message and outputs an equivalent BUFR message with a tank receipt tim...
Definition: atrcpt.f:30
subroutine blocks(MBAY, MWRD)
This subroutine encapsulates a BUFR message with IEEE Fortran control words as specified via the most...
Definition: blocks.f:41
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
recursive subroutine cnved4(MSGIN, LMSGOT, MSGOT)
This subroutine reads an input BUFR message encoded using BUFR edition 3 and outputs an equivalent BU...
Definition: cnved4.f:31
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
Definition: errwrt.f:36
recursive subroutine getlens(MBAY, LL, LEN0, LEN1, LEN2, LEN3, LEN4, LEN5)
This subroutine reads the lengths of all of the individual sections of a given BUFR message,...
Definition: getlens.f:36
recursive function idxmsg(MESG)
Check whether a BUFR message contains DX BUFR tables information.
Definition: idxmsg.f:23
recursive function iupbs01(MBAY, S01MNEM)
Read a data value from Section 0 or Section 1 of a BUFR message.
Definition: iupbs01.f:69
subroutine msgwrt(LUNIT, MESG, MGBYT)
Perform final checks and updates on a BUFR message before writing it to a specified Fortran logical u...
Definition: msgwrt.f:38
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
Definition: bufrlib.F90:11
This module contains arrays used to store, for each output I/O stream, a copy of the BUFR message tha...
integer, dimension(:), allocatable msglen
Length (in integers) of BUFR message most recently written to each output I/O stream.
integer, dimension(:,:), allocatable msgtxt
BUFR message most recently written to each output I/O stream.
This module contains a declaration for an array used by various subroutines and functions to hold a t...
integer, dimension(:), allocatable mgwa
Temporary working copy of BUFR message.
This module contains a declaration for an array used by various subroutines and functions to hold a t...
integer, dimension(:), allocatable mgwb
Temporary working copy of BUFR message.
This module contains an array declaration used to store a switch for each internal I/O stream index,...
integer, dimension(:), allocatable null
Output switch for each internal I/O stream index:
This module contains array and variable declarations used to store custom values for certain mnemonic...
integer, dimension(:), allocatable ivmnem
Custom values for use within Sections 0 and 1 of all future output BUFR messages written to all Fortr...
integer ns01v
Number of custom values stored.
character *8, dimension(:), allocatable cmnem
Section 0 and 1 mnemonics corresponding to ivmnem.
This module declares and initializes the MXMSGL variable.
integer mxmsgld4
The value of mxmsgl divided by 4.
recursive function nmwrd(MBAY)
Given an integer array containing Section 0 from a BUFR message, this function determines the array s...
Definition: nmwrd.f:24
subroutine padmsg(MESG, LMESG, NPBYT)
This subroutine pads a BUFR message with zeroed-out bytes from the end of the message up to the next ...
Definition: padmsg.f:19
subroutine pkb(NVAL, NBITS, IBAY, IBIT)
This subroutine encodes an integer value within a specified number of bits of an integer array,...
Definition: pkb.f:28
recursive subroutine pkbs1(IVAL, MBAY, S1MNEM)
This subroutines writes a specified value into a specified location within Section 1 of a BUFR messag...
Definition: pkbs1.f:51
subroutine pkc(CHR, NCHR, IBAY, IBIT)
Encode a character string within an integer array.
Definition: pkc.f:31
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
Definition: status.f:36
recursive subroutine stndrd(LUNIT, MSGIN, LMSGOT, MSGOT)
This subroutine performs the same function as subroutine stdmsg(), except that it operates on a BUFR ...
Definition: stndrd.f:28