subroutine get_branch_inv_matrix(lat,mat,mat_forward, nbranch, err) use bmad implicit none type (lat_struct), target :: lat type (branch_struct), pointer :: branch ! ring type (ele_struct) ele real(rp) mat(6,6),m(6,6), mat_forward(6,6) real(rp) temp(6,6) real(rp) test(6,6), diag_prod integer nbranch, n_loc,n integer i integer j logical err err=.false. temp = 0. forall(i=1:6)temp(i,i) = 1. branch => lat%branch(nbranch) do i = 1, branch%n_ele_track m = matmul(branch%ele(i)%mat6, temp) temp= m ! do j=1,6 ! print '(6es12.4)', branch%ele(i)%mat6(j,1:6) ! end do n=i if(index(branch%ele(i)%name,'INFA')/= 0 .or. index(branch%ele(i)%name,'MIDWAY')/=0)exit end do print '(/,a,1x,i10,1x,a)', 'get_branch_inv_matrix at:',n, branch%ele(n)%name mat_forward = m call invert_matrix(m) mat = m test = matmul(mat,temp) print '(/,a)', 'Branch 0 forward matrix' do j=1,6 print '(6es12.4)', temp(j,1:6) end do print '(/,a)', 'Branch 0 inverse matrix' do j=1,6 print '(6es12.4)', mat(j,1:6) end do print '(/,a)', 'test - mat*temp (should be identity)' do j=1,6 print '(6es12.4)', test(j,1:6) end do !the matrix should be the identity. And if it is then Prod test(i,i) = 1 diag_prod = test(1,1) * test(2,2)* test(3,3)* test(4,4)* test(5,5)* test(6,6) if(abs(diag_prod -1.) > 0.1)err = .true. if(err) print '(/,a)', ' No inverse injection line matrix ' return end