NCEPLIBS-bufr  12.0.0
numtab.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Get information about a descriptor, based on the WMO
3 C> bit-wise representation of an FXY value.
4 C>
5 C> @author J. Woollen @date 1994-01-06
6 
7 C> Get information about a descriptor, based on the WMO
8 C> bit-wise representation of an FXY value.
9 C>
10 C> This subroutine returns information about a descriptor from the
11 C> internal DX BUFR tables, based on the bit-wise representation of
12 C> the FXY value associated with that descriptor.
13 C>
14 C> For an description of the WMO bit-wise representation of the FXY
15 C> value, see ifxy().
16 C>
17 C> @param[in] LUN - integer: Internal I/O stream index associated
18 C> with DX BUFR tables.
19 C> @param[in] IDN - integer: WMO bit-wise representation of FXY value
20 C> for descriptor.
21 C> @param[out] NEMO - character*(*): Mnemonic associated with IDN.
22 C> @param[out] TAB - character: Type associated with IDN:
23 C> - 'B' Table B descriptor
24 C> - 'D' Table D descriptor
25 C> - 'C' Table C operator
26 C> - 'R' Replication descriptor
27 C> - 'F' Replication factor
28 C> @param[out] IRET - integer:
29 C> - Positional index of IDN within internal Table B, if TAB = 'B'.
30 C> - Positional index of IDN within internal Table D, if TAB = 'D'.
31 C> - The X portion of the FXY value in IDN, if TAB = 'C'.
32 C> - ((-1) * the Y portion of the FXY value in IDN), if TAB = 'R' and the
33 C> replication is regular (i.e. non-delayed).
34 C> - 5 if TAB = 'R' or TAB = 'F' and the replication is 1-bit delayed.
35 C> - 4 if TAB = 'R' or TAB = 'F' and the replication is 8-bit delayed (stack).
36 C> - 3 if TAB = 'R' or TAB = 'F' and the replication is 8-bit delayed.
37 C> - 2 if TAB = 'R' or TAB = 'F' and the replication is 16-bit delayed.
38 C> - 0 otherwise
39 C>
40 C> @author J. Woollen @date 1994-01-06
41  SUBROUTINE numtab(LUN,IDN,NEMO,TAB,IRET)
42 
43 C Note that the values within the COMMON /REPTAB/ arrays were
44 C initialized within subroutine BFRINI.
45 
46  COMMON /reptab/ idnr(5,2),typs(5,2),reps(5,2),lens(5)
47 
48  CHARACTER*(*) NEMO
49  CHARACTER*6 ADN30,CID
50  CHARACTER*3 TYPS
51  CHARACTER*1 REPS,TAB
52 
53 C-----------------------------------------------------------------------
54 C-----------------------------------------------------------------------
55 
56  nemo = ' '
57  iret = 0
58  tab = ' '
59 
60 C LOOK FOR A REPLICATOR OR A REPLICATION FACTOR DESCRIPTOR
61 C --------------------------------------------------------
62 
63  IF(idn.GE.idnr(1,1) .AND. idn.LE.idnr(1,2)) THEN
64 
65 C Note that the above test is checking whether IDN is the bit-
66 C wise representation of a FXY (descriptor) value denoting F=1
67 C regular (i.e. non-delayed) replication, since, as was
68 C initialized within subroutine BFRINI,
69 C IDNR(1,1) = IFXY('101000'), and IDNR(1,2) = IFXY('101255').
70 
71  tab = 'R'
72  iret = -mod(idn,256)
73  GOTO 100
74  ENDIF
75 
76  DO i=2,5
77  IF(idn.EQ.idnr(i,1)) THEN
78  tab = 'R'
79  iret = i
80  GOTO 100
81  ELSEIF(idn.EQ.idnr(i,2)) THEN
82  tab = 'F'
83  iret = i
84  GOTO 100
85  ENDIF
86  ENDDO
87 
88 C LOOK FOR IDN IN TABLE B AND TABLE D
89 C -----------------------------------
90 
91  CALL numtbd(lun,idn,nemo,tab,iret)
92  IF(iret.NE.0) GOTO 100
93 
94 C LOOK FOR IDN IN TABLE C
95 C -----------------------
96 
97  cid = adn30(idn,6)
98  IF (iokoper(cid).EQ.1) THEN
99  nemo = cid(1:6)
100  READ(nemo,'(1X,I2)') iret
101  tab = 'C'
102  GOTO 100
103  ENDIF
104 
105 C EXIT
106 C ----
107 
108 100 RETURN
109  END
integer function iokoper(NEMO)
This function determines whether a specified mnemonic is a Table C operator supported by the BUFRLIB ...
Definition: iokoper.f:18
subroutine numtab(LUN, IDN, NEMO, TAB, IRET)
Get information about a descriptor, based on the WMO bit-wise representation of an FXY value.
Definition: numtab.f:42
subroutine numtbd(LUN, IDN, NEMO, TAB, IRET)
Search for a Table B or Table D descriptor within the internal DX BUFR tables.
Definition: numtbd.f:24