NCEPLIBS-bufr  12.0.0
pkb.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Encode an integer value within an integer array.
3 C>
4 C> @author J. Woollen @date 1994-01-06
5 
6 C> This subroutine encodes an integer value within a specified
7 C> number of bits of an integer array, starting at the bit
8 C> immediately after a specified bit within the array.
9 C>
10 C> @param[in] NVAL -- integer: Value to be encoded
11 C> @param[in] NBITS -- integer: Number of bits of IBAY within
12 C> which to encode NVAL
13 C> @param[out] IBAY -- integer(*): Array containing encoded NVAL
14 C> @param[in,out] IBIT -- integer: Bit pointer within IBAY
15 C> - On input, IBIT points to the bit within
16 C> IBAY after which to begin encoding NVAL.
17 C> - On output, IBIT points to the last bit
18 C> of IBAY which contains the encoded NVAL.
19 C>
20 C> @remarks
21 C> - This subroutine is the logical inverse of subroutine upb().
22 C> - This subroutine will not work properly if NBITS is greater than
23 C> the number of bits in an integer, as determined via
24 C> an internal call to subroutine wrdlen().
25 C>
26 C> @author J. Woollen @date 1994-01-06
27  SUBROUTINE pkb(NVAL,NBITS,IBAY,IBIT)
28 
29  COMMON /hrdwrd/ nbytw,nbitw,iord(8)
30 
31  dimension ibay(*)
32 
33  CHARACTER*156 BORT_STR
34 
35 C----------------------------------------------------------------------
36 C----------------------------------------------------------------------
37 
38  IF(nbits.GT.nbitw) GOTO 900
39 
40  nwd = ibit/nbitw + 1
41  nbt = mod(ibit,nbitw)
42  ival = nval
43  IF(ishft(ival,-nbits).GT.0) ival = -1
44  int = ishft(ival,nbitw-nbits)
45  int = ishft(int,-nbt)
46  msk = ishft( -1,nbitw-nbits)
47  msk = ishft(msk,-nbt)
48  ibay(nwd) = irev(ior(iand(irev(ibay(nwd)),not(msk)),int))
49  IF(nbt+nbits.GT.nbitw) THEN
50 
51 C There are less than NBITS bits remaining within the current
52 C word (i.e. array member) of IBAY, so store as many bits as
53 C will fit within the current word and then store the remaining
54 C bits within the next word.
55 
56  int = ishft(ival,2*nbitw-(nbt+nbits))
57  msk = ishft( -1,2*nbitw-(nbt+nbits))
58  ibay(nwd+1) = irev(ior(iand(irev(ibay(nwd+1)),not(msk)),int))
59  ENDIF
60 
61  ibit = ibit + nbits
62 
63  RETURN
64 900 WRITE(bort_str,'("BUFRLIB: PKB - NUMBER OF BITS BEING PACKED '//
65  . ', NBITS (",I4,"), IS > THE INTEGER WORD LENGTH ON THIS '//
66  . 'MACHINE, NBITW (",I3,")")')
67  . nbits,nbitw
68  CALL bort(bort_str)
69  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
function irev(N)
This function will, when the local machine is "little-endian" (i.e., when it uses a right to left sch...
Definition: irev.F:33
subroutine pkb(NVAL, NBITS, IBAY, IBIT)
This subroutine encodes an integer value within a specified number of bits of an integer array,...
Definition: pkb.f:28