NCEPLIBS-bufr  12.0.0
seqsdx.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Decode the sequence information from a Table D mnemonic definition.
3 C>
4 C> @author Woollen @date 1994-01-06
5 
6 C> Decode the sequence information from a Table D mnemonic definition.
7 C>
8 C> This subroutine decodes the Table D sequence information
9 C> from a mnemonic definition card that was previously read from a
10 C> user-supplied DX BUFR table in character format by rdusdx().
11 C> These are then added to the
12 C> already-existing entry for that mnemonic (built in rdusdx()) within
13 C> the internal BUFR Table D array tabd(*,lun) in module @ref moda_tababd.
14 C>
15 C> @param[in] CARD - character*80: mnemonic definition card that was read
16 C> from a user-supplied DX BUFR table.
17 C> @param[in] LUN - integer: File ID.
18 C>
19 C> @author Woollen @date 1994-01-06
20  SUBROUTINE seqsdx(CARD,LUN)
21 
22  COMMON /reptab/ idnr(5,2),typs(5,2),reps(5,2),lens(5)
23 
24  CHARACTER*128 BORT_STR1,BORT_STR2
25  CHARACTER*80 CARD,SEQS
26  CHARACTER*12 ATAG,TAGS(250)
27  CHARACTER*8 NEMO,NEMA,NEMB
28  CHARACTER*6 ADN30,CLEMON
29  CHARACTER*3 TYPS
30  CHARACTER*1 REPS,TAB
31 
32  DATA maxtgs /250/
33  DATA maxtag /12/
34 
35 C-----------------------------------------------------------------------
36 C-----------------------------------------------------------------------
37 
38 C FIND THE SEQUENCE TAG IN TABLE D AND PARSE THE SEQUENCE STRING
39 C --------------------------------------------------------------
40 
41  nemo = card( 3:10)
42  seqs = card(14:78)
43 
44 C Note that an entry for this mnemonic should already exist within
45 C the internal BUFR Table D array TABD(*,LUN); this entry should
46 C have been created by subroutine RDUSDX when the mnemonic and its
47 C associated FXY value and description were initially defined
48 C within a card read from the "Descriptor Definition" section at
49 C the top of the user-supplied BUFR dictionary table in character
50 C format. Now, we need to retrieve the positional index for that
51 C entry within TABD(*,LUN) so that we can access the entry and then
52 C add the decoded sequence information to it.
53 
54  CALL nemtab(lun,nemo,idn,tab,iseq)
55  IF(tab.NE.'D') GOTO 900
56  CALL parstr(seqs,tags,maxtgs,ntag,' ',.true.)
57  IF(ntag.EQ.0 ) GOTO 901
58 
59  DO n=1,ntag
60  atag = tags(n)
61  irep = 0
62 
63 C CHECK FOR REPLICATOR
64 C --------------------
65 
66  DO i=1,5
67  IF(atag(1:1).EQ.reps(i,1)) THEN
68 
69 C Note that REPS(*,*), which contains all of the symbols used to
70 C denote all of the various replication schemes that are
71 C possible within a user-supplied BUFR dictionary table in
72 C character format, was previously defined within subroutine
73 C BFRINI.
74 
75  DO j=2,maxtag
76  IF(atag(j:j).EQ.reps(i,2)) THEN
77  IF(j.EQ.maxtag) GOTO 902
78 
79 C Note that subroutine STRNUM will return NUMR = 0 if the
80 C string passed to it contains all blanks (as *should* be the
81 C case whenever I = 2 '(' ')', 3 '{' '}', 4 '[' ']', or
82 C 5 '<' '>').
83 
84 C However, when I = 1 '"' '"', then subroutine STRNUM will
85 C return NUMR = (the number of replications for the mnemonic
86 C using F=1 "regular" (i.e. non-delayed) replication).
87 
88  CALL strnum(atag(j+1:maxtag),numr,ier)
89  IF(i.EQ.1 .AND. numr.LE.0 ) GOTO 903
90  IF(i.EQ.1 .AND. numr.GT.255) GOTO 904
91  IF(i.NE.1 .AND. numr.NE.0 ) GOTO 905
92  atag = atag(2:j-1)
93  irep = i
94  GOTO 1
95  ENDIF
96  ENDDO
97  GOTO 902
98  ENDIF
99  ENDDO
100 
101 C CHECK FOR VALID TAG
102 C -------------------
103 
104 1 iret=nemock(atag)
105  IF(iret.EQ.-1) GOTO 906
106  IF(iret.EQ.-2) GOTO 907
107  CALL nemtab(lun,atag,idn,tab,iret)
108  IF(iret.GT.0) THEN
109 
110 C Note that the next code line checks that we are not trying to
111 C replicate a Table B mnemonic (which is currently not allowed).
112 C The logic works because, for replicated mnemonics, IREP = I =
113 C (the index within REPS(*,*) of the symbol associated with the
114 C type of replication in question (e.g. "{, "<", etc.))
115 
116  IF(tab.EQ.'B' .AND. irep.NE.0) GOTO 908
117  IF(atag(1:1).EQ.'.') THEN
118 
119 C This mnemonic is a "following value" mnemonic
120 C (i.e. it relates to the mnemonic that immediately
121 C follows it within the user-supplied character-format BUFR
122 C dictionary table sequence), so confirm that it contains, as
123 C a substring, this mnemonic that immediately follows it.
124 
125  IF(n.EQ.ntag) GOTO 910
126  nemb = tags(n+1)(1:8)
127 c .... get NEMA from IDN
128  CALL numtab(lun,idn,nema,tab,itab)
129  CALL nemtab(lun,nemb,jdn,tab,iret)
130  CALL rsvfvm(nema,nemb)
131  IF(nema.NE.atag) GOTO 909
132  IF(tab.NE.'B') GOTO 911
133  ENDIF
134  ELSE
135  GOTO 912
136  ENDIF
137 
138 C WRITE THE DESCRIPTOR STRING INTO TABD ARRAY
139 C -------------------------------------------
140 c .... first look for a replication descriptor
141  IF(irep.GT.0) CALL pktdd(iseq,lun,idnr(irep,1)+numr,iret)
142  IF(iret.LT.0) GOTO 913
143  CALL pktdd(iseq,lun,idn,iret)
144  IF(iret.LT.0) GOTO 914
145 
146  ENDDO
147 
148 C EXITS
149 C -----
150 
151  RETURN
152 900 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
153  WRITE(bort_str2,'(18X,"MNEMONIC ",A," IS NOT A TABLE D ENTRY '//
154  . '(UNDEFINED, TAB=",A,")")') nemo,tab
155  CALL bort2(bort_str1,bort_str2)
156 901 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
157  WRITE(bort_str2,'(18X,"TABLE D SEQUENCE (PARENT) MNEMONIC ",A,'//
158  . '" DOES NOT CONTAIN ANY CHILD MNEMONICS")') nemo
159  CALL bort2(bort_str1,bort_str2)
160 902 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
161  WRITE(bort_str2,'(18X,"TABLE D SEQUENCE (PARENT) MNEMONIC ",A,'//
162  . '" CONTAINS A BADLY FORMED CHILD MNEMONIC ",A)') nemo,tags(n)
163  CALL bort2(bort_str1,bort_str2)
164 903 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
165  WRITE(bort_str2,'(9X,"TBL D MNEM. ",A," CONTAINS REG. REPL. '//
166  . 'CHILD MNEM. ",A," W/ INVALID # OF REPLICATIONS (",I3,") AFTER'//
167  . ' 2ND QUOTE")') nemo,tags(n),numr
168  CALL bort2(bort_str1,bort_str2)
169 904 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
170  WRITE(bort_str2,'(18X,"TBL D MNEM. ",A," CONTAINS REG. REPL. '//
171  . 'CHILD MNEM. ",A," W/ # OF REPLICATIONS (",I3,") > LIMIT OF '//
172  . '255")') nemo,tags(n),numr
173  CALL bort2(bort_str1,bort_str2)
174 905 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
175  WRITE(bort_str2,'(18X,"TBL D MNEM. ",A," CONTAINS DELAYED REPL.'//
176  . ' CHILD MNEM. ",A," W/ # OF REPL. (",I3,") SPECIFIED - A NO-'//
177  . 'NO")') nemo,tags(n),numr
178  CALL bort2(bort_str1,bort_str2)
179 906 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
180  WRITE(bort_str2,'(18X,"TABLE D (PARENT) MNEMONIC ",A," CONTAINS'//
181  .' A CHILD MNEMONIC ",A," NOT BETWEEN 1 & 8 CHARACTERS")')
182  . nemo,tags(n)
183  CALL bort2(bort_str1,bort_str2)
184 907 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
185  WRITE(bort_str2,'(18X,"TABLE D (PARENT) MNEMONIC ",A," CONTAINS'//
186  . ' A CHILD MNEMONIC ",A," WITH INVALID CHARACTERS")') nemo,tags(n)
187  CALL bort2(bort_str1,bort_str2)
188 908 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
189  WRITE(bort_str2,'(18X,"TABLE D (PARENT) MNEMONIC ",A," CONTAINS'//
190  . ' A REPLICATED CHILD TABLE B MNEMONIC ",A," - A NO-NO")')
191  . nemo,tags(n)
192  CALL bort2(bort_str1,bort_str2)
193 909 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
194  WRITE(bort_str2,'(18X,"TBL D (PARENT) MNEM. ",A," CONTAINS AN '//
195  . 'INVALID ''FOLLOWING VALUE'' MNEMONIC ",A,"(SHOULD BE ",A,")")')
196  . nemo,tags(n),nema
197  CALL bort2(bort_str1,bort_str2)
198 910 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
199  WRITE(bort_str2,'(18X,"TBL D (PARENT) MNEM. ",A," CONTAINS A '//
200  . '''FOLLOWING VALUE'' MNEMONIC WHICH IS LAST IN THE '//
201  . 'STRING")') nemo
202  CALL bort2(bort_str1,bort_str2)
203 911 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
204  WRITE(bort_str2,'(18X,"TBL D (PARENT) MNEM. ",A,", THE MNEM. ",'//
205  . 'A," FOLLOWING A ''FOLLOWING VALUE'' MNEM. IS NOT A TBL B '//
206  . 'ENTRY")') nemo,nemb
207  CALL bort2(bort_str1,bort_str2)
208 912 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
209  WRITE(bort_str2,'(18X,"TABLE D SEQUENCE (PARENT) MNEMONIC ",A,'//
210  . '" CONTAINS A CHILD MNEMONIC ",A," NOT FOUND IN ANY TABLE")')
211  . nemo,tags(n)
212  CALL bort2(bort_str1,bort_str2)
213 913 clemon = adn30(idnr(irep,1)+numr,6)
214  WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
215  WRITE(bort_str2,'(9X,"TBL D (PARENT) MNEM. ",A," - BAD RETURN '//
216  . 'FROM PKTDD TRYING TO STORE REPL. DESC. ",A,", SEE PREV. '//
217  . 'WARNING MSG")') nemo,clemon
218  CALL bort2(bort_str1,bort_str2)
219 914 WRITE(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
220  WRITE(bort_str2,'(9X,"TBL D (PARENT) MNEM. ",A," - BAD RETURN '//
221  . 'FROM PKTDD TRYING TO STORE CHILD MNEM. ",A,", SEE PREV. '//
222  . 'WARNING MSG")') nemo,tags(n)
223  CALL bort2(bort_str1,bort_str2)
224  END
subroutine bort2(STR1, STR2)
Log two error messages and abort application program.
Definition: bort2.f:18
function nemock(NEMO)
This function checks a mnemonic to verify that it has a length of between 1 and 8 characters and that...
Definition: nemock.f:18
subroutine nemtab(LUN, NEMO, IDN, TAB, IRET)
Get information about a descriptor, based on the mnemonic.
Definition: nemtab.f:29
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 parstr(STR, TAGS, MTAG, NTAG, SEP, LIMIT80)
Parse a string containing one or more substrings into an array of substrings.
Definition: parstr.f:24
subroutine pktdd(ID, LUN, IDN, IRET)
Store information about a child mnemonic within the internal arrays.
Definition: pktdd.f:26
subroutine rsvfvm(NEM1, NEM2)
This subroutine steps through the "following value" mnemonic NEM1 and, for each "....
Definition: rsvfvm.f:27
subroutine seqsdx(CARD, LUN)
Decode the sequence information from a Table D mnemonic definition.
Definition: seqsdx.f:21
recursive subroutine strnum(str, num, iret)
Decode an integer from a character string.
Definition: strnum.F90:24