program day5 implicit none integer, parameter :: i_kind = selected_int_kind(20) integer, parameter :: max_chars = 300 integer, parameter :: max_iter = 20 character(200) :: fname character(max_chars) :: fline integer :: n_arguments integer :: istat integer(kind=i_kind), allocatable :: seedvals(:) integer(kind=i_kind), allocatable :: dat_source(:), dat_dest(:) integer(kind=i_kind) :: ldat(1:3) logical, allocatable :: dat_point_found(:) integer :: pos_col, num_seeds, num_chars, i, sec integer(kind=i_kind) :: s_min, d_min, r_len, source_val integer(kind=i_kind) :: min_val integer :: min_index print *, "Number of bits: ", i_kind * 8 n_arguments = command_argument_count() if (n_arguments .eq. 1) then call get_command_argument(1, fname) print *, "File: ", trim(fname) print * else print *, "Wrong number of arguments: ", n_arguments stop end if open(10, file=fname) read(10, "(A)", iostat = istat) fline pos_col = scan(fline, ":") num_seeds = 0 num_chars = len_trim(fline) do i=pos_col + 1,num_chars if (fline(i:i) .eq. ' ') then num_seeds = num_seeds + 1 end if end do print *, "Number of seeds: ", num_seeds allocate(seedvals(1:num_seeds)) allocate(dat_source(1:num_seeds)) allocate(dat_dest(1:num_seeds)) allocate(dat_point_found(1:num_seeds)) read(fline((pos_col + 1):(num_chars)), *) seedvals read(10, "(A)", iostat = istat) fline dat_dest = seedvals do sec=1, max_iter dat_source = dat_dest dat_dest = 0 dat_point_found = .false. read(10, "(A)", iostat = istat) fline if (is_iostat_end(istat)) then exit end if do read(10, "(A)", iostat = istat) fline num_chars = len_trim(fline) if (is_iostat_end(istat) .or. (num_chars .eq. 0)) then exit end if read(fline, *) ldat s_min = ldat(2) d_min = ldat(1) r_len = ldat(3) do i=1,num_seeds source_val = dat_source(i) if ((source_val .ge. s_min) .and. (source_val .lt. (s_min + r_len))) then dat_point_found(i) = .true. dat_dest(i) = source_val - s_min + d_min !write(*, 20) ldat(1), ldat(2), ldat(3), source_val, dat_dest(i) end if end do end do do i=1,num_seeds if (.not. dat_point_found(i)) then dat_dest(i) = dat_source(i) !write(*, 21) i, dat_dest(i), dat_dest(i) end if end do !print * if (is_iostat_end(istat)) then exit end if end do close(10) min_val = huge(min_val) min_index = -1 do i=1,num_seeds if (dat_dest(i) .lt. min_val) then min_index = 1 min_val = dat_dest(i) end if end do print "(a, i11)", "Minimum location number: ", min_val deallocate(seedvals) deallocate(dat_source) deallocate(dat_dest) deallocate(dat_point_found) !20 format(i4, i4, i4, ': ', i4, ' -> ', i4) !21 format(i4, ': ', i4, ' -> ', i4) end program day5