NCEPLIBS-bufr  12.0.0
pktdd.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Store information about a child mnemonic within the internal arrays.
3 C>
4 C> @author Woollen @date 1994-01-06
5 
6 C> Store information about a child mnemonic within the internal arrays.
7 C>
8 C> This subroutine stores information about a "child"
9 C> mnemonic within the internal BUFR table D entry (in module @ref moda_tababd)
10 C> for a table D sequence ("parent") mnemonic when the
11 C> "child" mnemonic is contained within the sequence represented by
12 C> the "parent" mnemonic (as determined within seqsdx()).
13 C>
14 C> @param[in] ID - integer: positional index of parent mnemonic within internal BUFR table D array tabd(*,*).
15 C> @param[in] LUN - integer: File ID.
16 C> @param[in] IDN - integer: WMO bit-wise representation of FXY value corresponding to child mnemonic.
17 C> - 0 = delete all information about all child mnemonics from within tabd(id,lun).
18 C> @param[out] IRET - integer: total number of child mnemonics stored thus far
19 C> (including idn) for the parent mnemonic given by tabd(id,lun).
20 C> - 0 information was cleared from tabd(id,lun) because input IDN value was 0
21 C> - -1 bad counter value or maximum number of child mnemonics already stored
22 C> for this parent mnemonic
23 C>
24 C> @author Woollen @date 1994-01-06
25  SUBROUTINE pktdd(ID,LUN,IDN,IRET)
26 
27  USE modv_maxcd
28  USE moda_tababd
29 
30  COMMON /dxtab / maxdx,idxv,nxstr(10),ldxa(10),ldxb(10),ldxd(10),
31  . ld30(10),dxstr(10)
32  COMMON /quiet / iprt
33 
34  CHARACTER*128 ERRSTR
35  CHARACTER*56 DXSTR
36 
37 C-----------------------------------------------------------------------
38 C-----------------------------------------------------------------------
39 
40  ldd = ldxd(idxv+1)+1
41 
42 C LDD points to the byte within TABD(ID,LUN) which contains (in
43 C packed integer format) a count of the number of child mnemonics
44 C stored thus far for this parent mnemonic.
45 
46 C ZERO THE COUNTER IF IDN IS ZERO
47 C -------------------------------
48 
49  IF(idn.EQ.0) THEN
50  CALL ipkm(tabd(id,lun)(ldd:ldd),1,0)
51  iret = 0
52  GOTO 100
53  ENDIF
54 
55 C UPDATE THE STORED DESCRIPTOR COUNT FOR THIS TABLE D ENTRY
56 C ---------------------------------------------------------
57 
58  nd = iupm(tabd(id,lun)(ldd:ldd),8)
59 
60 C ND is the (unpacked) count of the number of child mnemonics
61 C stored thus far for this parent mnemonic.
62 
63  IF(nd.LT.0 .OR. nd.EQ.maxcd) THEN
64  IF(iprt.GE.0) THEN
65  CALL errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
66  IF(nd.LT.0) THEN
67  WRITE ( unit=errstr, fmt='(A,I4,A)' )
68  . 'BUFRLIB: PKTDD - BAD COUNTER VALUE (=', nd,
69  . ') - RETURN WITH IRET = -1'
70  ELSE
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 ',
74  . 'IRET = -1'
75  ENDIF
76  CALL errwrt(errstr)
77  CALL errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
78  CALL errwrt(' ')
79  ENDIF
80  iret = -1
81  GOTO 100
82  ELSE
83  nd = nd+1
84  CALL ipkm(tabd(id,lun)(ldd:ldd),1,nd)
85  iret = nd
86  ENDIF
87 
88 C PACK AND STORE THE DESCRIPTOR
89 C -----------------------------
90 
91  idm = ldd+1 + (nd-1)*2
92 
93 C IDM points to the starting byte within TABD(ID,LUN) at which
94 C the IDN value for this child mnemonic will be stored (as a
95 C packed integer of width = 2 bytes).
96 
97  CALL ipkm(tabd(id,lun)(idm:idm),2,idn)
98 
99 C EXIT
100 C ----
101 
102 100 RETURN
103  END
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 ipkm(CBAY, NBYT, N)
Encode an integer value within a character string.
Definition: ipkm.f:22
recursive function iupm(CBAY, NBITS)
Decode an integer value from a character string.
Definition: iupm.f:20
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.
Definition: pktdd.f:26