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