orog_mask_tools  1.13.0
find_limit.F90
Go to the documentation of this file.
1 
4 
14 !#define DIAG
15 SUBROUTINE find_limit (p1_in, p2_in, latmin, latmax)
16  REAL*8, INTENT(IN) :: p1_in(2), p2_in(2)
17  REAL*8, INTENT(OUT) :: latmin, latmax
18 
19  REAL*8 :: p1(2),p2(2), pm(2)
20  REAL*8 :: r2d = 180.0/acos(-1.0)
21 
22  p1 = p1_in/r2d; p2 = p2_in/r2d
23  latmin = min(p1(1), p2(1))
24  latmax = max(p1(1), p2(1))
25 
26  CALL middle(p1, p2, pm)
27 #ifdef DIAG
28  print*, 'before loop', p1(1)*r2d,p2(1)*r2d,pm(1)*r2d
29 #endif
30 
31  DO WHILE (abs(p1(1)-p2(1)) > 0.00001 .AND. &
32  abs(p1(2)-p2(2)) > 0.00001 )
33  IF (abs(p1(1)-pm(1)) < abs(p2(1)-pm(1))) THEN
34  p2 = pm
35  ELSE
36  p1 = pm
37  ENDIF
38  CALL middle(p1, p2, pm)
39 #ifdef DIAG
40  print*, 'in loop', p1(1)*r2d,p2(1)*r2d, pm(1)*r2d
41 #endif
42  ENDDO
43 
44  latmin = min(latmin, pm(1))
45  latmax = max(latmax, pm(1))
46 
47  latmin = latmin *r2d
48  latmax = latmax *r2d
49 
50 END SUBROUTINE find_limit
51 
79 SUBROUTINE middle(p1,p2,p)
80  IMPLICIT NONE
81 
82  ! Two given points in lat/lon:
83  REAL*8, INTENT(IN) :: p1(2),p2(2)
84  REAL*8, INTENT(OUT) :: p(2)
85  REAL*8 :: pi
86 
87  REAL*8 :: xyz1(3),xyz2(3),xyz(3)
88 
89  pi = acos(-1.0)
90 
91  ! Convert them into Cardesian coor:
92  xyz1(1) = cos(p1(1)) * cos(p1(2))
93  xyz1(2) = cos(p1(1)) * sin(p1(2))
94  xyz1(3) = sin(p1(1))
95 
96  xyz2(1) = cos(p2(1)) * cos(p2(2))
97  xyz2(2) = cos(p2(1)) * sin(p2(2))
98  xyz2(3) = sin(p2(1))
99 
100  ! middle point:
101 
102 ! coeff = 0.5 / sqrt((1.0 + dot_product(xyz1,xyz2)) / 2)
103 ! xyz = coeff * (xyz1 + xyz2)
104 
105  xyz = 0.5 * (xyz1 + xyz2)
106 
107  xyz = xyz / sqrt(dot_product(xyz,xyz))
108 
109  ! Convert the middle point to lat/lon coor:
110  p(1) = atan2(xyz(3), sqrt(xyz(1) * xyz(1) + xyz(2) * xyz(2)))
111  p(2) = atan2(xyz(2), xyz(1))
112 
113  IF (p(2) < -pi / 2.0) THEN
114  p(2) = p(2) + 2 * pi
115  END IF
116 
117 END SUBROUTINE middle
118 
subroutine find_limit(p1_in, p2_in, latmin, latmax)
Given two points on a cubed-sphere grid, compute the maximum and minimum latitudinal extent of the re...
Definition: find_limit.F90:16
subroutine middle(p1, p2, p)
Compute the latitude and longitude of the middle point between two given points.
Definition: find_limit.F90:80