C @(#)gauss3d.for 17.1.1.1 (ES0-DMD) 01/25/02 17:10:48 C=========================================================================== C Copyright (C) 1995 European Southern Observatory (ESO) C C This program is free software; you can redistribute it and/or C modify it under the terms of the GNU General Public License as C published by the Free Software Foundation; either version 2 of C the License, or (at your option) any later version. C C This program is distributed in the hope that it will be useful, C but WITHOUT ANY WARRANTY; without even the implied warranty of C MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the C GNU General Public License for more details. C C You should have received a copy of the GNU General Public C License along with this program; if not, write to the Free C Software Foundation, Inc., 675 Massachusetss Ave, Cambridge, C MA 02139, USA. C C Corresponding concerning ESO-MIDAS should be addressed as follows: C Internet e-mail: midas@eso.org C Postal address: European Southern Observatory C Data Management Division C Karl-Schwarzschild-Strasse 2 C D 85748 Garching bei Muenchen C GERMANY C=========================================================================== C SUBROUTINE GAUSS3(X,NP,PARAM,Y1,DERIV) C+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ C.COPYRIGHT: Copyright (c) 1987 European Southern Observatory, C all rights reserved C C.VERSION: 1.0 ESO-FORTRAN Conversion, AA 18:01 - 21 DEC 1987 C C.LANGUAGE: F77+ESOext C C.AUTHOR: J.D.PONZ C C-------------------------------------------------------------- C********************************************** C C IMPLICIT NONE C Three-dimensional Gaussian Distribution C C********************************************** C C Author: O.-G. Richter, ESO Garching C INTEGER NP DOUBLE PRECISION Y1,PARAM(NP),DERIV(NP) REAL X(3) DOUBLE PRECISION R11,R22,R33,R12,R13,R23,R,R1 DOUBLE PRECISION A,B,C,D,E,F,O,P,Q DOUBLE PRECISION B2,C2,D2,B22,C22,D22,E1,E2,E3 C ! \ R11 = 1.0D0 - PARAM(10)*PARAM(10) ! > Diagonals R22 = 1.0D0 - PARAM(9)*PARAM(9) ! / R33 = 1.0D0 - PARAM(8)*PARAM(8) C ! of correlation determ. ! \ R12 = PARAM(9)*PARAM(10) - PARAM(8) ! > Non-diagonals R13 = PARAM(8)*PARAM(10) - PARAM(9) ! / R23 = PARAM(8)*PARAM(9) - PARAM(10) C ! Total residual dispersion R = 2.0D0*R12*PARAM(8) + R11 + R22 - 1.0 ! and its inverse R1 = 1.0D0/R C A = 0.6931471806D0*R1 C B = (X(1)-PARAM(2))/PARAM(5) C = (X(2)-PARAM(3))/PARAM(6) D = (X(3)-PARAM(4))/PARAM(7) B2 = B*B C2 = C*C D2 = D*D B22 = B2*R11 C22 = C2*R22 D22 = D2*R33 C DERIV(1) = DEXP(-A* (B22+C22+D22+2.0* (B*C*R12+B*D*R13+C*D*R23))) C Y1 = DERIV(1)*PARAM(1) A = 2.0*A*Y1 C DERIV(2) = A* (B*R11+C*R12+D*R13)/PARAM(5) DERIV(3) = A* (B*R12+C*R22+D*R23)/PARAM(6) DERIV(4) = A* (B*R13+C*R23+D*R33)/PARAM(7) DERIV(5) = DERIV(2)*B DERIV(6) = DERIV(3)*C DERIV(7) = DERIV(4)*D A = A*R1 E = 2.0*R12*R13 E1 = E - PARAM(8)*R E2 = E - PARAM(9)*R E3 = E - PARAM(10)*R F = B22 + C22 + D22 O = B*C P = B*D Q = C*D C DERIV(8) = A* (R12*F+D2*PARAM(8)*R+O* (2.0*R12*R12+R)+P*E3+Q*E2) DERIV(9) = A* (R13*F+C2*PARAM(9)*R+O*E3+P* (2.0*R13*R13+R)+Q*E1) DERIV(10) = A* (R23*F+B2*PARAM(10)*R+O*E2+P*E1+Q* (2.0*R23*R23+R)) C RETURN END