* Last processed by NICE on 12-Jun-2000 15:54:00 * Customized for : IEEE, LINUX, UNIX, MOTIF, F77 * makplan_elcon.f * SUBROUTINE ELCON(MAPD_AZ,MAPW_AZ,MAPD_EL,MAPW_EL,YCOORD,IFUN) * C******************************************************************* c this subroutine makes the az-el map from the azimuth scans * c by convolution of the data onto the number grid of the map * c array 'amap'. in the process it noise-filters in the elevation * c direction and regrids the data to allow for an elevation * c offset. * C******************************************************************* * * IMPLICIT NONE * INCLUDE 'const.inc' INCLUDE 'parameter.inc' INCLUDE 'makplan.inc' * * REAL*4 MAPD_AZ(1) ! corresponds to mapd_az(1,isubscan,ich REAL*4 MAPW_AZ(1) ! corresponds to mapw_az(1,isubscan,ich REAL*4 MAPD_EL(1) ! corresponds to mapd_az(1,isubscan,ich REAL*4 MAPW_EL(1) ! corresponds to mapw_az(1,isubscan,ich REAL*4 YCOORD * REAL*8 FUNWID,TOTWID REAL*8 X,Z,ZK REAL*8 POS, MAGI, DIAMETER * INTEGER IFIRST,ILAST INTEGER I,J,IJ,IFUNC,IFUN * * C The unit length of the new grid is YINC in elevation * C Compute function window width in the new system unit : C funwid = lambda/(1.67*diam_telescope)/yinc C funwid = 1.34 if freq=230ghz, diam_telescope=30m and yinc=4arcsec * MAGI = 0 IF (IFUN.EQ.1) MAGI = 1.6806492007530D0 ! Parabolic IF (IFUN.EQ.2) MAGI = 1.6982249549743D0 ! Gaussian IF (IFUN.EQ.3) MAGI = 1.8363197305085D0 ! Linear IF (MAGI.EQ.0) MAGI = 1.6574002064571D0 ! No taper * DIAMETER = 30 IF (TELESCOPE(1:3).EQ.'CSO') DIAMETER = 10 IF (TELESCOPE(1:3).EQ.'HHT') DIAMETER = 10 FUNWID = VLIGHT/FREQUENCY /(MAGI*DIAMETER) $/(XINC*SEC_TO_RAD) * IF (FUNWID.LT.1D0) FUNWID = 1D0 TOTWID = 4D0 * FUNWID * POS = (YCOORD/10.+ ABS(OELV)*3600.)/YINC +1.0005D0 ! position of row in * new grid * IFIRST = POS - TOTWID + 1D0 ILAST = POS + TOTWID IF (IFIRST.LT.1) IFIRST = 1 IF (ILAST.GT.NROW) ILAST = NROW * DO I = 1, NCOL IJ = I + (IFIRST-1)*NCOL * DO J = IFIRST, ILAST X = (FLOAT(J) - POS) / FUNWID X = ABS(X) IFUNC = NINT(5D1*X)+1 Z = FUNC(IFUNC) ZK = MAPD_AZ(I) * MAPW_AZ(I) * Z MAPD_EL(IJ) = MAPD_EL(IJ) + SNGL(ZK) MAPW_EL(IJ) = MAPW_EL(IJ) + MAPW_AZ(I)* SNGL(Z) IJ = IJ + NCOL ENDDO ENDDO * RETURN END * * * * * * *