NCEPLIBS-w3emc 2.12.0
Loading...
Searching...
No Matches
w3fi82.f
Go to the documentation of this file.
1C> @file
2C> @brief Convert to second diff array
3C> @author Bill Cavanaugh @date 1993-07-14
4
5C> Accept an input array, convert to array of second
6C> differences. return the original first value and the first
7C> first-difference as separate values. align data in
8C> boustrephedonic style, (alternate row reversal).
9C>
10C> Program history log:
11C> - Bill Cavanaugh 1993-07-14
12C> - Bill Cavanaugh 1994-01-27 Added reversal of even numbered rows
13C> (boustrophedonic processing)
14C> - Bill Cavanaugh 1994-03-02 Corrected improper ordering of even
15C> numbered rows
16C> - Ebisuzaki 1999-12-06 Linux port
17C>
18C> @param[inout] IFLD
19C> - [in] Integer input array
20C> - [out] Second differenced field
21C> @param[in] NPTS Number of points in array
22C> @param[in] IGDS
23C> - (5) Number of rows in array
24C> - (4) Number of columns in array
25C> @param[in] PDS (8) Flag indicating presence of gds section
26C> @param[out] FVAL1 Floating point original first value
27C> @param[out] FDIFF1 Floating point first first-difference
28C>
29C> @author Bill Cavanaugh @date 1993-07-14
30 SUBROUTINE w3fi82 (IFLD,FVAL1,FDIFF1,NPTS,PDS,IGDS)
31C
32 REAL FVAL1,FDIFF1
33C
34 INTEGER IFLD(*),NPTS,NBOUST(300),IGDS(*)
35C
36 CHARACTER*1 PDS(*)
37C
38C ---------------------------------------------
39C TEST FOR PRESENCE OF GDS
40C
41c looks like an error CALL GBYTE(PDS,IQQ,56,8)
42 call gbytec(pds,iqq,56,1)
43 IF (iqq.NE.0) THEN
44 nrow = igds(5)
45 ncol = igds(4)
46C
47C LAY OUT DATA BOUSTROPHEDONIC STYLE
48C
49C PRINT*, ' DATA SET UP BOUSTROPHEDON'
50C
51 DO 210 i = 2, nrow, 2
52C
53C REVERSE THE EVEN NUMBERED ROWS
54C
55 DO 200 j = 1, ncol
56 npos = i * ncol - j + 1
57 nboust(j) = ifld(npos)
58 200 CONTINUE
59 DO 201 j = 1, ncol
60 npos = ncol * (i-1) + j
61 ifld(npos) = nboust(j)
62 201 CONTINUE
63 210 CONTINUE
64C
65C
66 END IF
67C =================================================================
68 DO 4000 i = npts, 2, -1
69 ifld(i) = ifld(i) - ifld(i-1)
70 4000 CONTINUE
71 DO 5000 i = npts, 3, -1
72 ifld(i) = ifld(i) - ifld(i-1)
73 5000 CONTINUE
74C
75C SPECIAL FOR GRIB
76C FLOAT OUTPUT OF FIRST POINTS TO ANTICIPATE
77C GRIB FLOATING POINT OUTPUT
78C
79 fval1 = ifld(1)
80 fdiff1 = ifld(2)
81C
82C SET FIRST TWO POINTS TO SECOND DIFF VALUE FOR BETTER PACKING
83C
84 ifld(1) = ifld(3)
85 ifld(2) = ifld(3)
86C -----------------------------------------------------------
87 RETURN
88 END
subroutine gbytec(in, iout, iskip, nbyte)
Wrapper for gbytesc() limiting NSKIP and N to 0 and 1.
Definition gbytec.f:14
subroutine w3fi82(ifld, fval1, fdiff1, npts, pds, igds)
Accept an input array, convert to array of second differences.
Definition w3fi82.f:31