AdventOfFortran/2023/src/day03.f90

152 lines
5.3 KiB
Fortran

program day3
implicit none
integer, parameter :: max_lines = 200
integer, parameter :: max_chars = 200
character(200) :: fname
integer :: n_arguments
character(10) :: numbers
character(11) :: non_symbols
character(1) :: symb
integer :: part_sum = 0
integer :: part_val
character(max_chars) :: schematic(1:max_lines)
character(max_chars) :: temp_line
character(max_chars) :: num_string
integer :: line, cp0, cp1, cp2, i1, i2, cind
integer :: schematic_width, schematic_height
integer :: istat
logical :: is_part
integer, parameter :: max_gears = 10000
integer :: gear_parts(max_gears, 0:2)
integer :: found_gears = 0
integer, allocatable :: gearmap(:,:)
integer, allocatable :: gearval(:,:)
integer :: gear_ratio_sum = 0
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
do i1=0,9
numbers(i1+1:i1+1) = char(ichar('0') + i1)
end do
non_symbols(1:10) = numbers
non_symbols(11:11) = "."
open(10, file=fname)
do line=1,max_lines
read(10, "(A)", iostat = istat) temp_line
if (is_iostat_end(istat)) then
exit
else if (len_trim(temp_line) .eq. 0) then
exit
else
schematic(line) = temp_line
end if
end do
schematic_height = line - 1
schematic_width = len_trim(schematic(1))
do line=1,schematic_height
temp_line = schematic(line)
cp2 = 1
do
cp0 = cp2
cp1 = scan(temp_line(cp0:schematic_width), numbers)
if (cp1 .eq. 0) then
exit
end if
cp1 = cp1 + cp0 - 1
cp2 = verify(temp_line(cp1:schematic_width), numbers)
if (cp2 .eq. 0) then
cp2 = schematic_width+1
else
cp2 = cp2 + cp1 - 1
end if
num_string = temp_line(cp1:(cp2-1))
read(num_string, *) part_val
i1 = max(1, cp1-1)
i2 = min(schematic_width, cp2)
is_part = .false.
if (line .gt. 1) then
cind = verify(schematic(line-1)(i1:i2), non_symbols)
if (cind .ne. 0) then
symb = schematic(line-1)(i1 + cind - 1:i1 + cind - 1)
print *, line, cp1, symb, part_val
part_sum = part_sum + part_val
is_part = .true.
if (symb .eq. '*') then
found_gears = found_gears + 1
gear_parts(found_gears, 0) = part_val
gear_parts(found_gears, 1) = cind+i1-1
gear_parts(found_gears, 2) = line-1
end if
end if
end if
cind = verify(schematic(line)(i1:i2), non_symbols)
if (cind .ne. 0) then
symb = schematic(line)(i1 + cind - 1:i1 + cind - 1)
print *, line, cp1, symb, part_val
if (.not. is_part) then
part_sum = part_sum + part_val
is_part = .true.
end if
if (symb .eq. '*') then
found_gears = found_gears + 1
gear_parts(found_gears, 0) = part_val
gear_parts(found_gears, 1) = cind+i1-1
gear_parts(found_gears, 2) = line
end if
end if
if (line .lt. schematic_height) then
cind = verify(schematic(line+1)(i1:i2), non_symbols)
if (cind .ne. 0) then
symb = schematic(line+1)(i1 + cind - 1:i1 + cind - 1)
print *, line, cp1, symb, part_val
part_sum = part_sum + part_val
if (.not. is_part) then
part_sum = part_sum + part_val
is_part = .true.
end if
if (symb .eq. '*') then
found_gears = found_gears + 1
gear_parts(found_gears, 0) = part_val
gear_parts(found_gears, 1) = cind+i1-1
gear_parts(found_gears, 2) = line+1
end if
end if
end if
end do
end do
close(10)
print *
print *, "Sum of part numbers: ", part_sum
print *, "Number of found gears: ", found_gears
allocate(gearmap(1:schematic_width, 1:schematic_height), source = 0)
allocate(gearval(1:schematic_width, 1:schematic_height), source = 1)
do i1=1,found_gears
cp1 = gear_parts(i1, 1)
cp2 = gear_parts(i1, 2)
gearmap(cp1, cp2) = gearmap(cp1, cp2) + 1
gearval(cp1, cp2) = gearval(cp1, cp2) * gear_parts(i1, 0)
end do
do i1=1,found_gears
cp1 = gear_parts(i1, 1)
cp2 = gear_parts(i1, 2)
if (gearmap(cp1, cp2) .eq. 2) then
gearmap(cp1, cp2) = -1
gear_ratio_sum = gear_ratio_sum + gearval(cp1, cp2)
end if
end do
print *, "Gear ratio sum: ", gear_ratio_sum
deallocate(gearmap)
deallocate(gearval)
end program day3