subroutine stash_split_lat (i_train, j_car, particle, n_trains_tot, n_cars, lat, rec_taylor) ! subroutine to make matrices, compute closed orbits for, lat ! and save taylor as digested file and/or get taylor from digested file ! with name i_train//_//j_car//_//n_trains_tot//_//n_cars.lat use bmad use bmad_interface use bmadz_mod use bmadz_interface implicit none type (lat_struct) lat type (lat_struct), save :: lat_dum type (coord_struct), allocatable,save :: orbit(:) integer k integer n integer i, j integer i_train, j_car, particle, n_trains_tot, n_cars integer version ! Allow 10 trains 9 sep 09 jac character*2 train, trains_tot, part ! Increase from 1 to 2 to allow 10 cars per train 19 jan 06 character*2 car,cars ! Increase from 28 to 30 to allow 10 cars per train 19 jan 06 character*40 name character*3 species(-1:1)/'ele','neu','pos'/ character(20) :: r_name='stash_split_lat' logical rec_taylor, err logical transferred_all call reallocate_coord( orbit, lat%n_ele_max ) if(rec_taylor)then ! Allow 10 trains 9 sep 09 jac write(train,'(i2.2)')i_train ! Increase from i1 to i2.2 to allow 10 cars per train 19 jan 06 write(car,'(i2.2)')j_car ! Allow 10 trains 9 sep 09 jac write(trains_tot,'(i2.2)')n_trains_tot ! Increase from i1 to i2.2 to allow 10 cars per train 19 jan 06 write(cars,'(i2.2)')n_cars lat_dum = lat name = 'digested_'//train//'_'//car//'_'//species(particle)//'_'//trains_tot//'_'//cars//'_'//species(-particle)//'.lat' call out_io(s_info$,r_name,name) ! print *,' Stash_split_lat :',name call out_io(s_blank$,r_name,' read_digested_file') ! print *,' Stash_split_lat: read_digested_file' call read_digested_bmad_file (name, lat_dum, version, err_flag = err) if(.not. err .and. (lat_dum%ele(0)%value(e_tot$) == lat%ele(0)%value(e_tot$)))then call out_io(s_blank$,r_name,' transfer_taylor') ! print *,' Stash_split_lat: transfer_taylor' call transfer_lat_taylors(lat_dum, lat, .true.,transferred_all ) if(.not. transferred_all)then do i=1,lat%n_ele_max if(lat%ele(i)%tracking_method == taylor$ .and. & .not. associated(lat%ele(i)%taylor(1)%term))call lat_make_mat6(lat, i) end do call out_io(s_blank$,r_name,' write_digested_file') ! print *,' Stash_split_lat: write_digested_file' call write_digested_bmad_file (name, lat) endif else call lat_make_mat6(lat,-1) call out_io(s_blank$,r_name,' write_digested_file') ! print *,' Stash_split_lat: write_digested_file' call write_digested_bmad_file (name, lat) endif else call lat_make_mat6(lat, -1) !make up taylor about on axis orbit endif orbit(0)%vec(6) = 0. call closed_orbit_calc(lat, orbit, 4) call track_all(lat, orbit) call lat_make_mat6(lat, -1, orbit) return end