source: trunk/src/distance2.f90 @ 28

Last change on this file since 28 was 4, checked in by mlanger, 11 years ago
File size: 3.1 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22!-----------------------------------------------------------------------
23function distance2(rlat1,rlon1,rlat2,rlon2)
24
25  !$$$  SUBPROGRAM DOCUMENTATION BLOCK
26  !
27  ! SUBPROGRAM:  GCDIST     COMPUTE GREAT CIRCLE DISTANCE
28  !   PRGMMR: IREDELL       ORG: W/NMC23       DATE: 96-04-10
29  !
30  ! ABSTRACT: THIS SUBPROGRAM COMPUTES GREAT CIRCLE DISTANCE
31  !      BETWEEN TWO POINTS ON THE EARTH. COORDINATES ARE GIVEN IN RADIANS!
32  !
33  ! PROGRAM HISTORY LOG:
34  !   96-04-10  IREDELL
35  !
36  ! USAGE:    ...GCDIST(RLAT1,RLON1,RLAT2,RLON2)
37  !
38  !   INPUT ARGUMENT LIST:
39  !rlat1    - REAL LATITUDE OF POINT 1 IN RADIANS
40  !rlon1    - REAL LONGITUDE OF POINT 1 IN RADIANS
41  !rlat2    - REAL LATITUDE OF POINT 2 IN RADIANS
42  !rlon2    - REAL LONGITUDE OF POINT 2 IN RADIANS
43  !
44  !   OUTPUT ARGUMENT LIST:
45  !distance2   - REAL GREAT CIRCLE DISTANCE IN KM
46  !
47  ! ATTRIBUTES:
48  !   LANGUAGE: Fortran 90
49  !
50  !$$$
51
52  use par_mod, only: dp
53
54  implicit none
55
56  real                    :: rlat1,rlon1,rlat2,rlon2,distance2
57  real(kind=dp)           :: clat1,clat2,slat1,slat2,cdlon,crd
58  real(kind=dp),parameter :: rerth=6.3712e6_dp
59  real(kind=dp),parameter :: pi=3.14159265358979_dp
60
61  if ((abs(rlat1-rlat2).lt.0.0003).and. &
62       (abs(rlon1-rlon2).lt.0.0003)) then
63    distance2=0.0_dp
64  else
65
66  ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
67    clat1=cos(real(rlat1,kind=dp))
68    slat1=sin(real(rlat1,kind=dp))
69    clat2=cos(real(rlat2,kind=dp))
70    slat2=sin(real(rlat2,kind=dp))
71    cdlon=cos(real(rlon1-rlon2,kind=dp))
72    crd=slat1*slat2+clat1*clat2*cdlon
73    distance2=real(rerth*acos(crd)/1000.0_dp)
74  endif
75  ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
76end function distance2
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG