program day8b implicit none integer, parameter :: max_chars = 400 integer, parameter :: max_nodes = 1000 integer, parameter :: max_iter = 100000 character(200) :: fname character(max_chars) :: fline integer :: n_arguments integer :: istat character(max_chars) :: dir_ins integer :: n_dir_ins integer :: n_nodes character(len=3) :: node character(len=1) :: dir character(len=3) :: nodes(1:max_nodes), lnodes(1:max_nodes), rnodes(1:max_nodes) integer :: periods(max_nodes) integer :: cursors(max_nodes) integer :: n_cursors integer :: i, ic, i2, LRcur, i3 logical :: found_z integer, parameter :: b_kind = selected_int_kind(20) integer(kind=b_kind) :: p_sum 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)") dir_ins n_dir_ins = len_trim(dir_ins) read(10, "(a)") fline n_nodes = 0 do i=1,max_nodes read(10, "(a)", iostat=istat) fline if ((len_trim(fline) .eq. 0) .or. (is_iostat_end(istat))) then exit end if read(fline(1:3), "(a)") nodes(i) read(fline(8:10), "(a)") lnodes(i) read(fline(13:15), "(a)") rnodes(i) n_nodes = n_nodes + 1 end do close(10) cursors = -1 n_cursors = 0 do i=1, n_nodes if (nodes(i)(3:3) .eq. "A") then n_cursors = n_cursors + 1 cursors(n_cursors) = i end if end do print *, "Number of cursors: ", n_cursors periods = 0 do i=1,max_iter LRcur = mod(i-1, n_dir_ins) + 1 dir = dir_ins(LRcur:LRcur) do ic=1,n_cursors if (dir .eq. "L") then node = lnodes(cursors(ic)) else node = rnodes(cursors(ic)) end if do i2=1, n_nodes if (nodes(i2) .eq. node) then cursors(ic) = i2 exit end if end do end do found_z = .true. do ic=1,n_cursors if (nodes(cursors(ic))(3:3) .ne. "Z") then found_z = .false. else if (periods(ic) .eq. 0) then periods(ic) = i end if end do if (found_z) then exit end if end do if (found_z) then print *, "Found nodes ending in Z after ", i, " iterations" else print *, "Did not find nodes ending in Z after ", max_iter, " iterations" print *, "Periods:" print "(1i9)", periods(1:n_cursors) p_sum = 1 print * do ic=1,n_cursors p_sum = p_sum * periods(ic) end do print *, "Potential answer: ", p_sum do i=1,n_cursors-1 do i2 = i+1,n_cursors do i3=2,periods(i2) if (mod(periods(i), i3) .eq. 0 .and. mod(periods(i2), i3) .eq. 0) then do periods(i) = periods(i) / i3 if (mod(periods(i), i3) .ne. 0) then exit end if end do end if end do end do end do print *, "Factors: " print "(1i9)", periods(1:n_cursors) p_sum = 1 print * do ic=1,n_cursors p_sum = p_sum * periods(ic) end do print *, "Potential answer: ", p_sum end if end program day8b