25 SUBROUTINE pktdd(ID,LUN,IDN,IRET)
30 COMMON /dxtab / maxdx,idxv,nxstr(10),ldxa(10),ldxb(10),ldxd(10),
63 IF(nd.LT.0 .OR. nd.EQ.
maxcd)
THEN
65 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
67 WRITE ( unit=errstr, fmt=
'(A,I4,A)' )
68 .
'BUFRLIB: PKTDD - BAD COUNTER VALUE (=', nd,
69 .
') - RETURN WITH IRET = -1'
71 WRITE ( unit=errstr, fmt=
'(A,I4,A,A)' )
72 .
'BUFRLIB: PKTDD - MAXIMUM NUMBER OF CHILD MNEMONICS (=',
73 .
maxcd,
') ALREADY STORED FOR THIS PARENT - RETURN WITH ',
77 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
84 CALL ipkm(
tabd(id,lun)(ldd:ldd),1,nd)
91 idm = ldd+1 + (nd-1)*2
97 CALL ipkm(
tabd(id,lun)(idm:idm),2,idn)
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
recursive subroutine ipkm(CBAY, NBYT, N)
Encode an integer value within a character string.
recursive function iupm(CBAY, NBITS)
Decode an integer value from a character string.
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.
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 pktdd(ID, LUN, IDN, IRET)
Store information about a child mnemonic within the internal arrays.