NCEPLIBS-bufr  12.0.0
chekstab.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Check that an internal BUFR table
3 C> representation is self-consistent and fully defined.
4 C>
5 C> @author Woollen @date 1994-01-06
6 
7 C> This subroutine checks that an internal BUFR table
8 C> representation is self-consistent and fully defined. If any errors
9 C> are found, then an appropriate call is made to bufr archive library
10 C> subroutine bort().
11 C>
12 C> @param LUN I/O stream index into internal memory arrays.
13 C>
14 C> @author Woollen @date 1994-01-06
15  SUBROUTINE chekstab(LUN)
16 
17  USE moda_tababd
18  USE moda_nmikrp
19 
20  CHARACTER*128 BORT_STR
21  CHARACTER*24 UNIT
22  CHARACTER*8 NEMO
23  CHARACTER*1 TAB
24 
25 C-----------------------------------------------------------------------
26 C-----------------------------------------------------------------------
27 
28 C THERE MUST BE ENTRIES IN TABLES A, B, AND D
29 C -------------------------------------------
30 
31  IF(ntba(lun).EQ.0) GOTO 900
32  IF(ntbb(lun).EQ.0) GOTO 901
33  IF(ntbd(lun).EQ.0) GOTO 902
34 
35 C MAKE SURE EACH TABLE A ENTRY DEFINED AS A SEQUENCE
36 C --------------------------------------------------
37 
38  DO i=1,ntba(lun)
39  nemo = taba(i,lun)(4:11)
40  CALL nemtab(lun,nemo,idn,tab,iret)
41  IF(tab.NE.'D') GOTO 903
42  ENDDO
43 
44 C CHECK TABLE B CONTENTS
45 C ----------------------
46 
47  DO itab=1,ntbb(lun)
48  CALL nemtbb(lun,itab,unit,iscl,iref,ibit)
49  ENDDO
50 
51 C CHECK TABLE D CONTNETS
52 C ----------------------
53 
54  DO itab=1,ntbd(lun)
55  CALL nemtbd(lun,itab,nseq,nem(1,1),irp(1,1),krp(1,1))
56  ENDDO
57 
58 C EXITS
59 C -----
60 
61  RETURN
62 900 CALL bort
63  . ('BUFRLIB: CHEKSTAB - EMPTY TABLE A IN INTERNAL BUFR TABLES')
64 901 CALL bort
65  . ('BUFRLIB: CHEKSTAB - EMPTY TABLE B IN INTERNAL BUFR TABLES')
66 902 CALL bort
67  . ('BUFRLIB: CHEKSTAB - EMPTY TABLE D IN INTERNAL BUFR TABLES')
68 903 WRITE(bort_str,'("BUFRLIB: CHEKSTAB - TABLE A ENTRY: ",A," NOT '//
69  . 'DEFINED AS A SEQUENCE")') nemo
70  CALL bort(bort_str)
71  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
subroutine chekstab(LUN)
This subroutine checks that an internal BUFR table representation is self-consistent and fully define...
Definition: chekstab.f:16
This module contains declarations for arrays used by various subroutines to hold information about Ta...
integer, dimension(:,:), allocatable krp
Replication counts corresponding to nem:
integer, dimension(:,:), allocatable irp
Replication indicators corresponding to nem:
character *8, dimension(:,:), allocatable nem
Child mnemonics within Table D sequences.
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
integer, dimension(:), allocatable ntba
Number of Table A entries for each internal I/O stream (up to a maximum of MAXTBA,...
character *128, dimension(:,:), allocatable taba
Table A entries for each internal I/O stream.
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,...
subroutine nemtab(LUN, NEMO, IDN, TAB, IRET)
Get information about a descriptor, based on the mnemonic.
Definition: nemtab.f:29
subroutine nemtbb(LUN, ITAB, UNIT, ISCL, IREF, IBIT)
Get information about a Table B descriptor.
Definition: nemtbb.f:22
subroutine nemtbd(LUN, ITAB, NSEQ, NEMS, IRPS, KNTS)
This subroutine returns information about a Table D descriptor from the internal DX BUFR tables.
Definition: nemtbd.f:44