NCEPLIBS-w3emc  2.11.0
gbytes.f
Go to the documentation of this file.
1 C> @file
2 C> @brief This is the fortran version of gbytes.
3 C> @author Dr. Robert C. Gammill @date 1972-05
4 
5 C> Program history log:
6 C> - Russell E. Jones 1991-03
7 C> Changes for SiliconGraphics IRIS-4D/25
8 C> SiliconGraphics 3.3 FORTRAN 77
9 C>
10 C> To unpack a series of bytes into a target
11 C> array. Each unpacked byte is right-justified
12 C> in its target word, and the remainder of the
13 C> word is zero-filled.
14 C>
15 C> @param[in] IPACKD The word or array containing the packed bytes.
16 C> @param[out] IUNPKD The array which will contain the unpacked bytes.
17 C> @param[in] NOFF The initial number of bits to skip, left to right,
18 C> in 'IPACKD' in order to locate the first byte to unpack.
19 C> @param[in] NBITS Number of bits in the byte to be unpacked.
20 C> Maximum of 64 bits on 64 bit machine, 32 bits on 32 bit machine.
21 C> @param[in] ISKIP The number of bits to skip between each byte in
22 C> 'IPACKD' in order to locate the next byte to be unpacked.
23 C> @param[in] ITER The number of bytes to be unpacked.
24 C>
25  SUBROUTINE gbytes(IPACKD,IUNPKD,NOFF,NBITS,ISKIP,ITER)
26 
27  INTEGER IPACKD(*)
28 
29  INTEGER IUNPKD(*)
30  INTEGER MASKS(64)
31 C
32  SAVE
33 C
34  DATA ifirst/1/
35  IF(ifirst.EQ.1) THEN
36  CALL w3fi01(lw)
37  nbitsw = 8 * lw
38  jshift = -1 * nint(alog(float(nbitsw)) / alog(2.0))
39  masks(1) = 1
40  DO i=2,nbitsw-1
41  masks(i) = 2 * masks(i-1) + 1
42  ENDDO
43  masks(nbitsw) = -1
44  ifirst = 0
45  ENDIF
46 C
47 C NBITS MUST BE LESS THAN OR EQUAL TO NBITSW
48 C
49  icon = nbitsw - nbits
50  IF (icon.LT.0) RETURN
51  mask = masks(nbits)
52 C
53 C INDEX TELLS HOW MANY WORDS INTO THE ARRAY 'IPACKD' THE NEXT BYTE
54 C APPEARS.
55 C
56  index = ishft(noff,jshift)
57 C
58 C II TELLS HOW MANY BITS THE BYTE IS FROM THE LEFT SIDE OF THE WORD.
59 C
60  ii = mod(noff,nbitsw)
61 C
62 C ISTEP IS THE DISTANCE IN BITS FROM THE START OF ONE BYTE TO THE NEXT.
63 C
64  istep = nbits + iskip
65 C
66 C IWORDS TELLS HOW MANY WORDS TO SKIP FROM ONE BYTE TO THE NEXT.
67 C
68  iwords = istep / nbitsw
69 C
70 C IBITS TELLS HOW MANY BITS TO SKIP AFTER SKIPPING IWORDS.
71 C
72  ibits = mod(istep,nbitsw)
73 C
74  DO 10 i = 1,iter
75 C
76 C MOVER SPECIFIES HOW FAR TO THE RIGHT A BYTE MUST BE MOVED IN ORDER
77 C
78 C TO BE RIGHT ADJUSTED.
79 C
80  mover = icon - ii
81 C
82 C THE BYTE IS SPLIT ACROSS A WORD BREAK.
83 C
84  IF (mover.LT.0) THEN
85  movel = - mover
86  mover = nbitsw - movel
87  iunpkd(i) = iand(ior(ishft(ipackd(index+1),movel),
88  & ishft(ipackd(index+2),-mover)),mask)
89 C
90 C RIGHT ADJUST THE BYTE.
91 C
92  ELSE IF (mover.GT.0) THEN
93  iunpkd(i) = iand(ishft(ipackd(index+1),-mover),mask)
94 C
95 C THE BYTE IS ALREADY RIGHT ADJUSTED.
96 C
97  ELSE
98  iunpkd(i) = iand(ipackd(index+1),mask)
99  ENDIF
100 C
101 C INCREMENT II AND INDEX.
102 C
103  ii = ii + ibits
104  index = index + iwords
105  IF (ii.GE.nbitsw) THEN
106  ii = ii - nbitsw
107  index = index + 1
108  ENDIF
109 C
110  10 CONTINUE
111  RETURN
112  END
subroutine gbytes(IPACKD, IUNPKD, NOFF, NBITS, ISKIP, ITER)
Program history log:
Definition: gbytes.f:26
subroutine w3fi01(LW)
Determines the number of bytes in a full word for the particular machine (IBM or cray).
Definition: w3fi01.f:19