NCEPLIBS-bufr 11.7.1
gettagre.f
Go to the documentation of this file.
1C> @file
2C> @brief Check whether a Table B mnemonic references another
3C> Table B mnemonic via an internal bitmap.
4
5C> This subroutine determines whether a specified Table B mnemonic
6C> references another Table B mnemonic within the same data subset
7C> via an internal bitmap, and if so returns the referenced
8C> mnemonic and its location within the subset.
9C>
10C> @author J. Ator
11C> @date 2016-06-07
12C>
13C> @param[in] LUNIT -- integer: Fortran logical unit number for
14C> BUFR file
15C> @param[in] TAGI -- character*(*): Table B mnemonic
16C> @param[in] NTAGI -- integer: Ordinal occurrence of TAGI for
17C> which TAGRE is to be returned, counting from
18C> the beginning of the overall subset definition
19C> @param[out] TAGRE -- character*(*): Table B mnemonic referenced by
20C> TAGI via an internal bitmap
21C> @param[out] NTAGRE -- integer: Ordinal occurrence of TAGRE
22C> referenced by (NTAGI)th occurrence of TAGI,
23C> counting from the beginning of the overall
24C> subset definition
25C> @param[out] IRET -- integer: return code
26C> - 0 = normal return
27C> - -1 = TAGRE could not be found, or some
28C> other error occurred
29C>
30C> <p>A data subset must already be in scope within the BUFRLIB
31C> internal arrays for LUNIT, either via a previous call to one
32C> of the [subset-reading subroutines](@ref hierarchy)
33C> (when reading BUFR data subsets) or via a previous call to one
34C> of the [message-writing subroutines](@ref hierarchy)
35C> (when writing BUFR data subsets).
36C>
37C> <b>Program history log:</b>
38C> | Date | Programmer | Comments |
39C> | -----|------------|----------|
40C> | 2016-06-07 | J. Ator | Original author |
41C>
42 SUBROUTINE gettagre ( LUNIT, TAGI, NTAGI, TAGRE, NTAGRE, IRET )
43
44 USE moda_usrint
45 USE moda_msgcwd
46 USE moda_tables
47
48 CHARACTER*(*) TAGI, TAGRE
49
50 CHARACTER*10 TAGTMP
51
52C----------------------------------------------------------------------
53C----------------------------------------------------------------------
54
55 iret = -1
56
57C Get LUN from LUNIT.
58
59 CALL status( lunit, lun, il, im )
60 IF ( il .EQ. 0 ) RETURN
61 IF ( inode(lun) .NE. inv(1,lun) ) RETURN
62
63C Get TAGRE and NTAGRE from the (NTAGI)th occurrence of TAGI.
64
65 CALL fstag( lun, tagi, ntagi, 1, ni, iret )
66 IF ( iret .NE. 0 ) RETURN
67 nre = nrfelm(ni,lun)
68 IF ( nre .GT. 0 ) THEN
69 iret = 0
70 tagre = tag(inv(nre,lun))
71 CALL strsuc( tagre, tagtmp, ltre )
72 ntagre = 0
73 DO ii = 1, nre
74 IF ( tag(inv(ii,lun))(1:ltre) .EQ. tagre(1:ltre) ) THEN
75 ntagre = ntagre + 1
76 END IF
77 END DO
78 END IF
79
80 RETURN
81 END
subroutine fstag(LUN, UTAG, NUTAG, NIN, NOUT, IRET)
THIS SUBROUTINE FINDS THE (NUTAG)th OCCURRENCE OF MNEMONIC UTAG WITHIN THE CURRENT OVERALL SUBSET DEF...
Definition: fstag.f:41
subroutine gettagre(LUNIT, TAGI, NTAGI, TAGRE, NTAGRE, IRET)
This subroutine determines whether a specified Table B mnemonic references another Table B mnemonic w...
Definition: gettagre.f:43
This module contains array and variable declarations used to store the internal jump/link table.
Definition: moda_tables.F:13
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
Definition: moda_tables.F:132
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
Definition: status.f:56
subroutine strsuc(STR1, STR2, LENS)
This subroutine removes leading and trailing blanks from a character string.
Definition: strsuc.f:24