27 RECURSIVE SUBROUTINE stndrd(LUNIT,MSGIN,LMSGOT,MSGOT)
35 COMMON /hrdwrd/ nbytw,nbitw,iord(8)
37 dimension msgin(*),msgot(*)
39 CHARACTER*128 bort_str
55 CALL x84 ( lunit, my_lunit, 1 )
56 CALL x84 ( lmsgot, my_lmsgot, 1 )
57 CALL stndrd ( my_lunit, msgin, my_lmsgot*2, msgot )
66 CALL status(lunit,lun,il,im)
72 CALL getlens(msgin,5,len0,len1,len2,len3,len4,len5)
77 lenn = len0+len1+len2+len3+len4+len5
81 IF(lenn.NE.lenm)
GOTO 901
84 CALL upc(sevn,4,msgin,mbit,.true.)
85 IF(sevn.NE.
'7777')
GOTO 902
90 mxbyto = (lmsgot*nbytw) - 8
93 IF(lbyto.GT.mxbyto)
GOTO 905
94 CALL mvb(msgin,1,msgot,1,lbyto)
103 DO WHILE ((.NOT.found).AND.(ii.GE.8))
104 isub =
iupb(msgin,iad3+ii,16)
105 CALL numtab(lun,isub,subset,tab,itab)
106 IF((itab.NE.0).AND.(tab.EQ.
'D'))
THEN
107 CALL nemtbax(lun,subset,mtyp,msbt,inod)
108 IF(inod.NE.0) found = .true.
112 IF(.NOT.found)
GOTO 903
138 lbyto = lbyto + len3 - 7
139 IF(lbyto.GT.mxbyto)
GOTO 905
145 CALL pkb(icd(n),16,msgot,ibit)
152 CALL pkb(0,8,msgot,ibit)
158 CALL pkb(len3,24,msgot,ibit)
163 IF(
iupbs3(msgin,
'ICMP').EQ.1)
THEN
168 IF((lbyto+len4+4).GT.mxbyto)
GOTO 905
170 CALL mvb(msgin,iad4+1,msgot,lbyto+1,len4)
172 jbit = (lbyto+len4)*8
186 nsub =
iupbs3(msgin,
'NSUB')
189 CALL upb(lsub,16,msgin,ibit)
202 islen = iad4+len4-(ibit/8)
203 IF (mod(len4,2).EQ.0) islen = islen - 1
206 CALL upb(nval,8,msgin,ibit)
208 IF(lbyto.GT.mxbyto)
GOTO 905
209 CALL pkb(nval,8,msgot,jbit)
213 CALL upb(kval,8,msgin,kbit)
228 IF(lbyto+6.GT.mxbyto)
GOTO 905
233 DO WHILE(.NOT.(mod(jbit,8).EQ.0))
234 CALL pkb(0,1,msgot,jbit)
241 IF( (iben.LT.4) .AND. (mod(jbit/8,2).NE.0) )
THEN
242 CALL pkb(0,8,msgot,jbit)
247 CALL pkb(len4,24,msgot,ibit)
248 CALL pkb(0,8,msgot,ibit)
255 lenn = len0+len1+len2+len3+len4+len5
256 CALL pkb(lenn,24,msgot,ibit)
258 CALL pkc(
'7777',4,msgot,jbit)
264 900
CALL bort(
'BUFRLIB: STNDRD - BUFR FILE IS CLOSED, IT MUST BE'//
266 901
WRITE(bort_str,
'("BUFRLIB: STNDRD - INPUT MESSAGE LENGTH FROM'//
267 .
' SECTION 0",I6," DOES NOT EQUAL SUM OF ALL INDIVIDUAL SECTION'//
268 .
' LENGTHS (",I6,")")') lenm,lenn
270 902
WRITE(bort_str,
'("BUFRLIB: STNDRD - INPUT MESSAGE DOES NOT '//
271 .
'END WITH ""7777"" (ENDS WITH ",A)') sevn
273 903
CALL bort(
'BUFRLIB: STNDRD - TABLE A SUBSET DESCRIPTOR '//
275 904
CALL bort(
'BUFRLIB: STNDRD - BIT MISMATCH COPYING SECTION 4 '//
276 .
'FROM INPUT TO OUTPUT (STANDARD) MESSAGE')
277 905
CALL bort(
'BUFRLIB: STNDRD - OVERFLOW OF OUTPUT (STANDARD) '//
278 .
'MESSAGE ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY')
subroutine bort(STR)
Log one error message and abort application program.
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,...
function istdesc(IDN)
Check whether a descriptor is WMO-standard.
recursive function iupb(MBAY, NBYT, NBIT)
Decode an integer value from an integer array.
recursive function iupbs01(MBAY, S01MNEM)
Read a data value from Section 0 or Section 1 of a BUFR message.
recursive function iupbs3(MBAY, S3MNEM)
This function returns a specified value from within Section 3 of a BUFR message.
subroutine mvb(IB1, NB1, IB2, NB2, NBM)
This subroutine copies a specified number of bytes from one packed binary array to another.
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
This module declares and initializes the IM8B variable.
logical, public im8b
Status indicator to keep track of whether all future calls to BUFRLIB subroutines and functions from ...
This module declares and initializes the MAXNC variable.
integer, parameter, public maxnc
Maximum number of descriptors within Section 3 of a BUFR message.
subroutine nemtbax(LUN, NEMO, MTYP, MSBT, INOD)
This subroutine searches for a descriptor within Table A of the internal DX BUFR tables.
subroutine numtab(LUN, IDN, NEMO, TAB, IRET)
Get information about a descriptor, based on the WMO bit-wise representation of an FXY value.
subroutine pkb(NVAL, NBITS, IBAY, IBIT)
This subroutine encodes an integer value within a specified number of bits of an integer array,...
subroutine pkc(CHR, NCHR, IBAY, IBIT)
Encode a character string within an integer array.
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
recursive subroutine stndrd(LUNIT, MSGIN, LMSGOT, MSGOT)
This subroutine performs the same function as subroutine stdmsg(), except that it operates on a BUFR ...
subroutine upb(NVAL, NBITS, IBAY, IBIT)
This subroutine decodes an integer value from within a specified number of bits of an integer array,...
subroutine upc(CHR, NCHR, IBAY, IBIT, CNVNULL)
Decode a character string from an integer array.
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.