!+ ! Subroutine poscon (det, b1, b2, b3, b4, v, h) ! ! Subroutine to convert button values to horizontal and vertical position. ! ! Input: ! det -- Integer: detector index. If negative then do something special: ! = -1 --> Set offset calibrations to 0. ! = -2 --> Reset offset calibrations & reread calib file. ! = -3 --> Turn off denominator summation normalization. ! = -4 --> Turn back on denominator normalization. ! b1, b2, b3, b4 -- Real: Button values. ! ! Output: ! v -- Real: Vertical position in meters. ! h -- Real: Horizontal position in meters. !- subroutine poscon(loc, f1, f2, f3, f4, v, h) use str_find_mod use cesr_utils_interface implicit none integer(4) loc, j, i, iu integer(4) three(120) real f1, f2, f3, f4, v, h, sum real pqv, pqh, hold, hhmm, factr, b1, b2, b3, b4 real theta, c, c1, c2, c3, c4, s1, s2, s3, s4 real, save :: ratio, eqsum(120), pdcm(2, 0:120) character(120) file_name, fname logical, save :: init_needed = .true., sumone = .false., iotit !! common /oftype/ iotit Removed DCS 2009-01-05 !! common /pdtcal/ pdcm Removed DCS 2009-01-05 !! common /ofaxis/ ratio, eqsum Removed DCS 2009-01-05 ! Init if (init_needed) then init_needed = .false. ! once-only readin and convert mm to meters iu = open_cesr_constants_file('offset.bpm') do while(.true.) read(iu, *, end = 999) i, pdcm(1, i), pdcm(2, i) enddo 999 close(unit = iu) pdcm = 0.001 * pdcm three = 0 call fullfilename('$CESR_ONLINE/machine_data/meas/orbit/three.inf', fname) open(unit = iu, file = fname, status='old',action='read') do while(.true.) read(iu, *, end = 888) i, three(i) enddo 888 close(unit = iu) endif ! ------------------end-readin-det-calibration---------------------- v = 0 h = 0 b1 = f1 ! protect in case three button modifies b1-b4 b2 = f2 b3 = f3 b4 = f4 ! -------------------convert-three-to-four------------------------- if (loc>0) then if (three(loc) /= 0) then if ((b1+b2+b3+b4)>10000.) then if (three(loc) == 1) then b1 = b4+(b3-b4)+(b2-b4) elseif (three(loc) == 2) then b2 = b3+(b4-b3)+(b1-b3) elseif (three(loc) == 3) then b3 = b2+(b4-b2)+(b1-b2) elseif (three(loc) == 4) then b4 = b1+(b3-b1)+(b2-b1) endif endif endif endif ! if something special needs to be done if (loc < -4 .or. loc > 120) then print *, 'ERROR IN POSCON: BAD DETECTOR LOC', loc return endif if (loc == -4) then sumone = .false. ! for normal denominator return endif if (loc == -3) then sumone = .true. ! for coupling meas return endif if (loc == -2) then init_needed = .true. ! will cause re-cal (turn on zero offset) return endif if (loc == -1) then ! turn off zero offset do j = 0, 100 pdcm(1, j) = 0. pdcm(2, j) = 0. enddo return endif ! preceed as normal sum = b1+b2+b3+b4 if (sumone) sum = 1 if (sum == 0) return pqv = pdcm(1, loc) pqh = pdcm(2, loc) !-------------------------------------------------------------------- ! usual case ! 2W/E ! up to phase iii (10/10/2001) was: dcs, jjw ! v = .0287*(b3+b4-b1-b2)/sum - pqv !fit to L0 Horz data spring 1999 ! h = .0287*(b2+b4-b3-b1)/sum - pqh !q2 q48 45 degrees, elliptical pipe ! changed to standard BPM for phase iii select case (loc) ! 0W/E ! up to phase iii (10/10/2001) was: dcs, jjw ! v = .0204*(b3+b4-b1-b2)/sum - pqv !fit Horz data spring 1999 ! h = .0204*(b2+b4-b3-b1)/sum - pqh !0 det (formerly same as q1) ! case (99, 100) !!2002 if (loc == 100) theta = 26.0 ! Det 0W !!2002 if (loc == 99) theta = 37.5 ! Det 0E ! if (loc == 100) theta = 44.66 ! Det 0W 2003 JULY 11 ! if (loc == 99) theta = 44.56 ! Det 0E ! ! c = 0.0203 * sqrt(2.0) ! c1 = c * cosd(theta+180) ! c2 = c * cosd(theta-90) ! c3 = c * cosd(theta+90) ! c4 = c * cosd(theta) ! s1 = c * sind(theta+180) ! s2 = c * sind(theta-90) ! s3 = c * sind(theta+90) ! s4 = c * sind(theta) ! h = (c1*b1 + c2*b2 + c3*b3 + c4*b4) / sum - pqh ! v = (s1*b1 + s2*b2 + s3*b3 + s4*b4) / sum - pqv ! ! Changed to standard BPM for CesrTA. DCS 2008/11/18. ! 1W/E ! used .027 up through spring 1999; jwelch looked at h orbits, conclude ! was too small by 1.7 , det 0 and 2 too large, mult by .76, .68 ! was 0.0463 up to phase iii (10/10/2001) dcs, jjw ! ! case (1, 98) ! v = .0542*(b3+b4-b1-b2)/sum - pqv ! h = .0542*(b2+b4-b3-b1)/sum - pqh ! ! Changed to standard BPM for CesrTA. DCS 2008/11/18. ! 48W/E case (48, 51) v = .0287*(b3+b4-b1-b2)/sum - pqv ! fit to L0 Horz data spring 1999 h = .0287*(b2+b4-b3-b1)/sum - pqh ! q2 q48 45 degrees, elliptical pipe ! 49W/E case (49, 50) v = .035*(b3+b4-b1-b2)/sum - pqv ! q49 45 degree, 4" diam h = .035*(b2+b4-b3-b1)/sum - pqh ! changed from .042 to .035, dec89 RML ! south arc x5c to 9w case (1:7) v = .0104*(b3+b4-b1-b2)/sum - pqv ! h = .0102*(b2+b4-b3-b1)/sum - pqh ! ! south arc x1a to x5b case (93:110) v = .0104*(b3+b4-b1-b2)/sum - pqv ! h = .0102*(b2+b4-b3-b1)/sum - pqh ! ! normal arc detectors case default v = .0198*(b3+b4-b1-b2)/sum - pqv h = .0259*(b2+b4-b3-b1)/sum - pqh ! if ((ratio /= 0).and.(eqsum(loc) /= 0)) then ! if (sum*ratio/eqsum(loc)<.85) then ! hold = 1000.*h ! h = sign(.043-.0315*sum*ratio/eqsum(loc), h)-pqh ! hhmm = 1000.*h ! factr = sum*ratio/eqsum(loc) !if (iotit) then ! print '(a, f5.3, i3, 2f6.2)', ' but ratio ', factr, ' at', loc, & ! ' use offaxis:horz mm', hold, ' >>> ', hhmm !endif ! endif ! sum*ratio/eqsum(loc)<85 ! endif ! ratio /= 0 end select end subroutine poscon