NCEPLIBS-bufr 11.7.1
upftbv.f
Go to the documentation of this file.
1C> @file
2C> @brief Determine the bit settings equivalent to a numerical
3C> flag table value.
4
5C> Given a Table B mnemonic with flag table units and a
6C> corresponding numerical data value, this subroutine determines
7C> the bit settings equivalent to that numerical value.
8C>
9C> @author J. Ator
10C> @date 2005-11-29
11C>
12C> @param[in] LUNIT -- integer: Fortran logical unit number for
13C> BUFR file
14C> @param[in] NEMO -- character*(*): Table B mnemonic with
15C> flag table units
16C> @param[in] VAL -- real*8: Value corresponding to NEMO
17C> @param[in] MXIB -- integer: Dimensioned size (in integers) of
18C> IBIT; used by the subroutine to ensure that
19C> it doesn't overflow the IBIT array
20C> @param[out] IBIT -- integer(*): Bit numbers which were set to
21C> "On" (i.e. set to "1") in VAL
22C> @param[out] NIB -- integer: Number of bit numbers returned in
23C> IBIT
24C>
25C> @remarks
26C> - This subroutine is the logical inverse of function pkftbv().
27C> - According to the WMO standard, bits within a bit field are
28C> numbered from left to right, so bit #1 is always the high-order
29C> (i.e. most significant) bit in any bit field.
30C>
31C> <b>Program history log:</b>
32C> | Date | Programmer | Comments |
33C> | -----|------------|----------|
34C> | 2005-11-29 | J. Ator | Original version |
35C> | 2014-12-10 | J. Ator | Use modules instead of COMMON blocks |
36C>
37 SUBROUTINE upftbv(LUNIT,NEMO,VAL,MXIB,IBIT,NIB)
38
39 USE moda_tababd
40
41 real*8 val,r8val,r82i
42
43 INTEGER IBIT (*)
44
45 CHARACTER*(*) NEMO
46 CHARACTER*128 BORT_STR
47 CHARACTER*1 TAB
48
49C----------------------------------------------------------------------
50C----------------------------------------------------------------------
51
52C Perform some sanity checks.
53
54 CALL status(lunit,lun,il,im)
55 IF(il.EQ.0) GOTO 900
56
57 CALL nemtab(lun,nemo,idn,tab,n)
58 IF(n.EQ.0) GOTO 901
59 IF(tabb(n,lun)(71:74).NE.'FLAG') GOTO 902
60
61C Figure out which bits are set.
62
63 nib = 0
64 r8val = val
65 nbits = valx(tabb(n,lun)(110:112))
66 DO i=(nbits-1),0,-1
67 r82i = (2.)**i
68 IF(abs(r8val-r82i).LT.(0.005)) THEN
69 nib = nib + 1
70 IF(nib.GT.mxib) GOTO 903
71 ibit(nib) = nbits-i
72 RETURN
73 ELSEIF(r82i.LT.r8val) THEN
74 nib = nib + 1
75 IF(nib.GT.mxib) GOTO 903
76 ibit(nib) = nbits-i
77 r8val = r8val - r82i
78 ENDIF
79 ENDDO
80
81 RETURN
82900 CALL bort('BUFRLIB: UPFTBV - INPUT BUFR FILE IS CLOSED, IT '//
83 . 'MUST BE OPEN FOR INPUT')
84901 WRITE(bort_str,'("BUFRLIB: UPFTBV - MNEMONIC ",A,'//
85 . '" NOT FOUND IN TABLE B")') nemo
86 CALL bort(bort_str)
87902 WRITE(bort_str,'("BUFRLIB: UPFTBV - MNEMONIC ",A,'//
88 . '" IS NOT A FLAG TABLE")') nemo
89 CALL bort(bort_str)
90903 CALL bort('BUFRLIB: UPFTBV - IBIT ARRAY OVERFLOW')
91 END
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
Definition: bort.f:23
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
Definition: moda_tababd.F:10
character *128, dimension(:,:), allocatable tabb
Table B entries for each internal I/O stream.
Definition: moda_tababd.F:59
subroutine nemtab(LUN, NEMO, IDN, TAB, IRET)
This subroutine returns information about a descriptor from the internal DX BUFR tables,...
Definition: nemtab.f:45
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 upftbv(LUNIT, NEMO, VAL, MXIB, IBIT, NIB)
Given a Table B mnemonic with flag table units and a corresponding numerical data value,...
Definition: upftbv.f:38
function valx(STR)
This function decodes a real number from a character string.
Definition: valx.f:26