NCEPLIBS-w3emc 2.12.0
Loading...
Searching...
No Matches
w3fi83.f
Go to the documentation of this file.
1C> @file
2C> @brief Restore delta packed data to original.
3C> @author Bill Cavanaugh @date 1993-08-18
4
5C> Restore delta packed data to original values
6C> restore from boustrephedonic alignment.
7C>
8C> Program history log:
9C> - Bill Cavanaugh 1993-07-14
10C> - John Satckpole 1993-07-22 Additions to fix scaling.
11C> - Bill Cavanaugh 1994-01-27 Added reversal of even numbered rows
12C> (boustrophedonic processing) to restore
13C> data to original sequence.
14C> - Bill Cavanaugh 1994-03-02 Corrected reversal of even numbered rows.
15C> - Mark Iredell 1995-10-31 Removed saves and prints.
16C>
17C> @param[inout] DATA
18C> - [in] Second order differences.
19C> - [out] Expanded original data values.
20C> @param[in] NPTS Number of points in array.
21C> @param[in] FVAL1 Original first entry in array.
22C> @param[in] FDIFF1 Original first first-difference.
23C> @param[in] ISCAL2 Power-of-two exponent for unscaling.
24C> @param[in] ISC10 Power-of-ten exponent for unscaling.
25C> @param[in] KPDS Array of information for pds.
26C> @param[in] KGDS Array of information for gds.
27C>
28C> @note Subprogram can be called from a multiprocessing environment.
29C>
30C> @author Bill Cavanaugh @date 1993-08-18
31 SUBROUTINE w3fi83 (DATA,NPTS,FVAL1,FDIFF1,ISCAL2,
32 * ISC10,KPDS,KGDS)
33C
34 REAL FVAL1,FDIFF1
35 REAL DATA(*),BOUST(200)
36 INTEGER NPTS,NROW,NCOL,KPDS(*),KGDS(*),ISC10
37C ---------------------------------------
38C
39C REMOVE DECIMAL UN-SCALING INTRODUCED DURING UNPACKING
40C
41 dscal = 10.0 ** isc10
42 IF (dscal.EQ.0.0) THEN
43 DO 50 i=1,npts
44 DATA(i) = 1.0
45 50 CONTINUE
46 ELSE IF (dscal.EQ.1.0) THEN
47 ELSE
48 DO 51 i=1,npts
49 DATA(i) = DATA(i) * dscal
50 51 CONTINUE
51 END IF
52C
53 DATA(1) = fval1
54 DATA(2) = fdiff1
55 DO 200 j = 3,2,-1
56 DO 100 k = j, npts
57 DATA(k) = DATA(k) + DATA(k-1)
58 100 CONTINUE
59 200 CONTINUE
60C
61C NOW REMOVE THE BINARY SCALING FROM THE RECONSTRUCTED FIELD
62C AND THE DECIMAL SCALING TOO
63C
64 IF (dscal.EQ.0) THEN
65 scale = 0.0
66 ELSE
67 scale =(2.0**iscal2)/dscal
68 END IF
69 DO 300 i=1,npts
70 DATA(i) = DATA(i) * scale
71 300 CONTINUE
72C ==========================================================
73 IF (iand(kpds(4),128).NE.0) THEN
74 nrow = kgds(3)
75 ncol = kgds(2)
76C
77C DATA LAID OUT BOUSTROPHEDONIC STYLE
78C
79C
80C PRINT*, ' REVERSE BOUSTROPHEDON'
81 DO 210 i = 2, nrow, 2
82C
83C REVERSE THE EVEN NUMBERED ROWS
84C
85 DO 201 j = 1, ncol
86 npos = i * ncol - j + 1
87 boust(j) = DATA(npos)
88 201 CONTINUE
89 DO 202 j = 1, ncol
90 npos = ncol * (i-1) + j
91 DATA(npos) = boust(j)
92 202 CONTINUE
93 210 CONTINUE
94C
95C
96 END IF
97C =================================================================
98 RETURN
99 END
subroutine w3fi83(data, npts, fval1, fdiff1, iscal2, isc10, kpds, kgds)
Restore delta packed data to original values restore from boustrephedonic alignment.
Definition w3fi83.f:33