NCEPLIBS-w3emc 2.12.0
Loading...
Searching...
No Matches
getbit.f
Go to the documentation of this file.
1C> @file
2C> @brief Compute number of bits and round field.
3C> @author Mark Iredell @date 1992-10-31
4
5C> The number of bits required to pack a given field.
6C> The field is rounded off to the decimal scaling for packing.
7C> The minimum and maximum rounded field values are also returned.
8C> For particular binary and decimal scalings is computed.
9C> Grib bitmap masking for valid data is optionally used.
10C>
11C> Program history log:
12C> - Mark Iredell 1996-09-16
13C>
14C> @param[in] IBM Integer bitmap flag (=0 for no bitmap).
15C> @param[in] IBS Integer binary scaling (e.g. ibs=3 to round field
16C> to nearest eighth value).
17C> @param[in] IDS Integer decimal scaling (e.g. ids=3 to round field
18C> to nearest milli-value) (note that ids and ibs can both be nonzero,
19C> e.g. ids=1 and ibs=1 rounds to the nearest twentieth).
20C> @param[in] LEN Integer length of the field and bitmap.
21C> @param[in] MG Integer (LEN) bitmap if ibm=1 (0 to skip, 1 to keep).
22C> @param[in] G Real (LEN) field.
23C> @param[out] GROUND Real (LEN) field rounded to decimal and binary scaling
24C> (set to zero where bitmap is 0 if ibm=1).
25C> @param[out] GMIN Real minimum valid rounded field value.
26C> @param[out] GMAX Real maximum valid rounded field value.
27C> @param[out] NBIT Integer number of bits to pack.
28C>
29C> @note CRAY FORTRAN
30C>
31C> @author Mark Iredell @date 1992-10-31
32 SUBROUTINE getbit(IBM,IBS,IDS,LEN,MG,G,GROUND,GMIN,GMAX,NBIT)
33 dimension mg(len),g(len),ground(len)
34C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
35C ROUND FIELD AND DETERMINE EXTREMES WHERE BITMAP IS ON
36 s=2.**ibs*10.**ids
37 IF(ibm.EQ.0) THEN
38 ground(1)=nint(g(1)*s)/s
39 gmax=ground(1)
40 gmin=ground(1)
41 DO i=2,len
42 ground(i)=nint(g(i)*s)/s
43 gmax=max(gmax,ground(i))
44 gmin=min(gmin,ground(i))
45 ENDDO
46 ELSE
47 i1=1
48 dowhile(i1.LE.len.AND.mg(i1).EQ.0)
49 i1=i1+1
50 ENDDO
51 IF(i1.LE.len) THEN
52 DO i=1,i1-1
53 ground(i)=0.
54 ENDDO
55 ground(i1)=nint(g(i1)*s)/s
56 gmax=ground(i1)
57 gmin=ground(i1)
58 DO i=i1+1,len
59 IF(mg(i).NE.0) THEN
60 ground(i)=nint(g(i)*s)/s
61 gmax=max(gmax,ground(i))
62 gmin=min(gmin,ground(i))
63 ELSE
64 ground(i)=0.
65 ENDIF
66 ENDDO
67 ELSE
68 DO i=1,len
69 ground(i)=0.
70 ENDDO
71 gmax=0.
72 gmin=0.
73 ENDIF
74 ENDIF
75C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
76C COMPUTE NUMBER OF BITS
77 nbit=log((gmax-gmin)*s+0.9)/log(2.)+1.
78C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
79 RETURN
80 END
subroutine getbit(ibm, ibs, ids, len, mg, g, ground, gmin, gmax, nbit)
The number of bits required to pack a given field.
Definition getbit.f:33