19 COMMON /dxtab / maxdx,idxv,nxstr(10),ldxa(10),ldxb(10),ldxd(10),
22 CHARACTER*128 BORT_STR
23 CHARACTER*128 TABB1,TABB2
30 dimension ldxbd(10),ldxbe(10)
34 DATA ldxbd /38,70,8*0/
35 DATA ldxbe /42,42,8*0/
38 ja(i) = ia+1+lda*(i-1)
39 jb(i) = ib+1+ldb*(i-1)
46 IF(idxs.GT.idxv+1) idxs =
iupbs01(mesg,
'MTVL')+1
47 IF(ldxa(idxs).EQ.0)
GOTO 901
48 IF(ldxb(idxs).EQ.0)
GOTO 901
49 IF(ldxd(idxs).EQ.0)
GOTO 901
51 CALL getlens(mesg,3,len0,len1,len2,len3,l4,l5)
55 CALL upc(dxcmp,nxstr(idxs),mesg,jbit,.false.)
56 IF(dxcmp.NE.dxstr(idxs))
GOTO 902
81 CALL upc(
taba(n,lun),lda,mesg,jbit,.true.)
82 numb =
' '//
taba(n,lun)(1:3)
83 nemo =
taba(n,lun)(4:11)
84 cseq =
taba(n,lun)(13:67)
85 CALL stntbia(n,lun,numb,nemo,cseq)
94 CALL upc(tabb1,ldbd,mesg,jbit,.true.)
95 jbit = 8*(jb(i)+ldbd-1)
96 CALL upc(tabb2,ldbe,mesg,jbit,.true.)
97 tabb(n,lun) = tabb1(1:ldxbd(idxv+1))//tabb2(1:ldxbe(idxv+1))
98 numb =
tabb(n,lun)(1:6)
99 nemo =
tabb(n,lun)(7:14)
100 CALL nenubd(nemo,numb,lun)
102 unit =
tabb(n,lun)(71:94)
104 tabb(n,lun)(71:94) = unit
114 CALL upc(
tabd(n,lun),ldd,mesg,jbit,.true.)
115 numb =
tabd(n,lun)(1:6)
116 nemo =
tabd(n,lun)(7:14)
117 CALL nenubd(nemo,numb,lun)
119 nd =
iupb(mesg,id+ldd+1,8)
120 IF(nd.GT.
maxcd)
GOTO 903
122 ndd = id+ldd+2 + (j-1)*l30
124 CALL upc(cidn,l30,mesg,jbit,.true.)
125 idn =
idn30(cidn,l30)
126 CALL pktdd(n,lun,idn,iret)
127 IF(iret.LT.0)
GOTO 904
129 id = id+ldd+1 + nd*l30
130 IF(
iupb(mesg,id+1,8).EQ.0) id = id+1
138 901
CALL bort(
'BUFRLIB: STBFDX - UNEXPECTED DICTIONARY MESSAGE '//
139 .
'SUBTYPE OR LOCAL VERSION NUMBER (E.G., L.V.N. HIGHER THAN '//
141 902
CALL bort(
'BUFRLIB: STBFDX - UNEXPECTED DICTIONARY MESSAGE '//
143 903
WRITE(bort_str,
'("BUFRLIB: STBFDX - NUMBER OF DESCRIPTORS IN '//
144 .
'TABLE D ENTRY ",A," IN BUFR TABLE (",I4,") EXCEEDS THE LIMIT '//
145 .
' (",I4,")")') nemo,nd,
maxcd
147 904
CALL bort(
'BUFRLIB: STBFDX - BAD RETURN FROM BUFRLIB ROUTINE '//
148 .
'PKTDD, SEE PREVIOUS WARNING MESSAGE')
subroutine bort(STR)
Log one error message and abort application program.
subroutine capit(STR)
This subroutine capitalizes all of the alphabetic characters in a string.
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 idn30(ADN30, L30)
Convert an FXY value from a character string to the WMO bit-wise representation.
function ifxy(ADSC)
Convert an FXY value from its 6 character representation to its WMO bit-wise representation.
function igetntbi(LUN, CTB)
This function returns the next available index for storing an entry within a specified internal DX BU...
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.
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
character *600, dimension(:,:), allocatable tabd
Table D entries for each internal I/O stream.
character *128, dimension(:,:), allocatable taba
Table A entries for each internal I/O stream.
integer, dimension(:), allocatable ntbd
Number of Table D entries for each internal I/O stream (up to a maximum of MAXTBD,...
integer, dimension(:), allocatable ntbb
Number of Table B entries for each internal I/O stream (up to a maximum of MAXTBB,...
integer, dimension(:,:), allocatable idnd
Bit-wise representations of the FXY values corresponding to tabd.
integer, dimension(:,:), allocatable idnb
Bit-wise representations of the FXY values corresponding to tabb.
character *128, dimension(:,:), allocatable tabb
Table B entries for each internal I/O stream.
This module declares and initializes the MAXCD variable.
integer, public maxcd
Maximum number of child descriptors that can be included within the sequence definition of a Table D ...
subroutine nenubd(NEMO, NUMB, LUN)
Confirm that a mnemonic and FXY value haven't already been defined.
subroutine pktdd(ID, LUN, IDN, IRET)
Store information about a child mnemonic within the internal arrays.
subroutine stbfdx(LUN, MESG)
This subroutine copies a DX BUFR tables message from the input array mesg into the internal memory ar...
subroutine stntbia(N, LUN, NUMB, NEMO, CELSQ)
This subroutine stores a new entry within internal BUFR Table A.
subroutine upc(CHR, NCHR, IBAY, IBIT, CNVNULL)
Decode a character string from an integer array.