source: lmdz_wrf/WRFV3/external/io_grib2/g2lib/gbytesc.F @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 3.7 KB
Line 
1      SUBROUTINE G2LIB_GBYTE(IN,IOUT,ISKIP,NBYTE)
2      character*1 in(*)
3      integer iout(*)
4      CALL G2LIB_GBYTES(IN,IOUT,ISKIP,NBYTE,0,1)
5      RETURN
6      END
7
8      SUBROUTINE G2LIB_SBYTE(OUT,IN,ISKIP,NBYTE)
9      character*1 out(*)
10      integer in(*)
11      CALL G2LIB_SBYTES(OUT,IN,ISKIP,NBYTE,0,1)
12      RETURN
13      END
14
15      SUBROUTINE G2LIB_GBYTES(IN,IOUT,ISKIP,NBYTE,NSKIP,N)
16C          Get bytes - unpack bits:  Extract arbitrary size values from a
17C          packed bit string, right justifying each value in the unpacked
18C          array.
19C            IN    = character*1 array input
20C            IOUT  = unpacked array output
21C            ISKIP = initial number of bits to skip
22C            NBYTE = number of bits to take
23C            NSKIP = additional number of bits to skip on each iteration
24C            N     = number of iterations
25C v1.1
26C
27      character*1 in(*)
28      integer iout(*)
29      integer ones(8), tbit, bitcnt
30      save ones
31      data ones/1,3,7,15,31,63,127,255/
32
33c     nbit is the start position of the field in bits
34      nbit = iskip
35      do i = 1, n
36         bitcnt = nbyte
37         index=nbit/8+1
38         ibit=mod(nbit,8)
39         nbit = nbit + nbyte + nskip
40
41c        first byte
42         tbit = min(bitcnt,8-ibit)
43         itmp = iand(mova2i(in(index)),ones(8-ibit))
44         if (tbit.ne.8-ibit) itmp = ishft(itmp,tbit-8+ibit)
45         index = index + 1
46         bitcnt = bitcnt - tbit
47
48c        now transfer whole bytes
49         do while (bitcnt.ge.8)
50             itmp = ior(ishft(itmp,8),mova2i(in(index)))
51             bitcnt = bitcnt - 8
52             index = index + 1
53         enddo
54
55c        get data from last byte
56         if (bitcnt.gt.0) then
57             itmp = ior(ishft(itmp,bitcnt),iand(ishft(mova2i(in(index)),
58     1          -(8-bitcnt)),ones(bitcnt)))
59         endif
60
61         iout(i) = itmp
62      enddo
63
64      RETURN
65      END                                                                 
66
67      SUBROUTINE G2LIB_SBYTES(OUT,IN,ISKIP,NBYTE,NSKIP,N)
68C          Store bytes - pack bits:  Put arbitrary size values into a
69C          packed bit string, taking the low order bits from each value
70C          in the unpacked array.
71C            IOUT  = packed array output
72C            IN    = unpacked array input
73C            ISKIP = initial number of bits to skip
74C            NBYTE = number of bits to pack
75C            NSKIP = additional number of bits to skip on each iteration
76C            N     = number of iterations
77C v1.1
78C
79      character*1 out(*)
80      integer in(N), bitcnt, ones(8), tbit
81      save ones
82      data ones/    1,  3,  7, 15, 31, 63,127,255/
83
84c     number bits from zero to ...
85c     nbit is the last bit of the field to be filled
86
87      nbit = iskip + nbyte - 1
88      do i = 1, n
89         itmp = in(i)
90         bitcnt = nbyte
91         index=nbit/8+1
92         ibit=mod(nbit,8)
93         nbit = nbit + nbyte + nskip
94
95c        make byte aligned
96         if (ibit.ne.7) then
97             tbit = min(bitcnt,ibit+1)
98             imask = ishft(ones(tbit),7-ibit)
99             itmp2 = iand(ishft(itmp,7-ibit),imask)
100             itmp3 = iand(mova2i(out(index)), 255-imask)
101             out(index) = char(ior(itmp2,itmp3))
102             bitcnt = bitcnt - tbit
103             itmp = ishft(itmp, -tbit)
104             index = index - 1
105         endif
106
107c        now byte aligned
108
109c        do by bytes
110         do while (bitcnt.ge.8)
111             out(index) = char(iand(itmp,255))
112             itmp = ishft(itmp,-8)
113             bitcnt = bitcnt - 8
114             index = index - 1
115         enddo
116
117c        do last byte
118
119         if (bitcnt.gt.0) then
120             itmp2 = iand(itmp,ones(bitcnt))
121             itmp3 = iand(mova2i(out(index)), 255-ones(bitcnt))
122             out(index) = char(ior(itmp2,itmp3))
123         endif
124      enddo
125
126      return
127      end
Note: See TracBrowser for help on using the repository browser.