subroutine track_electron_ele(lat,nbranch,s1,start_orb,ix_start,electrons_ele,n,nmuons,n_ele,end) use bmad use muon_mod IMPLICIT NONE !When a muon decay within an element,this subroutine track the generated electron to the end of that element and then track !for a whole turn element by element. Information is recorded in electrons_ele(:,:) type (lat_struct),target:: lat type (branch_struct),pointer:: branch !ring type (coord_struct) start_orb type (coord_struct),dimension(0:n_ele):: temp type (electron_struct),dimension(0:nmuons,0:n_ele)::electrons_ele integer nbranch,ix_start integer nmuons,n_ele integer track_state integer k,n !n is the index of muon in muons(:) logical end real(rp) s1,s2 !start and end position for the element real(rp) error/0.00001/ !used to avoid problems in the bmad tracking program branch => lat%branch(nbranch) !if not already at the end, track the electron to the end of element if (.not.(end)) then s2 = branch%ele(ix_start)%s if (s2-s1 /= 0 ) s2 = s2-error !avoid exceptions call track_from_s_to_s(lat,s1,s2,start_orb,temp(ix_start),ix_branch = nbranch, track_state = track_state) end if if (end) temp(ix_start) = start_orb !record the information in a proper place electrons_ele(n,0)%coord = temp(ix_start) electrons_ele(n,0)%ix_start = ix_start electrons_ele(n,0)%exist = .true. if (track_state /= moving_forward$) electrons_ele(n,0)%lost = .true. !track the electron for a whole turn if (track_state == moving_forward$) then call track_many(lat,temp,ix_start,ix_start,1,nbranch,track_state) if (track_state /= moving_forward$) electrons_ele(n,0)%lost = .true. do k = 1,branch%n_ele_track electrons_ele(n,k)%coord = temp(k) print *, 'coord', electrons_ele(n,k)%coord%vec(1) print *, 'lost',lost$,electrons_ele(n,k)%coord%state,'alive',alive$ print *, 'electron_temp',temp(k)%vec(1) end do print *, 'n',n print *, 'start',electrons_ele(n,0)%ix_start end if !if moving forward return end subroutine track_electron_ele subroutine track_electron_s(lat,nbranch,s10,start_orb,ix_start,electrons_s,n,nmuons,steps,tot_track,n_row,ncolumns,n_ele,end) use bmad use muon_mod IMPLICIT NONE !When a muon decay within an element,this subroutine track the generated electron to the end of that element and then track through a !specified amount of elements (given by tot_track). The number of tracking steps in each element is given by the variable steps. type (lat_struct),target:: lat type (branch_struct),pointer:: branch !ring type (coord_struct) start_orb type (coord_struct),allocatable:: temp(:) type (electron_struct),dimension(0:n_row,0:ncolumns):: electrons_s !used to store tracking information integer nbranch,ix_start !ix_start is the index of element where the electron is generated integer nmuons,line/0./,n_row integer n_ele !number of elements integer ncolumns integer tot_track !number of elements to be tracked after the one at which the muon decayed integer track_state integer i,j,k,n !n is the index of muon in muons(:) integer steps integer index1,index2 logical end real(rp) s10,s20 !start and end position real(rp) s1,s2 !start and end position for each step real(rp) l_remain real(rp) len !effective element length real(rp) error/0.00001/ !used to avoid problems in the bmad tracking program allocate(temp(0:steps*(1+tot_track))) branch => lat%branch(nbranch) track_state = moving_forward$ temp(0) = start_orb !if not already at the end, track the electron to the end of element line = line + 1 if (.not.(end)) then s20 = branch%ele(ix_start)%s if (s20-s10 /= 0) s20 = s20-error !avoid execptions l_remain = s20 - s10 temp(0) = start_orb do i = 0,steps-1 s1 = s10 + i*l_remain/steps s2 = s1 + l_remain/steps call track_from_s_to_s(lat,s1,s2,temp(i),temp(i+1),ix_branch = nbranch, track_state = track_state) if (track_state /= moving_forward$) exit end do end if ! if not at the end if (end) temp(steps) = temp(0) if(track_state == moving_forward$) then !track the remaining elements(amount specified by tot_track) do i = 1,tot_track index1 = mod(ix_start+i-1,n_ele) index2 = mod(ix_start+i,n_ele) if (index1 == 0) index1 = n_ele if (index2 == 0) index2 = n_ele s10 = branch%ele(index1)%s s20 = branch%ele(index2)%s print *, 'indices',index1,index2 if (index1 == n_ele) s10 = 0 if (index1 == n_ele) print *,'AfreeBefore' if (index1 == 2) print *,'AfreeAfter' if (index1 == 9) print *,'KICKER2BBefore' if (index1 == 11) print *,'KICKER2BAFTER' if (index1 == 1) print *,'Afree' if (index1 == 10) print *, 'KICKER2B' len = s20-s10 if (len == 0 ) then temp(steps+(i-1)*steps+1:steps+i*steps) = temp(steps + (i-1)*steps) !skip elements with length = 0 cycle else s10 = s10 + error if (s20 /= 0) then s20 = s20 - error len = len-2*error else len = len - error end if end if !if (s20-s10 /= 0) then !s10 = s10 + error !s20 = s20 - error !end if do j = 0,steps-1 s1 = s10 + j*len/steps s2 = s1 + len/steps call track_from_s_to_s(lat,s1,s2,temp(steps+(i-1)*steps+j),temp(steps+(i-1)*steps+j+1),ix_branch = nbranch, track_state = track_state) if (track_state /= moving_forward$) exit end do if (track_state /= moving_forward$) exit end do end if ! tracking_state = moving_forward$ in the starting element !record information in electrons_s,some parameters are recorded in elctrons_s(n,0) do i = 0, steps*(1 + tot_track) electrons_s(line,i)%coord = temp(i) end do electrons_s(line,0)%exist = .true. electrons_s(line,0)%ix_start = ix_start electrons_s(line,0)%index_mu = n if (track_state /= moving_forward$) then electrons_s(line,0)%lost = .true. electrons_s(line,0)%ix_lost = track_state end if print *,'finish' return end subroutine track_electron_s