C @(#)adjpsf.for 17.1.1.1 (ES0-DMD) 01/25/02 17:15:38 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 C+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ C C C C----------------------------------------------------------------------- SUBROUTINE ADJPSF(RARR, LPXL, LSBP, CPSF) IMPLICIT NONE C REAL RARR(64) ! IN: Real keywords INTEGER LPXL ! IN: Half-number of p.s.f. pixels INTEGER LSBP ! IN: Half-number of subpixels REAL CPSF((-LPXL):LPXL,(-LPXL):LPXL, & (-LSBP):LSBP,(-LSBP):LSBP) ! MOD: Two dimensional p.s.f. C INTEGER I INTEGER ITMP INTEGER I1, I2 INTEGER J INTEGER J1, J2 INTEGER K INTEGER K1, K2 INTEGER L INTEGER L1, L2 C REAL A1 REAL CORR REAL TEMP, TEMP1, TEMP2 C C *** Calculate average of two first points in C *** one-dimensional point spread function. A1 = 10.0 ** (-RARR(14)) TEMP1 = ( 1.0 + 8.0 * ( 10.0 ** (-RARR(14)) ) ) / 9.0 C C *** Select matching region of two-dimensional p.s.f. C I1 = MAX( -1 , -LPXL ) I2 = MIN( 1 , LPXL ) J1 = MAX( -1 , -LPXL ) J2 = MIN( 1 , LPXL ) K1 = -LSBP K2 = LSBP L1 = -LSBP L2 = LSBP C C *** Calculate corresponding average of two-dimensional p.s.f. C TEMP = 0.0 DO 10 L = L1 , L2 DO 20 K = K1 , K2 DO 30 J = J1 , J2 DO 40 I = I1 , I2 TEMP2 = TEMP2 + CPSF(I,J,K,L) 40 CONTINUE 30 CONTINUE 20 CONTINUE 10 CONTINUE ITMP = ( ( (2*LSBP+1)**2 ) * (J2-J1+1) * (I2-I1+1) ) TEMP2 = TEMP2 / FLOAT(ITMP) IF ( TEMP2 .LE. 0.0 ) RETURN IF ( LPXL .EQ. 0 ) THEN CORR = 1.0 / TEMP2 ELSE CORR = TEMP1 / TEMP2 ENDIF C C *** Correct two-dimensional point spread function. C DO 50 L = L1 , L2 DO 60 K = K1 , K2 DO 70 J = -LPXL , LPXL DO 80 I = -LPXL , LPXL CPSF(I,J,K,L) = CPSF(I,J,K,L) * CORR 80 CONTINUE 70 CONTINUE 60 CONTINUE 50 CONTINUE C RETURN END