!+ ! Subroutine validator (con, lat, iunit) ! ! IUNIT -- Integer: ! 0 -> Type constraint list and write to file cons_ ! +int -> Write to that unit number ! !- subroutine validator (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 character * 12, lookit ! if (iunit == 0) then open(unit=29, file='validation.dat') iu = 29 else iu = iunit endif write (iu, '(a19,a)')' Lattice file name: ', con%lat_file write (iu, '(a33)')' The following are out of bounds ' print '(a33)',' The following are out of bounds ' write (iu, '(5x, a)') 'Constraint Plane Where1' // & ' Where2 Value Merit Target/Max' print '(5x, a)', 'Constraint Plane Where1' // & ' Where2 Value OK Target/Max' fmt = '(1x, i3, 1x, a, 2x, a3,1x, a8, 2x, a7, 1pe12.3, a12, 2x, a10)' fmt2 = '(1x, i3, 1x, a, 2x, a3,1x, a8, 2x, a7, 1pe12.3, a12, 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 if (location > 0) then ! if a range then find nearest recognizable name if (con%c(i)%where2(1:4) /= 'NULL') 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 lookit = ' ' if(contrib > 0)then lookit = ' ****** ' print fmt, i,var_name(variable), plane_name(plane),con%c(i)%where1, & con%c(i)%where2, value, lookit, lat%ele(location)%name write(iu,fmt)i,var_name(variable), plane_name(plane),con%c(i)%where1, & con%c(i)%where2, value, lookit, lat%ele(location)%name endif else lookit = ' ' if(contrib > 0)then lookit = ' ****** ' print fmt2, i,var_name(variable), plane_name(plane),con%c(i)%where1, & con%c(i)%where2, value, lookit, con%c(i)%target_value write(iu,fmt2)i,var_name(variable), plane_name(plane),con%c(i)%where1, & con%c(i)%where2, value, lookit, con%c(i)%target_value endif endif end do print * 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 if (iunit == 0) close(unit=iu) end subroutine