NCEPLIBS-ip  4.1.0
movect.F90
Go to the documentation of this file.
1 
4 
25  SUBROUTINE movect(FLAT,FLON,TLAT,TLON,CROT,SROT)
26  IMPLICIT NONE
27 !
28  INTEGER, PARAMETER :: KD=selected_real_kind(15,45)
29 !
30  REAL, INTENT(IN ) :: FLAT, FLON
31  REAL, INTENT(IN ) :: TLAT, TLON
32  REAL, INTENT( OUT) :: CROT, SROT
33 !
34  REAL(KIND=kd), PARAMETER :: crdlim=0.9999999
35  REAL(KIND=kd), PARAMETER :: pi=3.14159265358979
36  REAL(KIND=kd), PARAMETER :: dpr=180./pi
37 !
38  REAL(KIND=kd) :: ctlat,stlat,cflat,sflat
39  REAL(KIND=kd) :: cdlon,sdlon,crd
40  REAL(KIND=kd) :: srd2rn,str,ctr,sfr,cfr
41 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
42 ! COMPUTE COSINE OF THE RADIAL DISTANCE BETWEEN THE POINTS.
43  ctlat=cos(tlat/dpr)
44  stlat=sin(tlat/dpr)
45  cflat=cos(flat/dpr)
46  sflat=sin(flat/dpr)
47  cdlon=cos((flon-tlon)/dpr)
48  sdlon=sin((flon-tlon)/dpr)
49  crd=stlat*sflat+ctlat*cflat*cdlon
50 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
51 ! COMPUTE ROTATIONS AT BOTH POINTS WITH RESPECT TO THE GREAT CIRCLE
52 ! AND COMBINE THEM TO GIVE THE TOTAL VECTOR ROTATION PARAMETERS.
53  IF(abs(crd).LE.crdlim) THEN
54  srd2rn=-1/(1-crd**2)
55  str=cflat*sdlon
56  ctr=cflat*stlat*cdlon-sflat*ctlat
57  sfr=ctlat*sdlon
58  cfr=ctlat*sflat*cdlon-stlat*cflat
59  crot=real(srd2rn*(ctr*cfr-str*sfr))
60  srot=real(srd2rn*(ctr*sfr+str*cfr))
61 ! USE A DIFFERENT APPROXIMATION FOR NEARLY COINCIDENT POINTS.
62 ! MOVING VECTORS TO ANTIPODAL POINTS IS AMBIGUOUS ANYWAY.
63  ELSE
64  crot=real(cdlon)
65  srot=real(sdlon*stlat)
66  ENDIF
67 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
68  END SUBROUTINE movect
subroutine movect(FLAT, FLON, TLAT, TLON, CROT, SROT)
This subprogram provides the rotation parameters to move a vector along a great circle from one posit...
Definition: movect.F90:26