NCEPLIBS-bufr  12.2.0
ciencode.F90
Go to the documentation of this file.
1 
5 
24 subroutine pkc(chr,nchr,ibay,ibit)
25 
26  use modv_vars, only: nbitw, nbytw, iordle, iordbe
27 
28  implicit none
29 
30  character*(*), intent(in) :: chr
31  character*1 cval(8)
32 
33  integer, intent(in) :: nchr
34  integer, intent(out) :: ibay(*)
35  integer, intent(inout) :: ibit
36  integer ival(2), lb, i, nwd, nbt, nbit, int, msk, irev
37 
38  equivalence(cval,ival)
39 
40  ! Set lb to point to the "low-order" (i.e. least significant) byte within a machine word.
41 
42 #ifdef BIG_ENDIAN
43  lb = iordbe(nbytw)
44 #else
45  lb = iordle(nbytw)
46 #endif
47 
48  ival(1) = 0
49  nbit = 8
50 
51  do i=1,nchr
52  if(i<=len(chr)) then
53  cval(lb) = chr(i:i)
54  else
55  cval(lb) = ' '
56  endif
57 
58  nwd = ibit/nbitw + 1
59  nbt = mod(ibit,nbitw)
60  int = ishft(ival(1),nbitw-nbit)
61  int = ishft(int,-nbt)
62  msk = ishft( -1,nbitw-nbit)
63  msk = ishft(msk,-nbt)
64  ibay(nwd) = irev(ior(iand(irev(ibay(nwd)),not(msk)),int))
65  if(nbt+nbit>nbitw) then
66 
67  ! This character will not fit within the current word (i.e. array member) of ibay, because there
68  ! are less than 8 bits of space left. Store as many bits as will fit within the current
69  ! word and then store the remaining bits within the next word.
70 
71  int = ishft(ival(1),2*nbitw-(nbt+nbit))
72  msk = ishft( -1,2*nbitw-(nbt+nbit))
73  ibay(nwd+1) = irev(ior(iand(irev(ibay(nwd+1)),not(msk)),int))
74  endif
75  ibit = ibit + nbit
76  enddo
77 
78  return
79 end subroutine pkc
80 
96 subroutine pkb8(nval,nbits,ibay,ibit)
97 
98  use modv_vars, only: nbitw
99 
100  implicit none
101 
102  integer*8, intent(in) :: nval
103  integer, intent(in) :: nbits
104  integer, intent(out) :: ibay(*)
105  integer, intent(inout) :: ibit
106 
107  integer*8 :: nval8
108  integer :: nval4, nvals(2)
109 
110  equivalence(nval8,nvals)
111 
112  if(nbits<0) call bort('bufrlib: pkb8 - nbits < zero !!!!!')
113  if(nbits>64) call bort('bufrlib: pkb8 - nbits > 64 !!!!!')
114 
115  nval8=nval
116  nval4=nvals(2)
117  call pkb(nval4,max(nbits-nbitw,0),ibay,ibit)
118  nval4=nvals(1)
119  call pkb(nval4,min(nbits,nbitw),ibay,ibit)
120 
121  return
122 end subroutine pkb8
123 
139 subroutine pkb(nval,nbits,ibay,ibit)
140 
141  use modv_vars, only: nbitw
142 
143  implicit none
144 
145  integer, intent(in) :: nval, nbits
146  integer, intent(out) :: ibay(*)
147  integer, intent(inout) :: ibit
148  integer nwd, nbt, ival, int, msk, irev
149 
150  character*156 bort_str
151 
152  if(nbits>nbitw) then
153  write(bort_str,'("BUFRLIB: PKB - NUMBER OF BITS BEING PACKED '// &
154  ', NBITS (",I4,"), IS > THE INTEGER WORD LENGTH ON THIS MACHINE, NBITW (",I3,")")') nbits,nbitw
155  call bort(bort_str)
156  endif
157 
158  nwd = ibit/nbitw + 1
159  nbt = mod(ibit,nbitw)
160  ival = nval
161  if(ishft(ival,-nbits)>0) ival = -1
162  int = ishft(ival,nbitw-nbits)
163  int = ishft(int,-nbt)
164  msk = ishft(-1,nbitw-nbits)
165  msk = ishft(msk,-nbt)
166  ibay(nwd) = irev(ior(iand(irev(ibay(nwd)),not(msk)),int))
167  if(nbt+nbits>nbitw) then
168 
169  ! There are less than nbits bits remaining within the current word (i.e. array member) of ibay,
170  ! so store as many bits as will fit within the current word and then store the remaining bits
171  ! within the next word.
172 
173  int = ishft(ival,2*nbitw-(nbt+nbits))
174  msk = ishft( -1,2*nbitw-(nbt+nbits))
175  ibay(nwd+1) = irev(ior(iand(irev(ibay(nwd+1)),not(msk)),int))
176  endif
177 
178  ibit = ibit + nbits
179 
180  return
181 end subroutine pkb
182 
193 recursive subroutine ipkm(cbay,nbyt,n)
194 
195  use modv_vars, only: im8b, nbytw
196 
197  implicit none
198 
199  integer, intent(in) :: n, nbyt
200  integer my_n, my_nbyt, int, irev, i
201 
202  character*(*), intent(out) :: cbay
203  character*128 bort_str
204  character*4 cint
205 
206  equivalence(cint,int)
207 
208  ! Check for I8 integers.
209 
210  if(im8b) then
211  im8b=.false.
212 
213  call x84(n,my_n,1)
214  call x84(nbyt,my_nbyt,1)
215  call ipkm(cbay,my_nbyt,my_n)
216 
217  im8b=.true.
218  return
219  endif
220 
221  if(nbyt>nbytw) then
222  write(bort_str,'("BUFRLIB: IPKM - NUMBER OF BYTES BEING PACKED '// &
223  ', NBYT (",I4,"), IS > THE INTEGER WORD LENGTH ON THIS MACHINE, NBYTW (",I3,")")') nbyt,nbytw
224  call bort(bort_str)
225  endif
226 
227  int = irev(ishft(n,(nbytw-nbyt)*8))
228  do i=1,nbyt
229  cbay(i:i) = cint(i:i)
230  enddo
231 
232  return
233 end subroutine ipkm
234 
251 integer*8 function ipks(val,node) result(i8ret)
252 
253  use moda_tables
254  use moda_nrv203
255 
256  implicit none
257 
258  integer*8 imask
259  integer, intent(in) :: node
260  integer jj
261 
262  real*8, parameter :: ten = 10.
263  real*8, intent(in) :: val
264 
265  i8ret = nint(val * ten**isc(node),8) - irf(node)
266 
267  if ( nnrv > 0 ) then
268  ! There are redefined reference values in the jump/link table, so we need to check if this node is affected by any of them.
269  do jj = 1, nnrv
270  if ( node == inodnrv(jj) ) then
271  ! This node contains a redefined reference value. Per the rules of BUFR, negative values should be encoded as positive
272  ! integers with the left-most bit set to 1.
273  nrv(jj) = nint(val)
274  if ( nrv(jj) < 0 ) then
275  imask = 2_8**(ibt(node)-1)
276  i8ret = ior(abs(nrv(jj)),imask)
277  else
278  i8ret = nrv(jj)
279  end if
280  return
281  else if ( ( tag(node)(1:8) == tagnrv(jj) ) .and. ( node >= isnrv(jj) ) .and. ( node <= ienrv(jj) ) ) then
282  ! The corresponding redefinded reference value needs to be used when encoding this value.
283  i8ret = nint(val * ten**isc(node),8) - nrv(jj)
284  return
285  end if
286  end do
287  end if
288 
289  return
290 end function ipks
recursive subroutine bort(str)
Log an error message, then either return to or abort the application program.
Definition: borts.F90:15
subroutine pkc(chr, nchr, ibay, ibit)
Encode a character string within a specified number of bytes of an integer array, starting at the bit...
Definition: ciencode.F90:25
integer *8 function ipks(val, node)
Pack a real*8 value into an integer by applying the proper scale and reference values.
Definition: ciencode.F90:252
recursive subroutine ipkm(cbay, nbyt, n)
Encode an integer value within a specified number of bytes of a character string, up to a maximum of ...
Definition: ciencode.F90:194
subroutine pkb(nval, nbits, ibay, ibit)
Encode an integer value within a specified number of bits of an integer array, starting at the bit im...
Definition: ciencode.F90:140
subroutine pkb8(nval, nbits, ibay, ibit)
Encode an 8-byte integer value within a specified number of bits of an integer array,...
Definition: ciencode.F90:97
integer function irev(n)
Return a copy of an integer value with the bytes possibly reversed.
Definition: misc.F90:236
Declare arrays and variables for use with any 2-03-YYY (change reference value) operators present wit...
integer, dimension(:), allocatable ienrv
End of entry range in jump/link table, within which the corresponding new reference value in nrv will...
character *8, dimension(:), allocatable tagnrv
Table B mnemonic to which the corresponding new reference value in nrv applies.
integer, dimension(:), allocatable isnrv
Start of entry range in jump/link table, within which the corresponding new reference value in nrv wi...
integer nnrv
Number of entries in the jump/link table which contain new reference values (up to a maximum of mxnrv...
integer *8, dimension(:), allocatable nrv
New reference values corresponding to inodnrv.
integer, dimension(:), allocatable inodnrv
Entries within jump/link table which contain new reference values.
Declare arrays and variables used to store the internal jump/link table.
integer, dimension(:), allocatable irf
Reference values corresponding to tag and typ:
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
subroutine x84(iin8, iout4, nval)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x4884.F90:65