[daip] Bug in PBCOR ?

Eric Greisen egreisen at cv3.cv.nrao.edu
Mon Apr 9 13:10:27 EDT 2001


Found it and made a new patch:

ID:           4.
Task:         PBCOR

Summary:      PBCOR will not handle data cubes properly due to an
              error in the scaling of parameters by the low-level
              subroutine that computes the correction.

Files:        /31DEC00/APL/SUB/PBCALC.FOR

Fix:          1. Fetch the file listed above and place it in the
                 corresponding area ($APLSUB) on your system.
              2. COMRPL $APLSUB/PBCALC.FOR
              3. COMLNK $APLPGM/PBCOR
              4. COMLNK $APGNOT/{FACES,SETFC,PATGN}

Documentor:   Eric Greisen
Date:         2001-04-09


------------ CUT HERE ------------------------------------------
      SUBROUTINE PBCALC (ANGLE, LAMBDA, CPARM, BMFACT)
C-----------------------------------------------------------------------
C! Computes the (single-dish) primary beam power
C# Imaging
C-----------------------------------------------------------------------
C;  Copyright (C) 2000
C;  Associated Universities, Inc. Washington DC, USA.
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 Massachusetts Ave, Cambridge,
C;  MA 02139, USA.
C;
C;  Correspondence concerning AIPS should be addressed as follows:
C;         Internet email: aipsmail at nrao.edu.
C;         Postal address: AIPS Project Office
C;                         National Radio Astronomy Observatory
C;                         520 Edgemont Road
C;                         Charlottesville, VA 22903-2475 USA
C-----------------------------------------------------------------------
C   Estimates the beam factor
C   Inputs:
C      ANGLE    D      Angle from pointing position (deg)
C      LAMBDA   D      Wavelength
C   In/out:
C      CPARM    R(6)   Beam parameters: (1) flag, (2-6) parms
C   Outputs:
C      BMFACT   R      Beam value (> = 0.01)
C-----------------------------------------------------------------------
      DOUBLE PRECISION ANGLE, LAMBDA
      REAL      CPARM(6), BMFACT
C
      INCLUDE 'INCS:PSTD.INC'
      INTEGER   I
      REAL      PBCORF, TABLE(3,8)
      LOGICAL   FIRST
      DOUBLE PRECISION X, BMPARM(7), BMULT, Y, FREQ, PLAMBD
      SAVE PLAMBD, BMPARM, BMULT
      DATA PLAMBD /0.0D0/
      DATA TABLE / 0.000,  0.000,  0.000,
     *             0.000,  0.000,  0.000,
     *            -1.343,  6.579, -1.186,
     *            -1.372,  6.940, -1.309,
     *            -1.306,  6.253, -1.100,
     *            -1.305,  6.155, -1.030,
     *            -1.417,  7.332, -1.352,
     *            -1.321,  6.185, -0.983/
C-----------------------------------------------------------------------
      BMFACT = 0.0
      FREQ = VELITE / LAMBDA / 1.0D9
      FIRST = LAMBDA.NE.PLAMBD
      PLAMBD = LAMBDA
C                                       74 MHz ("4-Band")
      IF (FREQ.LT.0.15) THEN
         IF (FIRST) THEN
C                                       new form
            BMPARM(1) = 42.0D0
            BMPARM(2) = 1.17D-3
            BMPARM(3) = 2.04D-5
            BMULT = VELITE / LAMBDA / 73.8D6
            IF ((CPARM(1).GT.0.0) .AND. (CPARM(2).NE.0.0)) THEN
               BMPARM(1) = CPARM(2)
               BMPARM(2) = CPARM(3)
               BMPARM(3) = CPARM(4)
               END IF
            FIRST = .FALSE.
            CPARM(1) = 1.0
            CPARM(2) = BMPARM(1)
            CPARM(3) = BMPARM(2)
            CPARM(4) = BMPARM(3)
            CPARM(5) = 0.0
            CPARM(6) = 0.0
            END IF
         X = (ANGLE * BMULT)
         Y = X * X
         IF (X.LE.13.0) THEN
            PBCORF = EXP(Y/BMPARM(1)) + Y * (BMPARM(2) + Y * BMPARM(3))
            BMFACT = 1.0 / PBCORF
            END IF
C                                       P band
      ELSE IF (FREQ.LT.1.1) THEN
         IF (FIRST) THEN
C                                       new form
            BMULT = VELITE / LAMBDA / 327.5D6
            BMPARM(1) = 0.9739D0
            BMPARM(2) = -0.4364D0
            BMPARM(3) = 0.0261D0
            IF ((CPARM(1).GT.0.0) .AND. (CPARM(2).NE.0.0)) THEN
               BMPARM(1) = CPARM(2)
               BMPARM(2) = CPARM(3)
               BMPARM(3) = CPARM(4)
               BMPARM(4) = CPARM(5)
               BMPARM(5) = CPARM(6)
               END IF
            FIRST = .FALSE.
            CPARM(1) = 1.0
            CPARM(2) = BMPARM(1)
            CPARM(3) = BMPARM(2)
            CPARM(4) = BMPARM(3)
            CPARM(5) = BMPARM(4)
            CPARM(6) = BMPARM(5)
            END IF
         X = ANGLE * BMULT
         IF (X.LT.5.5) BMFACT = BMPARM(1) * EXP (BMPARM(2)*X*X) +
     *      BMPARM(3)
C                                       Normal VLA bands
      ELSE
         IF (FIRST) THEN
            BMULT = FREQ * 60.0D0
            IF (FREQ.LT.2.) THEN
               I = 3
            ELSE IF (FREQ.LT.6) THEN
               I = 4
            ELSE IF (FREQ.LT.10.) THEN
               I = 5
            ELSE IF (FREQ.LT.18) THEN
               I = 6
            ELSE IF (FREQ.LT.30.) THEN
               I = 7
            ELSE
               I = 8
               END IF
            BMPARM(1) = TABLE(1,I) * 1.0D-3
            BMPARM(2) = TABLE(2,I) * 1.0D-7
            BMPARM(3) = TABLE(3,I) * 1.0D-10
            BMPARM(4) = 0.0D0
            BMPARM(5) = 0.0D0
            IF ((CPARM(1).GT.0.0) .AND. (CPARM(2).NE.0.0)) THEN
               BMPARM(1) = CPARM(2) * 1.0D-3
               BMPARM(2) = CPARM(3) * 1.0D-7
               BMPARM(3) = CPARM(4) * 1.0D-10
               BMPARM(4) = CPARM(5) * 1.0D-13
               BMPARM(5) = CPARM(6) * 1.0D-16
               END IF
            FIRST = .FALSE.
            CPARM(1) = 1.0
            CPARM(2) = BMPARM(1) * 1.0D+3
            CPARM(3) = BMPARM(2) * 1.0D+7
            CPARM(4) = BMPARM(3) * 1.0D+10
            CPARM(5) = BMPARM(4) * 1.0D+13
            CPARM(6) = BMPARM(5) * 1.0D+16
            END IF
         X = (ANGLE * BMULT) ** 2
         BMFACT = 1.0 + (BMPARM(1) + (BMPARM(2) + (BMPARM(3) +
     *      (BMPARM(4) + BMPARM(5) * X) * X) * X) * X) * X
         END IF
C                                       here, make some "reasonable"
C                                       estimate on the rumbling around
C                                       in far sidelobes, and the depths
C                                       of the nulls...
      BMFACT = MIN (1.0, MAX (BMFACT, 0.01))
C
 999  RETURN
      END



More information about the Daip mailing list