NCEPLIBS-g2  3.4.7
simpack.f
Go to the documentation of this file.
1 
4 
25  subroutine simpack(fld,ndpts,idrstmpl,cpack,lcpack)
26  use intmath
27  implicit none
28 
29  integer,intent(in) :: ndpts
30  real,intent(in) :: fld(ndpts)
31  character(len=1),intent(out) :: cpack(*)
32  integer,intent(inout) :: idrstmpl(*)
33  integer,intent(out) :: lcpack
34 
35  real(4) :: ref,rmin4
36 
37  integer(4) :: iref
38  integer :: ifld(ndpts)
39  integer,parameter :: zero=0
40  integer :: nbittot, nbits, maxnum, maxdif, left
41  integer :: imax, imin, j
42  real :: rmax, rmin, temp, dscale, bscale
43 
44  bscale=2.0**real(-idrstmpl(2))
45  dscale=10.0**real(idrstmpl(3))
46  if (idrstmpl(4).le.0.OR.idrstmpl(4).gt.31) then
47  nbits=0
48  else
49  nbits=idrstmpl(4)
50  endif
51 
52 ! Find max and min values in the data
53  if(ndpts<1) then
54  rmin=0
55  rmax=0
56  else
57  rmax=fld(1)
58  rmin=fld(1)
59  do j=2,ndpts
60  if (fld(j).gt.rmax) rmax=fld(j)
61  if (fld(j).lt.rmin) rmin=fld(j)
62  enddo
63  endif
64 
65 ! If max and min values are not equal, pack up field.
66 ! If they are equal, we have a constant field, and the reference
67 ! value (rmin) is the value for each point in the field and
68 ! set nbits to 0.
69  if (rmin.ne.rmax) then
70 
71  ! Determine which algorithm to use based on user-supplied
72  ! binary scale factor and number of bits.
73  if (nbits.eq.0.AND.idrstmpl(2).eq.0) then
74 
75  ! No binary scaling and calculate minumum number of
76  ! bits in which the data will fit.
77  imin=nint(rmin*dscale)
78  imax=nint(rmax*dscale)
79  maxdif=imax-imin
80  temp=i1log2(maxdif+1)
81  nbits=ceiling(temp)
82  rmin=real(imin)
83  ! scale data
84  do j=1,ndpts
85  ifld(j)=nint(fld(j)*dscale)-imin
86  enddo
87  elseif (nbits.ne.0.AND.idrstmpl(2).eq.0) then
88 
89  ! Use minimum number of bits specified by user and
90  ! adjust binary scaling factor to accomodate data.
91  rmin=rmin*dscale
92  rmax=rmax*dscale
93  maxnum=(2**nbits)-1
94  temp=ilog2(nint(real(maxnum)/(rmax-rmin)))
95  idrstmpl(2)=ceiling(-1.0*temp)
96  bscale=2.0**real(-idrstmpl(2))
97  ! scale data
98  do j=1,ndpts
99  ifld(j)=max(0,nint(((fld(j)*dscale)-rmin)*bscale))
100  enddo
101  elseif (nbits.eq.0.AND.idrstmpl(2).ne.0) then
102 
103  ! Use binary scaling factor and calculate minumum number of
104  ! bits in which the data will fit.
105  rmin=rmin*dscale
106  rmax=rmax*dscale
107  maxdif=nint((rmax-rmin)*bscale)
108  temp=i1log2(maxdif)
109  nbits=ceiling(temp)
110  ! scale data
111  do j=1,ndpts
112  ifld(j)=max(0,nint(((fld(j)*dscale)-rmin)*bscale))
113  enddo
114  elseif (nbits.ne.0.AND.idrstmpl(2).ne.0) then
115 
116  ! Use binary scaling factor and use minumum number of
117  ! bits specified by user. Dangerous - may loose
118  ! information if binary scale factor and nbits not set
119  ! properly by user.
120  rmin=rmin*dscale
121  ! scale data
122  do j=1,ndpts
123  ifld(j)=max(0,nint(((fld(j)*dscale)-rmin)*bscale))
124  enddo
125  endif
126 
127  ! Pack data, Pad last octet with Zeros, if necessary,
128  ! and calculate the length of the packed data in bytes
129  call g2_sbytesc(cpack,ifld,0,nbits,0,ndpts)
130  nbittot=nbits*ndpts
131  left=8-mod(nbittot,8)
132  if (left.ne.8) then
133  call g2_sbytec(cpack,zero,nbittot,left) ! Pad with zeros to fill Octet
134  nbittot=nbittot+left
135  endif
136  lcpack=nbittot/8
137 
138  else
139  !print *,'nbits 0'
140  nbits=0
141  lcpack=0
142  endif
143 
144 
145 ! Fill in ref value and number of bits in Template 5.0
146  rmin4 = real(rmin, 4)
147  call mkieee(rmin4,ref,1) ! ensure reference value is IEEE format
148  iref=transfer(ref,iref)
149  idrstmpl(1)=iref
150  idrstmpl(4)=nbits
151  idrstmpl(5)=0 ! original data were reals
152 
153  end
subroutine g2_sbytec(out, in, iskip, nbits)
Put arbitrary size values into a packed bit string, taking the low order bits from each value in the ...
Definition: g2_gbytesc.F90:42
subroutine g2_sbytesc(out, in, iskip, nbits, nskip, n)
Put arbitrary size values into a packed bit string, taking the low order bits from each value in the ...
Definition: g2_gbytesc.F90:120
subroutine mkieee(a, rieee, num)
Copy an array of real to an array of 32-bit IEEE floating points.
Definition: mkieee.F90:14
Define math functions used by compack(), simpack(), and misspack().
Definition: intmath.f:22
subroutine simpack(fld, ndpts, idrstmpl, cpack, lcpack)
Pack up a data field using a simple packing algorithm as defined in the GRIB2 documention.
Definition: simpack.f:26