AdventOfFortran/2019/src/day03.f90

109 lines
3.3 KiB
Fortran
Raw Normal View History

2023-12-01 06:07:03 +00:00
program day3
implicit none
integer, parameter :: path_length = 100
integer, parameter :: n_data_lines = 2
integer, parameter :: max_chars = 2000
character(path_length) :: fname
integer :: n_arguments
character(max_chars), allocatable :: data_strs(:)
!integer :: i
n_arguments = command_argument_count()
if (n_arguments .eq. 1) then
call get_command_argument(1, fname)
print *, "File: ", fname
else
print *, "Wrong number of arguments: ", n_arguments
stop
end if
data_strs = read_instruction_strings(fname)
print *, data_strs
print *, data_strs(1)
print *, data_strs(1)(5:)
deallocate(data_strs)
contains
function read_instruction_strings(fname) result(strs)
implicit none
character(path_length) :: fname
character(max_chars), allocatable :: strs(:)
integer :: i_read
allocate(strs(n_data_lines))
open(10, file=fname)
do i_read=1,n_data_lines
read(10, "(A)") strs(i_read)
end do
close(10)
end function read_instruction_strings
function all_occupied_points(istring) result(occupied)
implicit none
integer, parameter :: imax = 6
character(max_chars), allocatable :: istring
integer :: n_cmds = 1
integer :: i_chars, i1, i2, i_s
integer :: t_strlen
integer :: t_mvmnt, s_mvmnt
integer :: d_x, d_y, c_x, c_y
character(imax), allocatable :: tcmds(:)
character(1), allocatable :: dirs(:)
integer, allocatable :: mvmnts(:)
logical, allocatable :: occupied(:,:)
t_strlen = len_trim(istring)
do i_chars=1,t_strlen
if (istring(i_chars:i_chars) .eq. ',') then
n_cmds = n_cmds + 1
end if
end do
allocate(tcmds(1:n_cmds))
allocate(dirs(1:n_cmds))
allocate(mvmnts(1:n_cmds))
read(istring, *) tcmds
s_mvmnt = 0
do i1 = 1,n_cmds
dirs(i1) = tcmds(i1)(1:1)
read(tcmds(i1)(2:), *) t_mvmnt
s_mvmnt = s_mvmnt + t_mvmnt
mvmnts(i1) = t_mvmnt
end do
allocate(occupied(1:2, 1:s_mvmnt))
c_x = 0
c_y = 0
i_s = 1
do i1=1,n_cmds
if (dirs(i1) .eq. 'U') then
d_y = 1
d_x = 0
else if (dirs(i1) .eq. 'D') then
d_y = -1
d_x = 0
else if (dirs(i1) .eq. 'L') then
d_y = 0
d_x = -1
else
d_y = 0
d_x = 1
end if
t_mvmnt = mvmnts(i1)
do i2 = i, t_mvmnt
c_x = c_x + d_x
c_y = c_y + d_y
occupied(1, i_s) = c_x
occupied(2, i_s) = c_y
i_s = i_s + 1
end do
end do
deallocate(tcmds)
deallocate(dirs)
deallocate(mvmnts)
end function all_occupied_points
end program day3