Skip to content

Commit

Permalink
Merge d60bed7 into d19d317
Browse files Browse the repository at this point in the history
  • Loading branch information
tpersson committed Mar 1, 2021
2 parents d19d317 + d60bed7 commit 7b69cff
Show file tree
Hide file tree
Showing 14 changed files with 471 additions and 155 deletions.
2 changes: 1 addition & 1 deletion Makefile_test
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ test-rfmultipole-ptc-1 \
test-ptc-twiss-1 test-ptc-twiss-2 test-ptc-twiss-3 test-ptc-twiss-4 \
test-ptc-twiss-old1 test-ptc-twiss-old2 test-ptc-twiss-old3 test-ptc-twiss-old4 test-ptc-twiss-old5 test-ptc-twiss-old6 test-ptc-twiss-old7 \
test-ptc-twiss-5D test-ptc-twiss-5Dt test-ptc-twiss-56D test-ptc-twiss-56Dt test-ptc-twiss-56Dl test-ptc-twiss-56Dtl test-ptc-twiss-6D test-ptc-twiss-6D-ALS \
test-ptc-twiss-accel-56D test-ptc-twiss-56Dt-ini_map_man test-ptc-twiss-56Dt-ini_mtx_man test-ptc-twiss-56Dt-ini_mtx_tbl \
test-ptc-twiss-accel-56D test-ptc-twiss-56Dt-ini_map_man test-ptc-twiss-56Dt-ini_mtx_man test-ptc-twiss-56Dt-ini_mtx_tbl test-ptc-twiss-tilt \
test-ptc-normal test-ptc-normal-5D-beambeam \
test-ptc-twiss-normal-genfu test-ptc-twiss-normal-5D test-ptc-twiss-normal-6D test-ptc-twiss-maptable \
test-ptc-track test-ptc-track-2 test-ptc-track-3 test-ptc-track-4 test-ptc-track-5 \
Expand Down
20 changes: 13 additions & 7 deletions libs/ptc/src/Sm_tracking.f90
Original file line number Diff line number Diff line change
Expand Up @@ -510,7 +510,7 @@ SUBROUTINE TRACK_FIBRE_R(C,X,K,X_IN)
ENDIF
IF(PRESENT(X_IN)) CALL XMID(X_IN,X,-3)

CALL DTILTD(C%MAG%P%TILTD,1,X)

IF(PRESENT(X_IN)) CALL XMID(X_IN,X,-2)
! The magnet frame of reference is located here implicitely before misalignments

Expand All @@ -519,6 +519,8 @@ SUBROUTINE TRACK_FIBRE_R(C,X,K,X_IN)
ou = ALWAYS_EXACTMIS !K%EXACTMIS.or.
CALL MIS_FIB(C,X,k,OU,DONEITT)
ENDIF
CALL DTILTD(C%MAG%P%TILTD,1,X)

IF(PRESENT(X_IN)) then
CALL XMID(X_IN,X,-1)
X_IN%POS(2)=X_IN%nst
Expand All @@ -532,12 +534,12 @@ SUBROUTINE TRACK_FIBRE_R(C,X,K,X_IN)
X_IN%POS(3)=X_IN%nst
endif

CALL DTILTD(C%MAG%P%TILTD,2,X)
IF(C%MAG%MIS) THEN
CALL MIS_FIB(C,X,k,OU,DONEITF)
ENDIF
IF(PRESENT(X_IN)) CALL XMID(X_IN,X,X_IN%nst+1)
! The magnet frame of reference is located here implicitely before misalignments
CALL DTILTD(C%MAG%P%TILTD,2,X)

IF(PRESENT(X_IN)) CALL XMID(X_IN,X,X_IN%nst+1)

IF(PATCHT/=0.AND.PATCHT/=1.AND.(K%TOTALPATH==0)) THEN
Expand Down Expand Up @@ -700,13 +702,14 @@ SUBROUTINE TRACK_FIBRE_P(C,X,K)
ENDIF
! IF(PRESENT(X_IN)) CALL XMID(X_IN,X,-3)

CALL DTILTD(C%MAGP%P%TILTD,1,X)
! IF(PRESENT(X_IN)) CALL XMID(X_IN,X,-2)
! IF(PRESENT(X_IN)) CALL XMID(X_IN,X,-2)
! MISALIGNMENTS AT THE ENTRANCE
IF(C%MAGP%MIS) THEN
OU =ALWAYS_EXACTMIS ! K%EXACTMIS.OR.
CALL MIS_FIB(C,X,k,OU,DONEITT)
ENDIF
! Apply tilt after misalignments
CALL DTILTD(C%MAGP%P%TILTD,1,X)

CALL TRACK(C%MAGP,X,K)
! if(abs(x(1))+abs(x(3))>absolute_aperture.or.(.not.CHECK_MADX_APERTURE)) then ! new 2010
Expand All @@ -716,13 +719,16 @@ SUBROUTINE TRACK_FIBRE_P(C,X,K)



! MISALIGNMENTS AT THE EXIT

CALL DTILTD(C%MAGP%P%TILTD,2,X)
! Tilt back before misalignment

IF(C%MAGP%MIS) THEN
CALL MIS_FIB(C,X,k,OU,DONEITF)
ENDIF
! IF(PRESENT(X_IN)) CALL XMID(X_IN,X,X_IN%nst+1)

CALL DTILTD(C%MAGP%P%TILTD,2,X)

! IF(PRESENT(X_IN)) CALL XMID(X_IN,X,X_IN%nst+1)

!EXIT PATCH
Expand Down
30 changes: 18 additions & 12 deletions libs/ptc/src/Sma_multiparticle.f90
Original file line number Diff line number Diff line change
Expand Up @@ -637,15 +637,17 @@ SUBROUTINE TRACK_FIBRE_FRONTR(C,X,K)
endif
ENDIF

CALL DTILTD(C%MAG%P%TILTD,1,X)
! The magnet frame of reference is located here implicitely before misalignments


! CALL TRACK(C,X,EXACTMIS=K%EXACTMIS)
IF(C%MAG%MIS) THEN
ou = ALWAYS_EXACTMIS !K%EXACTMIS.or.
CALL MIS_FIB(C,X,k,OU,DONEITT)
ENDIF


! Apply the tilt after the misalignments
CALL DTILTD(C%MAG%P%TILTD,1,X)

END SUBROUTINE TRACK_FIBRE_FRONTR

SUBROUTINE TRACK_FIBRE_FRONTP(C,X,K)
Expand Down Expand Up @@ -724,14 +726,15 @@ SUBROUTINE TRACK_FIBRE_FRONTP(C,X,K)
endif
ENDIF

CALL DTILTD(C%MAGP%P%TILTD,1,X)
! The magnet frame of reference is located here implicitely before misalignments


! CALL TRACK(C,X,EXACTMIS=K%EXACTMIS)
IF(C%MAGP%MIS) THEN
ou = ALWAYS_EXACTMIS !K%EXACTMIS.or.
CALL MIS_FIB(C,X,k,OU,DONEITT)
ENDIF
!Apply after the misalignments T.Persson
CALL DTILTD(C%MAGP%P%TILTD,1,X)


END SUBROUTINE TRACK_FIBRE_FRONTP
Expand All @@ -758,14 +761,15 @@ SUBROUTINE TRACK_FIBRE_BACKR(C,X,K)
PATCHT=0 ; PATCHE=0 ;PATCHG=0;
ENDIF


IF(C%MAG%MIS) THEN

! First tilt back T.Persson
CALL DTILTD(C%MAG%P%TILTD,2,X)
IF(C%MAG%MIS) THEN
ou = ALWAYS_EXACTMIS !K%EXACTMIS.or.
CALL MIS_FIB(C,X,k,OU,DONEITF)
ENDIF
! The magnet frame of reference is located here implicitely before misalignments
CALL DTILTD(C%MAG%P%TILTD,2,X)



IF(PATCHT/=0.AND.PATCHT/=1.AND.(K%TOTALPATH==0)) THEN
if(K%time) then
X(6)=X(6)-C%PATCH%b_T !/c%beta0
Expand Down Expand Up @@ -841,14 +845,16 @@ SUBROUTINE TRACK_FIBRE_BACKP(C,X,K)
PATCHT=0 ; PATCHE=0 ;PATCHG=0;
ENDIF

! First tilt back T. Persson
CALL DTILTD(C%MAGP%P%TILTD,2,X)

IF(C%MAGP%MIS) THEN
ou = ALWAYS_EXACTMIS !K%EXACTMIS.or.
CALL MIS_FIB(C,X,k,OU,DONEITF)
ENDIF


! The magnet frame of reference is located here implicitely before misalignments
CALL DTILTD(C%MAGP%P%TILTD,2,X)


IF(PATCHT/=0.AND.PATCHT/=1.AND.(K%TOTALPATH==0)) THEN
if(K%time) then
Expand Down
24 changes: 14 additions & 10 deletions src/twiss.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2045,7 +2045,6 @@ SUBROUTINE twcptk(re,orbit)
eflag = 0

call element_name(name,len(name))

!---- Dispersion.
DT = matmul(RE, DISP)

Expand Down Expand Up @@ -2269,7 +2268,7 @@ SUBROUTINE twcptk_twiss(matx, maty, error)
double precision :: maty11, maty12, maty21, maty22
double precision :: alfx_ini, betx_ini, tempa
double precision :: alfy_ini, bety_ini, tempb
double precision :: detx, dety
double precision :: detx, dety, atanm12
logical :: error
double precision, parameter :: eps=1d-36
character(len=name_len) :: name
Expand Down Expand Up @@ -2307,10 +2306,12 @@ SUBROUTINE twcptk_twiss(matx, maty, error)
betx = (tempb * tempb + matx12 * matx12) / (detx*betx_ini)
!if (abs(matx12).gt.eps) amux = amux + atan2(matx12,tempb)
if (abs(matx12).gt.eps) then
amux = amux + atan2(matx12,tempb)

if (atan2(matx12,tempb) .lt. zero)then
if (ele_body .and. abs(atan2(matx12,tempb)) > 0.1) then
atanm12 = atan2(matx12,tempb)
if(abs(atanm12) < 3.14 .or. ele_body) then
amux = amux + atanm12
endif
if (atanm12 .lt. zero)then
if (ele_body .and. abs(atanm12) > 0.1) then
write (warnstr,'(a,e13.6,a,a)') "Negative phase advance in x-plane ", &
atan2(matx12,tempb), " in the element ", name
call fort_warn('TWCPTK_TWISS: ', warnstr)
Expand All @@ -2332,12 +2333,15 @@ SUBROUTINE twcptk_twiss(matx, maty, error)
bety = (tempb * tempb + maty12 * maty12) / (detx*bety_ini)
! if (abs(maty12).gt.eps) amuy = amuy + atan2(maty12,tempb)
if (abs(maty12).gt.eps) then
amuy = amuy + atan2(maty12,tempb)
atanm12 = atan2(maty12,tempb)
if(abs(atanm12) < 3.14 .or. ele_body) then ! If no body phase advance < 180 deg
amuy = amuy + atanm12
endif

if (atan2(maty12,tempb) .lt. zero) then
if (ele_body .and. abs(atan2(maty12,tempb)) > 0.1 ) then
if (ele_body .and. abs(atanm12) > 0.1 ) then
write (warnstr,'(a,e13.6,a,a)') "Negative phase advance in y-plane ", &
atan2(maty12,tempb), " in the element ", name
atanm12, " in the element ", name
call fort_warn('TWCPTK_TWISS: ', warnstr)
! print*, " maty12 =", maty12, " tempb = ", tempb , "maty11 * bety_ini =", maty11 * bety_ini, &
! " maty12 * alfy_ini = ", maty12 * alfy_ini
Expand Down Expand Up @@ -6683,7 +6687,6 @@ SUBROUTINE tmsrot(ftrk,orbit,fmap,ek,re,te)
re(4,2) = -st
re(4,4) = ct


!---- Track orbit.
if (ftrk) call tmtrak(ek,re,te,orbit,orbit)

Expand Down Expand Up @@ -7630,6 +7633,7 @@ SUBROUTINE tmali2(el, orb1, errors, beta, gamma, orb2, rm)
orbt(4) = orb1(4) - w(3,2)
orbt(5) = orb1(5) - s2 / beta
orbt(6) = orb1(6)

ORB2 = matmul(RM,ORBT)

end SUBROUTINE tmali2
Expand Down
125 changes: 0 additions & 125 deletions tests/test-crabcavity/fodo.ptc

This file was deleted.

3 changes: 3 additions & 0 deletions tests/test-ptc-twiss-tilt/test-ptc-twiss-tilt.cfg
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
1-7 * skip # head
* * abs=1e-13
871 4 abs=4e-13 # disp1max in summ of ptc_twiss

0 comments on commit 7b69cff

Please sign in to comment.