NCEPLIBS-w3emc  2.11.0
w3fi82.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Convert to second diff array
3 C> @author Bill Cavanaugh @date 1993-07-14
4 
5 C> Accept an input array, convert to array of second
6 C> differences. return the original first value and the first
7 C> first-difference as separate values. align data in
8 C> boustrephedonic style, (alternate row reversal).
9 C>
10 C> Program history log:
11 C> - Bill Cavanaugh 1993-07-14
12 C> - Bill Cavanaugh 1994-01-27 Added reversal of even numbered rows
13 C> (boustrophedonic processing)
14 C> - Bill Cavanaugh 1994-03-02 Corrected improper ordering of even
15 C> numbered rows
16 C> - Ebisuzaki 1999-12-06 Linux port
17 C>
18 C> @param[inout] IFLD
19 C> - [in] Integer input array
20 C> - [out] Second differenced field
21 C> @param[in] NPTS Number of points in array
22 C> @param[in] IGDS
23 C> - (5) Number of rows in array
24 C> - (4) Number of columns in array
25 C> @param[in] PDS (8) Flag indicating presence of gds section
26 C> @param[out] FVAL1 Floating point original first value
27 C> @param[out] FDIFF1 Floating point first first-difference
28 C>
29 C> @author Bill Cavanaugh @date 1993-07-14
30  SUBROUTINE w3fi82 (IFLD,FVAL1,FDIFF1,NPTS,PDS,IGDS)
31 C
32  REAL FVAL1,FDIFF1
33 C
34  INTEGER IFLD(*),NPTS,NBOUST(300),IGDS(*)
35 C
36  CHARACTER*1 PDS(*)
37 C
38 C ---------------------------------------------
39 C TEST FOR PRESENCE OF GDS
40 C
41 c 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)
46 C
47 C LAY OUT DATA BOUSTROPHEDONIC STYLE
48 C
49 C PRINT*, ' DATA SET UP BOUSTROPHEDON'
50 C
51  DO 210 i = 2, nrow, 2
52 C
53 C REVERSE THE EVEN NUMBERED ROWS
54 C
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
64 C
65 C
66  END IF
67 C =================================================================
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
74 C
75 C SPECIAL FOR GRIB
76 C FLOAT OUTPUT OF FIRST POINTS TO ANTICIPATE
77 C GRIB FLOATING POINT OUTPUT
78 C
79  fval1 = ifld(1)
80  fdiff1 = ifld(2)
81 C
82 C SET FIRST TWO POINTS TO SECOND DIFF VALUE FOR BETTER PACKING
83 C
84  ifld(1) = ifld(3)
85  ifld(2) = ifld(3)
86 C -----------------------------------------------------------
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