1C Copyright 1981-2016 ECMWF.
2C
3C This software is licensed under the terms of the Apache Licence
4C Version 2.0 which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
5C
6C In applying this licence, ECMWF does not waive the privileges and immunities
7C granted to it by virtue of its status as an intergovernmental organisation
8C nor does it submit to any jurisdiction.
9C
10
11      INTEGER FUNCTION NUMPTWE(WEST,EAST,GRIDSTEP)
12C
13C---->
14C**** NUMPTWE
15C
16C     Purpose
17C     -------
18C
19C     Calculate number of grid points in the range from west to east.
20C
21C
22C     Interface
23C     ---------
24C
25C     IRET = NUMPTWE(WEST,EAST,GRIDSTEP)
26C
27C     Input
28C     -----
29C
30C     WEST     - Western boundary in degrees
31C     EAST     - Eastern boundary in degrees
32C     GRIDSTEP - Grid interval in degrees
33C
34C
35C     Output
36C     ------
37C
38C     Function returns the number of grid points in the east-west
39C     interval.
40C
41C
42C     Method
43C     ------
44C
45C     The grid is assumed to start at Greenwich.
46C
47C
48C     Externals
49C     ---------
50C
51C     None.
52C
53C     Author
54C     ------
55C
56C     J.D.Chambers     ECMWF     Nov 1997
57C
58C
59C     Modifications
60C     -------------
61C
62C     None.
63C
64C----<
65C
66      IMPLICIT NONE
67C
68C     Function arguments
69C
70      REAL EAST, WEST, GRIDSTEP
71C
72C     Local variables
73C
74      INTEGER NL
75      REAL*8 DEAST, DWEST
76      REAL*8 LEFT, RIGHT, STEP, EPS
77      DATA EPS/1.0E-3/
78C
79C     Statement function
80      LOGICAL EQUAL
81      REAL*8 A, B
82      EQUAL(A,B) = ( ABS(A-B) .LT.EPS )
83C
84C ------------------------------------------------------------------
85C     Section 1.   Initialise
86C ------------------------------------------------------------------
87C
88  100 CONTINUE
89C
90C     Make all longitudes positive for calculation of difference
91C
92      DEAST = EAST
93      DWEST = WEST
94      RIGHT = DEAST + 360.0
95      LEFT  = DWEST + 360.0
96      STEP  = GRIDSTEP
97      IF( RIGHT.LT.LEFT) RIGHT = RIGHT + 360.0
98C
99C ------------------------------------------------------------------
100C     Section 2.   Calculate the number of points in the interval
101C ------------------------------------------------------------------
102C
103  200 CONTINUE
104C
105C     Equal boundaries
106C
107      IF( EQUAL(LEFT,RIGHT) ) THEN
108        NUMPTWE = 1
109        GOTO 900
110      ENDIF
111C
112C     Calculate offset of westernmost gridpoint
113C
114      NL = INT((LEFT+EPS)/STEP)
115      IF( .NOT. EQUAL(LEFT,(NL*STEP)) ) NL = NL + 1
116C
117      RIGHT = RIGHT - (NL*STEP)
118      NUMPTWE = INT((RIGHT+EPS)/STEP) + 1
119C
120C ------------------------------------------------------------------
121C     Section 9.   Return
122C ------------------------------------------------------------------
123C
124  900 CONTINUE
125C
126      RETURN
127      END
128