subroutine bpm_beampipe(x,y,np,rdum, button) use precision_def use bpm_mod use bpm_interface use nr use cesr_utils implicit none integer np real(rp) a/45./, b/24.92/, x0/12.98/,y0/24.92/ type (grid_struct), allocatable :: grid(:) type (bpm_geometry_struct) bpm real(rp) x,y !this is were the bunch is real(rp), allocatable :: C(:,:) real(rp) theta, dt real(rp) r0 !/0.1/ !radius of wire real(rp) r real(rp) angle(4) real(rp) button(4) ! real(rp) twopi/6.28318530718/ real(rp), allocatable :: BB(:,:) real(rp) rdum logical firstime/.true./ integer np_last integer i,j ! if(allocated(grid) .and. np /= np_last)then ! deallocate(grid) ! deallocate(C) ! endif ! if(.not. allocated(grid))then allocate(grid(1:np)) allocate(C(np,np)) allocate(BB(1:np,1)) call setup_extrusion_grid(grid, bpm,np, r0) ! np_last = np ! endif grid(1)%xs = x grid(1)%ys = y grid(1)%V = 1. do i=1,np write(16,'(i,2e12.4)')i, grid(i)%xs, grid(i)%ys do j=1,4 if(grid(i)%point(j))write(17,'(2i,5e12.4)')j,i,grid(i)%xs, grid(i)%ys, grid(i)%ts, bpm%min_angle(j), bpm%max_angle(j) end do write(18,'(i,e12.4)')i,grid(i)%ts*180/3.141592 end do do i=1,np if(i >=2)grid(i)%V=0. do j = 1,np if(i == j .and. i /= 1) then C(i,j) = log(r0/r0) elseif(i==j .and. i == 1)then C(i,j) = log(r0/r0) else r = sqrt((grid(i)%xs-grid(j)%xs)**2+(grid(i)%ys-grid(j)%ys)**2) if(r == 0.)then print *,i,j,r print '(4e12.4)', grid(i)%xs, grid(j)%xs, grid(i)%ys, grid(j)%ys else C(i,j) = log(r/r0) endif endif end do end do ! Suppose the charges are Q(i). Then V(i) = C(i,j)*Q(j). ! We know that if i /= 1 then V(i) = 0 ! Let's say that V(1) = 1. Then C(i,j)^{-1}V(i) = Q(j) ! And V(x,y) = Q(i)*log(|r-r(i)|) ! Or even better, the charge on the button is the sum over the charges ! intercepted by the angle. ! print *,' C ' ! call gjdet(C,grid(:)%V,grid(:)%Q,np) do i=1,np BB(i,1) = grid(i)%V end do call gaussj(C,BB) grid(1:np)%Q = BB(1:np,1) ! do i=2,np ! do j=1,4 ! if(point(j,i))write(12, '(3e12.4)') xs(i), ys(i), q(i) ! end do !write(11, '(3e12.4)') xs(i), ys(i), q(i) ! end do button(1:4) = 0. do i=2,np do j=1,4 if(grid(i)%point(j))button(j) = button(j) + grid(i)%Q end do write(19,'(i,2e12.4)')i, grid(i)%V, grid(i)%Q end do ! print '(2i,10e12.4)',np,j, x,y,button(1:4), button(1:4)/q(1) write(13, '(2i,10e12.4)')np,j, x,y,button(1:4), button(1:4)/grid(1)%q do j=1,4 call integrate_charge(bpm%min_angle(j), bpm%max_angle(j), grid(1:np)%q, grid(1:np)%ts, grid(1:np)%point(j), button(j)) end do ! print '(/,2i,10e12.4)',np,j, x,y,button(1:4), button(1:4)/q(1) write(15, '(2i,7e12.4)')np,j, x,y,button(1:4), grid(1)%q button(1:4) = button(1:4)/grid(1)%q deallocate(grid) deallocate(C) return end