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