44 COMMON /padesc/ ibct,ipd1,ipd2,ipd3,ipd4
45 COMMON /reptab/ idnr(5,2),typs(5,2),reps(5,2),lens(5)
47 CHARACTER*8 INIB(6,5),INID(5)
52 DATA inib /
'------',
'BYTCNT ',
'BYTES ',
'+0',
'+0',
'16',
53 .
'------',
'BITPAD ',
'NONE ',
'+0',
'+0',
'1 ',
54 .
'031000',
'DRF1BIT ',
'NUMERIC',
'+0',
'+0',
'1 ',
55 .
'031001',
'DRF8BIT ',
'NUMERIC',
'+0',
'+0',
'8 ',
56 .
'031002',
'DRF16BIT',
'NUMERIC',
'+0',
'+0',
'16'/
88 CALL pktdd(i,lun,0,iret)
96 inib(1,1) = adn30(ibct,6)
97 inib(1,2) = adn30(ipd4,6)
102 tabb(i,lun)( 1: 6) = inib(1,i)
103 tabb(i,lun)( 7: 70) = inib(2,i)
104 tabb(i,lun)( 71: 94) = inib(3,i)
105 tabb(i,lun)( 95: 98) = inib(4,i)
106 tabb(i,lun)( 99:109) = inib(5,i)
107 tabb(i,lun)(110:112) = inib(6,i)
112 idnd(n,lun) = idnr(i,1)
113 tabd(n,lun)(1: 6) = adn30(idnr(i,1),6)
114 tabd(n,lun)(7:70) = inid(i)
116 CALL pktdd(n,lun,idnr(1,1),iret)
118 CALL pktdd(n,lun,idnr(i,2),iret)
subroutine dxinit(LUN, IOI)
THIS SUBROUTINE INITIALIZES THE INTERNAL ARRAYS (IN MODULE TABABD) HOLDING THE DICTIONARY TABLE.
function ifxy(ADSC)
This function converts an FXY value from its 6 character representation to its bit-wise (integer) rep...
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
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.
character *128, dimension(:,:), allocatable taba
Table A entries for each internal I/O stream.
integer, dimension(:,:), allocatable mtab
Entries within jump/link table corresponding to taba.
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 ntba
Number of Table A entries for each internal I/O stream (up to a maximum of MAXTBA,...
integer, dimension(:,:), allocatable idnd
Bit-wise representations of the FXY values corresponding to tabd.
character *600, dimension(:,:), allocatable tabd
Table D entries for each internal I/O stream.
subroutine pktdd(ID, LUN, IDN, IRET)
THIS SUBROUTINE STORES INFORMATION ABOUT A "CHILD" MNEMONIC WITHIN THE INTERNAL BUFR TABLE D ENTRY (I...