!+ ! Subroutine track1_custom (start_orb, ele, param, end_orb, track, err_flag) ! ! For scattering in various markers ! ! Note: This routine is not to be confused with track1_custom2. ! See the Bmad manual for more details. ! ! General rule: Your code may NOT modify any argument that is not listed as ! an output agument below." ! ! Modules Needed: ! use bmad ! ! Input: ! start_orb -- Coord_struct: Starting position. ! ele -- Ele_struct: Element. ! param -- lat_param_struct: Lattice parameters. ! ! Output: ! end_orb -- Coord_struct: End position. ! track -- track_struct, optional: Structure holding the track information if the ! tracking method does tracking step-by-step. ! err_flag -- Logical: Set true if there is an error. False otherwise. !- subroutine track1_custom (start_orb, ele, param, end_orb, track, err_flag) use bmad_interface !, except_dummy => track1_custom use materials_mod use parameters_bmad !includes eloss, us_scatter, ds_scatter, tilt implicit none type (coord_struct) :: start_orb type (coord_struct) :: end_orb type (coord_struct) temp_orb, delta type (ele_struct) :: ele type (lat_param_struct) :: param type (track_struct), optional :: track logical err_flag logical energy_loss logical withinInflectorAperture logical first/.true./ character(32) :: r_name = 'track1_custom' integer lun ! !call out_io (s_fatal$, r_name, 'THIS DUMMY ROUTINE SHOULD NOT HAVE BEEN CALLED IN THE FIRST PLACE.') err_flag = .false. ! Remember to also set end_orb%t withinInflectorAperture = .true. energy_loss = eloss temp_orb = start_orb if(first)then write(51,'(a)')'Change in coordinate vector due to upstream inflector scattering' write(51,'(6a12)')'x','xp','y','yp','z','zp' write(52,'(a)')'Change in coordinate vector due to downstream inflector scattering' write(52,'(6a12)')'x','xp','y','yp','z','zp' endif !print '(a,1x,2(a,2es12.4),2es12.4)',ele%name,'start_orb = ',start_orb%vec(1:2), ' end_orb = ', end_orb%vec(1:2), start_orb%s, ele%s if(ele%name == 'MARK_CRYO_US' .and. us_scatter) call scatter( Al, 0.001_rp, temp_orb) if(ele%name == 'MARK_INFLECTOR_US')then withinInflectorAperture = .false. ! print '(a2,1x,6es12.4)','bs',temp_orb%vec(1:6) if(us_scatter)call inflector_scatter1(temp_orb, .true., .false., energy_loss) delta%vec = temp_orb%vec - start_orb%vec write(51,'(6es12.4)')delta%vec(1:6) ! print '(a2,1x,6es12.4)','us',temp_orb%vec(1:6),delta%vec(1:6) if(inflector_width == 0.009)call E821InflectorAperture(temp_orb%vec(1),temp_orb%vec(3),withinInflectorAperture,.true.,.false.) if(inflector_width > 0.009)call E989InflectorAperture(temp_orb%vec(1),temp_orb%vec(3),withinInflectorAperture,.true.,.false.) if(.not. withinInflectorAperture)temp_orb%state=lost$ endif if(ele%name == 'MARK_INFLECTOR_DS')then withinInflectorAperture = .false. if(ds_scatter)call inflector_scatter1(temp_orb, .false., .true., energy_loss) delta%vec = temp_orb%vec - start_orb%vec write(52,'(6es12.4)')delta%vec(1:6) ! print '(a2,1x,6es12.4)','ds',delta%vec(1:6) if(inflector_width == 0.009)call E821InflectorAperture(temp_orb%vec(1),temp_orb%vec(3),withinInflectorAperture, .false.,.true.) if(inflector_width > 0.009)call E989InflectorAperture(temp_orb%vec(1),temp_orb%vec(3),withinInflectorAperture, .false.,.true.) if(.not. withinInflectorAperture)temp_orb%state = lost$ endif end_orb = temp_orb end_orb%s = ele%s !if(end_orb%state == lost$)print '(a12,1x,a16,7es12.4)','Lost in',ele%name,end_orb%s,end_orb%vec(1:6) if(first)then lun=lunget() open (unit=lun, file = "log.dat",access='append') write(lun, '(a)')'TRACK1_CUSTOM: Scattering in inflector ends' write(lun, '(1x,a15,l)')' energy_loss = ', energy_loss write(lun,'(1x,a16)')ele%name first=.false. close(unit=lun) endif !end_orb = start_orb !end_orb%s = ele%s end subroutine