* Last processed by NICE on 12-Jun-2000 15:53:00 * Customized for : IEEE, LINUX, UNIX, MOTIF, F77 * nic_dangle.f * SUBROUTINE DANGLE(ALONG,ALAT,A) ************************************************************************ * version 1.0 mpifr cyber edition 22 may 1977. * * see nod 2 manual page m 9.1 * * c.g haslam mar 1972. * * this routine recovers the longitude and latitude angles, along * * (0 - 360) and alat ( +.- 180) in deg_to_radrees, which correspond to the * vector a. * ************************************************************************ * REAL*8 A(3) REAL*8 ALONG,ALAT REAL*8 AA * INCLUDE 'const.inc' * AA = A(1)*A(1)+A(2)*A(2) AA = DSQRT(AA) ALAT = 90.0D0 IF (AA.GE.0.000001D0) THEN AA = A(3)/AA ALAT = DATAN(AA)/DEG_TO_RAD ! latitude in deg_to_radrees ENDIF * IF (A(2).NE.0.D0 .OR. A(1).NE.0.D0) THEN ALONG=DATAN2(A(2),A(1))/DEG_TO_RAD ! longitude in deg_to_radrees ELSE ALONG = 0.D0 ENDIF * IF (ALONG.LT.0.0) ALONG=ALONG+360.0D0 RETURN END * SUBROUTINE DCOSIN(ALONG,ALAT,A) ! direction cosinus c*********************************************************************** c version 1.0 mpifr cyber edition 22 may 1977. * c see nod 2 manual page m 9.1 * c c.g haslam mar 1972. * c this routine computes the vector a for the angles, along and alat, * c which should be specified in deg_to_radrees. c*********************************************************************** * REAL*8 A(3) REAL*8 ALONG,ALAT REAL*8 X,Y,Z * INCLUDE 'const.inc' * X = DEG_TO_RAD*ALONG ! x in radians Y = DEG_TO_RAD*ALAT ! y in radians Z = DCOS(Y) A(1) = DCOS(X)*Z A(2) = DSIN(X)*Z A(3) = DSIN(Y) RETURN END * * SUBROUTINE MATMUL(MAT,A,B,N) c*********************************************************************** c version 1.0 mpifr cyber edition 22 may 1977. G.Haslam c version 2.0 iram c c this routine provides the transformation of vector a to vector b * c using the n dimensional direction cosine array, mat. * c*********************************************************************** * REAL*8 A(1),B(1),MAT(3,3) INTEGER I,J,N * IF (N.GT.0) THEN DO I=1,3 B(I) = 0.D0 DO J=1,3 B(I) = B(I)+MAT(I,J)*A(J) ENDDO ENDDO ELSE DO I=1,3 B(I) = 0.D0 DO J=1,3 B(I) = B(I)+MAT(J,I)*A(J) ENDDO ENDDO ENDIF RETURN END