source: CONFIG_DEVT/IPSLCM6.5_work_ENSEMBLES/oasis3-mct/examples/test_interpolation/distance_rad.f90 @ 5725

Last change on this file since 5725 was 5725, checked in by aclsce, 3 years ago

Added new oasis3-MCT version to be used to handle ensembles simulations with XIOS.

File size: 2.8 KB
Line 
1       FUNCTION distance_rad (lon1, lat1, lon2, lat2)
2!****
3!               *****************************
4!               * OASIS ROUTINE  -  LEVEL ? *
5!               * -------------     ------- *
6!               *****************************
7!
8!**** *distance*  - calculate the distance between two points on a sphere
9!
10!     Purpose:
11!     -------
12!     Calculation of the distance between two points on a sphere
13!       1. Transformation to x,y,z-coordinates
14!       2. Calculating the distance
15!       3. Calculating the distance on the sphere
16!
17!**   Interface:
18!     ---------
19!       *CALL*  *distance_rad*(lon1, lat1, lon2, lat2)
20!
21!     Input:
22!     -----
23!          lon1              : longitude of first point (rad)
24!          lat1              : latitude of first point (rad)
25!          lon2              : longitude of second point (rad)
26!          lat2              : latitude of second point (rad)
27!
28!     Output:
29!     ------
30!          distance          : distance
31!!
32!     History:
33!     -------
34!       Version   Programmer     Date        Description
35!       -------   ----------     ----        ----------- 
36!       2.5       V. Gayler      2001/09/20  created
37!
38!-----------------------------------------------------------------------
39      USE mod_oasis
40
41      IMPLICIT NONE
42!-----------------------------------------------------------------------
43!     INTENT(IN)
44!-----------------------------------------------------------------------
45      REAL (kind=ip_double_p), INTENT(IN) :: lon1, & ! longitude of first point (rad)
46                                             lon2, & ! longitude of second point (rad)
47                                             lat1, & ! latitude of first point (rad)
48                                             lat2    ! latitude of second point (rad)
49
50!-----------------------------------------------------------------------
51!     LOCAL VARIABLES
52!-----------------------------------------------------------------------
53      REAL (kind=ip_double_p) :: x1, y1, z1, & ! coordinates of the first point
54                                 x2, y2, z2, & ! coordinates of the second point
55                                 distance_rad ! distance between the points (rad)
56
57!-----------------------------------------------------------------------
58
59!     Transformation to x,y,z-coordinates
60!     -----------------------------------
61      x1 = cos(lat1)*cos(lon1)
62      y1 = cos(lat1)*sin(lon1)
63      z1 = sin(lat1)
64
65      x2 = cos(lat2)*cos(lon2)
66      y2 = cos(lat2)*sin(lon2)
67      z2 = sin(lat2)
68
69!     Calculation of the distance
70!     ---------------------------
71!     direct distance:
72      distance_rad = SQRT((x2-x1)**2 + (y2-y1)**2 + (z2-z1)**2)
73
74!     distance along the surface:
75      distance_rad= 2.d0*ASIN(distance_rad/2.d0)
76
77!-----------------------------------------------------------------------
78      RETURN
79      END FUNCTION distance_rad
80
Note: See TracBrowser for help on using the repository browser.