!........................................................................ ! ! Subroutine : Read_indep_var (con_file, lat, begin_str, vari, type_list) ! ! Description: Subroutine to parse the constraint file for the independent ! variables to use in optimization. ! ! Arguments : ! Input: ! con_file -- character(*): name of the constraint file ! lat -- record/lat_struct/: lookup list for variable names ! begin_str -- character(*): string to look for in con_file signifying ! the beginning of the variable list ! type_list -- Logical: If .true. then the list of variables will ! typed on the TTY. ! ! Output: ! vari -- record/indep_var/: array of variables to use ! ! Mod/Commons: ! ! Calls : ! ! Author : ! ! Modified : ! ! open file with the variable list ! find start of variable list ! read and parse variable list from file ! match variables with elements in the lat. ! also do some error checking. ! if needed then type out the variable list !........................................................................ subroutine read_indep_var(con_file, lat, begin_str, vari, type_list) use bmad use sim_utils use constraints_mod implicit none type (indep_var_struct) vari type (lat_struct), target :: lat type (ele_struct), pointer :: ele, lord type (control_struct), pointer :: ctl logical find_use, parsing, matched, type_list, match integer lun, ix, num_use, val_id, i, j integer rindex character(*) con_file, begin_str character(80) line character(16) val_name character(40) ele_name, lat_name ! open file with the variable list lun = lunget() open(lun, file=con_file, status='old', action='read') ! find start of variable list num_use = 0 find_use = .true. do while(find_use) read(lun, '(a)', end=100) line call string_trim (line, line, ix) call str_upcase (line, line) if((line(1:1) == '$' .or. line(1:1) == '&') .and. & line(2:ix) == begin_str) find_use = .false. enddo ! read and parse variable list from file parsing = .true. do while(parsing) read(lun, '(a)', end=100) line call str_upcase (line, line) if (index(line, '!') /= 0) line = line(:index(line, '!')) call string_trim (line, line, ix) if(line(1:ix) =='$END' .or. line(1:ix) == '/') then parsing = .false. else if(line(1:3)=='USE') then call string_trim (line(ix+1:), line, ix) num_use = num_use + 1 vari%v(num_use)%ele_name = line(:ix) call string_trim (line(ix+1:), line, ix) vari%v(num_use)%val_name = line(:ix) call string_trim (line(ix+1:), line, ix) read(line(:ix), *) vari%v(num_use)%delta call string_trim (line(ix+1:), line, ix) read(line(:ix), *) vari%v(num_use)%min_val call string_trim (line(ix+1:), line, ix) read(line(:ix), *) vari%v(num_use)%max_val if (vari%v(num_use)%max_val < vari%v(num_use)%min_val) then print *, 'ERROR IN READ_INDEP_VAR: VARIABLE MAX_VAL IS LESS THAN MIN_VAL' print *, ' FOR VARIABLE: ', trim(vari%v(num_use)%ele_name), & ' ', trim(vari%v(num_use)%ele_name) print *, ' MIN, MAX:', vari%v(num_use)%min_val, & vari%v(num_use)%max_val call err_exit endif elseif (line(1:1) /= ' ') then print *, 'ERROR IN READ_INDEP_VAR: FIRST WORD IN LINE NOT', & ' "USE" OR "GANG": ', line(:ix) call err_exit endif enddo 100 close(lun) ! match variables with elements in the lat. ! also do some error checking. do ix = 1, num_use call str_upcase(ele_name, vari%v(ix)%ele_name) matched = .false. do rindex = 1, lat%n_ele_max ele => lat%ele(rindex) call str_upcase(lat_name, ele%name) match = str_match_wild(lat_name, ele_name) if (match) then vari%v(ix)%rindex = rindex vari%v(ix)%ele_name = lat_name matched = .true. exit endif enddo if (.not. matched) then print *, 'ERROR IN READ_INDEP_VAR: ELEMENT NOT FOUND IN LAT: ', ele_name call err_exit endif val_name = vari%v(ix)%val_name val_id = attribute_index(ele, val_name) if (val_id <= 0) then print *, 'ERROR IN READ_INDEP_VAR: BAD ATTRIBUTE: ', val_name call err_exit endif vari%v(ix)%val_id = val_id if (ele%slave_status == super_slave$) then print *, 'ERROR IN READ_INDEX_VAR: VARIABLE IS A SUPER_SLAVE! ', lat_name call err_exit else do i = 1, ele%n_lord lord => pointer_to_lord(ele, i, ctl) if (ctl%ix_attrib == val_id) then print *, 'ERROR IN READ_INDEX_VAR: VARIABLE IS OVERLAYED AND CANNOT' print *, ' BE CONTROLLED DIRECTLY: ', lat_name, val_name print *, ' CONTROLLED BY OVERLAY: ', lord%name call err_exit endif enddo endif ! check for dependent variables if (.not. attribute_free(rindex, val_name, lat)) stop enddo ! if needed then type out the variable list if (type_list) then do ix = 1, num_use print *, ix, ' ', vari%v(ix)%ele_name, vari%v(ix)%val_name, ' ', vari%v(ix)%delta enddo endif vari%n_var = num_use return end