!........................................................................ ! ! Subroutine : showme (con, lat, iunit ! ! Description: ! ! Arguments : ! IUNIT -- Integer: ! 0 -> Type constraint list and write to file cons_ ! +int -> Write to that unit number ! ! Mod/Commons: ! ! Calls : ! ! Author : ! ! Modified : ! ! ! if a range then find nearest recognizable name !........................................................................ ! ! ! $Log$ ! Revision 1.9 2007/01/30 16:15:14 dcs ! merged with branch_bmad_1. ! ! Revision 1.5 2006/11/16 18:55:45 mjf7 ! Bmad change in ele_struct name length caused bugs. ! ! Revision 1.4 2006/09/26 16:05:01 mjf7 ! Adding sigma norming and fom_power back into main branch ! ! Revision 1.3.2.1 2006/09/25 18:33:49 mjf7 ! Added sigma norming ! ! Revision 1.3 2005/01/17 19:23:15 dlr ! lrbbi_setup - correct bug in condition for parameters to calc lrbbi ! read_contraints - add weak beam bunch to single variable list ! showme - change contribution to include weight ! ! Revision 1.2 2003/04/30 17:14:55 cesrulib ! dlr's changes since last import ! ! Revision 1.1.1.1 2002/12/13 19:23:30 cesrulib ! import bmadz ! ! !........................................................................ ! subroutine showme (con, lat, iunit) use bmad use constraints_mod implicit none type (lat_struct) lat type (constraint_struct) con integer i,location, variable, plane, iunit, iu real(rp) value, contrib character dummer*40, fmt*75, fmt2*75 integer location_north, location_south, n real(rp) distance_north, distance_south ! if (iunit == 0) then open(unit=29, file='cons_'//lat%lattice) iu = 29 else iu = iunit endif write (iu, '(5x, a)') 'Constraint Plane Where1' // & ' Where2 Value Merit Target/Max' print '(5x, a)', 'Constraint Plane Where1' // & ' Where2 Value Merit Target/Max' fmt = '(1x, i3, 1x, a20, 2x, a3, 1x, a8, 2x, a7, 1pe12.3, e12.2, 2x, a10)' fmt2 = '(1x, i3, 1x, a20, 2x, a3, 1x, a8, 2x, a7, 1pe12.3, e12.2, 2x, 1pe10.2)' do i=1,con%n_constraint location = con%c(i)%location value = con%c(i)%actual_value variable = con%c(i)%variable plane = con%c(i)%plane contrib = (con%c(i)%contribution*con%c(i)%weight)**con%fom_power if (location > 0) then ! if a range then find nearest recognizable name if (index(con%c(i)%where2,'NULL') == 0) then n=0 dummer = lat%ele(location)%name do while(dummer(1:1) /= 'I' .and. dummer(1:1) /= 'Q') !not IP or quad n=n+1 dummer = lat%ele(location-n)%name end do location_south = location-n distance_south = lat%ele(location)%s - lat%ele(location_south)%s n=0 dummer = lat%ele(location)%name do while(dummer(1:1) /= 'I' .and. dummer(1:1) /= 'Q') !not IP or quad n=n+1 dummer = lat%ele(location+n)%name end do location_north = location+n distance_north = lat%ele(location_north)%s - lat%ele(location)%s location = location_south if (distance_north < distance_south) location = location_north endif print fmt, i,var_name(variable), plane_name(plane),con%c(i)%where1, & con%c(i)%where2, value, contrib, lat%ele(location)%name write(iu,fmt)i,var_name(variable), plane_name(plane),con%c(i)%where1, & con%c(i)%where2, value, contrib, lat%ele(location)%name else print fmt2, i,var_name(variable), plane_name(plane),con%c(i)%where1, & con%c(i)%where2, value, contrib, con%c(i)%target_value write(iu,fmt2)i,var_name(variable), plane_name(plane),con%c(i)%where1, & con%c(i)%where2, value, contrib, con%c(i)%target_value endif end do print * print '(a,1pe13.6)', ' Figure of Merit:', Con%figure_of_merit write (iu, '(a,1pe13.6)') ' Figure of Merit:', Con%figure_of_merit print '(1x,2(a,i1),a,i2)', 'Number of trains = ',con%n_trains,' Number of cars = ',& con%n_cars, ' Bunch spacing(ns) = ',con%n_14ns_space*14 write (iu,'(2(a,i1),a,i2)') 'Number of trains = ',con%n_trains,' Number of cars = ',& con%n_cars, ' Bunch spacing(ns) = ',con%n_14ns_space*14 call showme_topten(con, lat, iu) if (iunit == 0) close(unit=iu) end subroutine