module align_mod
! Uses
use precision_mod
use physicalconstants_mod
use det_geom_mod
use calibrations_mod
use chambers_mod
use filters_mod
use tdc_mod
use unp_mod
use kalman_mod
use residuals_mod
use cluster_mod
use namelist_mod
use resolution_mod
use trackswim_mod
use track_mod
use hists_mod
use pattern_mod
use projections_mod
! Variables
real (kind=r4), private, DIMENSION(MAX_PLANES_D) :: ResidAvePlane
real (kind=r4), private, DIMENSION(MAX_PLANES_D) :: RotationCorr
real (kind=r4), private, DIMENSION(MAX_PLANES_D,MAX_WIRES_D) :: ResidAveWire
real (kind=r4), private, DIMENSION(MAX_PLANES_D,LengthBinMax) :: ResidAvePlaneLength
integer (kind=i4), private :: NEVENTS
integer (kind=i4), private :: CountSumPlane
integer (kind=i4), private :: CountSumWire
integer (kind=i4), private :: AlignTest
integer (kind=i4), private :: PlaneIteration
integer (kind=i4), private :: WireIteration
integer (kind=i4), private, PARAMETER :: CountSumPlaneCut = 500
integer (kind=i4), private, PARAMETER :: CountSumWireCut = 500
integer (kind=i4), private, PARAMETER :: AngleMin = -10
integer (kind=i4), private, PARAMETER :: AngleMax = 10
integer (kind=i4), private, PARAMETER :: AngleStep = 2
integer (kind=i4), private :: angle
real (kind=r4), private, PARAMETER :: Sigma = 70.E-04
real (kind=r4), private :: SigmaU
real (kind=r4), private :: SigmaV
real (kind=r4), private :: ErrFitParsU
real (kind=r4), private :: ErrFitParsV
real (kind=r4), private :: Chi2FitU
real (kind=r4), private :: Chi2FitV
logical, private :: AlignFail
! Subroutines and functions
public subroutine Align (iWindow)
public subroutine AlignInit ()
private subroutine AlignPlaneShifts ()
private subroutine AlignWireShifts ()
private subroutine AlignPlaneRotations ()
private subroutine AlignBeamAngle ()
private subroutine AlignPC (iWindow)
public subroutine AlignPlaneShiftsPrint ()
public subroutine AlignWireShiftsPrint ()
private subroutine AlignPlaneRotationsPrint ()
public subroutine AlignField (iWindow, iTrack)
private subroutine AlignBeamAnglePrint ()
end module align_mod
real (kind=r4), private, DIMENSION(MAX_PLANES_D) :: ResidAvePlane
real (kind=r4), private, DIMENSION(MAX_PLANES_D) :: RotationCorr
real (kind=r4), private, DIMENSION(MAX_PLANES_D,MAX_WIRES_D) :: ResidAveWire
real (kind=r4), private, DIMENSION(MAX_PLANES_D,LengthBinMax) :: ResidAvePlaneLength
integer (kind=i4), private :: NEVENTS
integer (kind=i4), private :: CountSumPlane
integer (kind=i4), private :: CountSumWire
integer (kind=i4), private :: AlignTest
integer (kind=i4), private :: PlaneIteration
integer (kind=i4), private :: WireIteration
integer (kind=i4), private, PARAMETER :: CountSumPlaneCut = 500
integer (kind=i4), private, PARAMETER :: CountSumWireCut = 500
integer (kind=i4), private, PARAMETER :: AngleMin = -10
integer (kind=i4), private, PARAMETER :: AngleMax = 10
integer (kind=i4), private, PARAMETER :: AngleStep = 2
integer (kind=i4), private :: angle
real (kind=r4), private, PARAMETER :: Sigma = 70.E-04
real (kind=r4), private :: SigmaU
real (kind=r4), private :: SigmaV
real (kind=r4), private :: ErrFitParsU
real (kind=r4), private :: ErrFitParsV
real (kind=r4), private :: Chi2FitU
real (kind=r4), private :: Chi2FitV
logical, private :: AlignFail
public subroutine Align (iWindow)
integer (kind=i4) :: iWindow
! Calls: AlignBeamAngle, AlignInit, AlignPC, AlignPlaneRotations, AlignPlaneShifts, AlignWireShifts, HFILL, KalFit, Residuals, kerror
end subroutine Align
public subroutine AlignInit () end subroutine AlignInit
private subroutine AlignPlaneShifts ()
! Calls: AlignPlaneShiftsPrint, SetupChambers, hfithn, hnoent, hreset
end subroutine AlignPlaneShifts
$ SUBROUTINE AlignPlaneShifts
$
$ !========================================================
$ ! Author: Maher Quraan
$ ! Date: August 16, 2001
$ !--------------------------------------------------------
$ ! Calculate plane positions.
$ !========================================================
$
$ IMPLICIT NONE
$
$ INTEGER(i4):: plane, LengthBin
$
$ PlaneIteration = PlaneIteration + 1
$ DO plane = FirstPlaneDC, LastPlaneDC
$ DO LengthBin = 1, LengthBinMax
$ ResidPlane(plane)%count = ResidPlane(plane)%count + ResidPlaneLength(plane,LengthBin)%count
$ END DO
$ CountSumPlane = SUM(ResidPlane(plane)%count)
$ IF(CountSumPlane < CountSumPlaneCut) THEN
$ ResidAvePlane(plane) = 0.
$ CYCLE
$ ELSE
$ ResidPlane(plane)%sum = SUM(ResidPlaneLength(plane,:)%sum)
$ ResidAvePlane(plane) = ResidPlane(plane)%sum / FLOAT(CountSumPlane)
$
$ DCplane_corr(plane)%UVshift = DCplane_corr(plane)%UVshift - ResidAvePlane(plane)
$
$ ENDIF
$ ENDDO
$
$ ! Fix a line in space to align planes with respect to
$! DCplane_corr(1)%UVshift = 59.2998E-04
$! DCplane_corr(2)%UVshift = 86.7663E-04
$! DCplane_corr(7)%UVshift = 9.90694E-04
$! DCplane_corr(8)%UVshift = 95.3779E-04
$
$ IF(FixPlanes) THEN
$ DCplane_corr(FixedPlane1)%UVshift = 0.0
$ DCplane_corr(FixedPlane2)%UVshift = 0.0
$ DCplane_corr(FixedPlane3)%UVshift = 0.0
$ DCplane_corr(FixedPlane4)%UVshift = 0.0
$ ENDIF
$
$ CALL AlignPlaneShiftsPrint
$
$ !CALL SetupDCplanes
$ !CALL SetupDCwires
$ CALL SetupChambers
$
$ DO plane = FirstPlaneDC, LastPlaneDC
$ IF(ResidAvePlane(plane) /= 0) THEN
$ ResidPlane(plane)%sum = 0.
$ ResidPlane(plane)%count = 0
$ DO LengthBin = 1, LengthBinMax
$ ResidPlaneLength(plane,LengthBin)%sum = 0.
$ ResidPlaneLength(plane,LengthBin)%count(:) = 0
$ END DO
$ ENDIF
$ ENDDO
$
$END SUBROUTINE AlignPlaneShifts
private subroutine AlignWireShifts ()
! Calls: AlignWireShiftsPrint
end subroutine AlignWireShifts
private subroutine AlignPlaneRotations ()
! Calls: AlignPlaneRotationsPrint, SetupChambers, hfithn, hnoent, hreset
end subroutine AlignPlaneRotations
$ SUBROUTINE AlignPlaneRotations
$
$ !========================================================
$ ! Author: Maher Quraan
$ ! Date: August 27, 2001
$ !--------------------------------------------------------
$ ! Calculate plane positions.
$ !========================================================
$
$ IMPLICIT NONE
$
$ INTEGER(i4):: plane, LengthBin
$ LOGICAL:: init
$ REAL(r4), DIMENSION(LengthBinMax):: Vbin
$ REAL(r4):: RotationTan, RotationTanAve
$
$ PlaneIteration = PlaneIteration + 1
$ DO plane = FirstPlaneDC, LastPlaneDC
$ RotationTan = 0.
$ DO LengthBin = 1, LengthBinMax
$ CountSumPlane = SUM(ResidPlaneLength(plane,LengthBin)%count)
$ IF(CountSumPlane < CountSumPlaneCut) THEN
$ ResidAvePlaneLength(plane,LengthBin) = 0.
$ CYCLE
$ ELSE
$ ResidAvePlaneLength(plane,LengthBin) = &
$ ResidPlaneLength(plane,LengthBin)%sum / &
$ FLOAT(CountSumPlane)
$ Vbin(LengthBin) = -17.5 + LengthBinWidth/2. + &
$ (LengthBin-1)*LengthBinWidth
$ IF(Vbin(LengthBin)/=0) THEN
$ RotationTan = RotationTan + &
$ ABS(ResidAvePlaneLength(plane,LengthBin))/&
$ ABS(Vbin(LengthBin))
$ ENDIF
$ ENDIF
$ ENDDO
$ RotationTanAve = RotationTan/(LengthBinMax-1)
$ RotationCorr(plane) = 180.0/PI*ATAN(RotationTanAve)
$ IF((ResidAvePlaneLength(plane,LengthBinMax) + &
$ ResidAvePlaneLength(plane,LengthBinMax-1) - &
$ ResidAvePlaneLength(plane,1)-ResidAvePlaneLength(plane,2) > 0)) &
$ RotationCorr(plane) = -RotationCorr(plane)
$ DCplane_corr(plane)%rotation = DCplane_corr(plane)%rotation + RotationCorr(plane)
$ ENDDO
$
$ ! Fix a line in space to align planes with respect to
$ !DCplane_corr(1)%UVshift = 0.
$ !DCplane_corr(2)%UVshift = 0.
$ !DCplane_corr(7)%UVshift = 0.
$ !DCplane_corr(8)%UVshift = 0.
$
$ CALL AlignPlaneRotationsPrint
$
$ !CALL SetupDCplanes
$ !CALL SetupDCwires
$ CALL SetupChambers
$
$ DO plane = FirstPlaneDC, LastPlaneDC
$ init = .TRUE.
$ DO LengthBin = 1, LengthBinMax
$ IF(ResidAvePlaneLength(plane,LengthBin) == 0) Init = .FALSE.
$ ENDDO
$ DO LengthBin = 1, LengthBinMax
$ IF(init) THEN
$ ResidPlaneLength(plane,LengthBin)%sum = 0.
$ ResidPlaneLength(plane,LengthBin)%count = 0
$ END IF
$ END DO
$ ENDDO
$
$ END SUBROUTINE AlignPlaneRotations
private subroutine AlignBeamAngle ()
! Calls: AlignBeamAnglePrint, SetupChambers, hfithn, hnoent, hreset, kerror
end subroutine AlignBeamAngle
private subroutine AlignPC (iWindow)
integer (kind=i4) :: iWindow
! Calls: HFILL, hfithn, hnoent
end subroutine AlignPC
public subroutine AlignPlaneShiftsPrint ()
! Calls: Fdate
end subroutine AlignPlaneShiftsPrint
public subroutine AlignWireShiftsPrint ()
! Calls: Fdate
end subroutine AlignWireShiftsPrint
private subroutine AlignPlaneRotationsPrint ()
! Calls: Fdate
end subroutine AlignPlaneRotationsPrint
public subroutine AlignField (iWindow, iTrack)
integer (kind=i4), INTENT(IN) :: iWindow
integer (kind=i4), INTENT(IN) :: iTrack
! Calls: kerror
end subroutine AlignField
========================================================
October 2002
--------------------------------------------------------
B field alignment
========================================================
Author: Maher Quraan
private subroutine AlignBeamAnglePrint ()
! Calls: Fdate
end subroutine AlignBeamAnglePrint