NCEPLIBS-bufr 11.7.1
strbtm.f
Go to the documentation of this file.
1C> @file
2C> @author J @date 2016-05-27
3
4C> THIS SUBROUTINE STORES INTERNAL INFORMATION IN
5C> MODULE BITMAPS IF THE INPUT ELEMENT IS PART OF A BITMAP.
6C>
7C> PROGRAM HISTORY LOG:
8C> 2016-05-27 J. ATOR -- ORIGINAL AUTHOR
9C> 2019-05-22 J. ATOR -- ADD CONFIRMATION CHECK
10C>
11C> USAGE: CALL STRBTM ( N, LUN )
12C> INPUT ARGUMENT LIST:
13C> N - INTEGER: SUBSET ELEMENT
14C> LUN - INTEGER: I/O STREAM INDEX INTO INTERNAL MEMORY ARRAYS
15C>
16C> THIS ROUTINE CALLS: BORT IBFMS LSTJPB
17C> THIS ROUTINE IS CALLED BY: RCSTPL RDCMPS
18C> Normally not called by any application
19C> programs.
20C>
21 SUBROUTINE strbtm ( N, LUN )
22
23 USE modv_mxbtm
24 USE modv_mxbtmse
25
26 USE moda_msgcwd
27 USE moda_usrint
28 USE moda_tables
29 USE moda_bitmaps
30
31 LOGICAL ISBTME
32
33C-----------------------------------------------------------------------
34C-----------------------------------------------------------------------
35
36 node = inv( n, lun )
37
38 IF ( tag(node)(1:5) .EQ. 'DPRI ' ) THEN
39
40C Confirm that this is really an entry within a bitmap.
41C Although it is rare, it is possible for a DPRI element
42C to appear in a subset definition outside of a bitmap.
43
44 isbtme = .false.
45 IF ( ntamc .GT. 0 ) THEN
46 nodtam = lstjpb( node, lun, 'SUB' )
47 DO ii = 1, ntamc
48 IF ( nodtam .EQ. inodtamc(ii) ) THEN
49 DO jj = 1, ntco(ii)
50 IF ( ( inodtco(ii,jj) .GE. inode(lun) ) .AND.
51 . ( inodtco(ii,jj) .LE. isc(inode(lun)) ) .AND.
52 . ( inodtco(ii,jj) .LT. node ) ) THEN
53 IF ( ctco(ii,jj) .EQ. '236000' ) THEN
54 isbtme = .true.
55 ELSE IF ( ( ctco(ii,jj) .EQ. '235000' ) .OR.
56 . ( ctco(ii,jj) .EQ. '237255' ) ) THEN
57 isbtme = .false.
58 END IF
59 END IF
60 END DO
61 END IF
62 END DO
63 END IF
64 IF ( .NOT. isbtme ) THEN
65 linbtm = .false.
66 RETURN
67 ELSE IF ( .NOT. linbtm ) THEN
68
69C This is the start of a new bitmap.
70
71 IF ( nbtm .GE. mxbtm ) GOTO 900
72 nbtm = nbtm + 1
73 istbtm(nbtm) = n
74 iszbtm(nbtm) = 0
75 nbtmse(nbtm) = 0
76 linbtm = .true.
77 END IF
78 iszbtm(nbtm) = iszbtm(nbtm) + 1
79 IF ( ibfms(val(n,lun)) .EQ. 0 ) THEN
80
81C This is a "set" (value=0) entry in the bitmap.
82
83 IF ( nbtmse(nbtm) .GE. mxbtmse ) GOTO 901
84 nbtmse(nbtm) = nbtmse(nbtm) + 1
86 END IF
87 ELSE IF ( itp(node) .GT. 1 ) THEN
88 linbtm = .false.
89 END IF
90
91 RETURN
92900 CALL bort('BUFRLIB: STRBTM - MXBTM OVERFLOW')
93901 CALL bort('BUFRLIB: STRBTM - MXBTMSE OVERFLOW')
94 END
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
Definition: bort.f:23
integer function ibfms(R8VAL)
This function provides a handy way to check whether a real*8 data value returned from a previous call...
Definition: ibfms.f:39
function lstjpb(NODE, LUN, JBTYP)
THIS FUNCTION SEARCHES BACKWARDS, BEGINNING FROM A GIVEN NODE WITHIN THE JUMP/LINK TABLE,...
Definition: lstjpb.f:58
This module contains array and variable declarations used to store bitmaps internally within a data s...
Definition: moda_bitmaps.F:13
integer nbtm
Number of stored bitmaps for the current data subset (up to a maximum of MXBTM).
Definition: moda_bitmaps.F:73
integer, dimension(:), allocatable iszbtm
Size of bitmap (total number of entries, whether "set" (set to a value of 0) or not).
Definition: moda_bitmaps.F:84
logical linbtm
TRUE if a bitmap is in the process of being read for the current data subset.
Definition: moda_bitmaps.F:77
integer, dimension(:,:), allocatable ibtmse
Ordinal positions in bitmap of bits that were "set" (set to a value of 0); these ordinal positions ca...
Definition: moda_bitmaps.F:85
integer, dimension(:), allocatable nbtmse
Number of "set" entries (set to a value of 0) in the bitmap.
Definition: moda_bitmaps.F:82
integer, dimension(:), allocatable inodtamc
Entries within jump/link table which contain Table A mnemonics.
Definition: moda_bitmaps.F:78
integer, dimension(:,:), allocatable inodtco
Entries within jump/link table which contain Table C operators.
Definition: moda_bitmaps.F:81
integer, dimension(:), allocatable istbtm
Ordinal position in data subset definition corresponding to the first entry of the bitmap.
Definition: moda_bitmaps.F:83
integer ntamc
Number of Table A mnemonics in jump/link table (up to a maximum of MXTAMC) which contain at least one...
Definition: moda_bitmaps.F:74
integer, dimension(:), allocatable ntco
Number of Table C operators (with an XX value of 21 or greater) within the data subset definition of ...
Definition: moda_bitmaps.F:79
character *6, dimension(:,:), allocatable ctco
Table C operators corresponding to inodtco.
Definition: moda_bitmaps.F:80
This module contains array and variable declarations used to store the internal jump/link table.
Definition: moda_tables.F:13
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
Definition: moda_tables.F:141
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
Definition: moda_tables.F:140
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
Definition: moda_tables.F:132
This module declares and initializes the MXBTM variable.
Definition: modv_MXBTM.f:13
integer mxbtm
Maximum number of bitmaps that can be stored internally for a data subset.
Definition: modv_MXBTM.f:19
This module declares and initializes the MXBTMSE variable.
Definition: modv_MXBTMSE.f:13
integer mxbtmse
Maximum number of "set" entries (set to a value of 0) within a bitmap.
Definition: modv_MXBTMSE.f:19
subroutine strbtm(N, LUN)
THIS SUBROUTINE STORES INTERNAL INFORMATION IN MODULE BITMAPS IF THE INPUT ELEMENT IS PART OF A BITMA...
Definition: strbtm.f:22