My yearly advent-of-code solutions
1module day_07_part_2_utils
2 use iso_fortran_env, only: int64
3 implicit none
4contains
5 recursive function test_values(arr, target, next_idx, current_value) result(pass)
6 implicit none
7 integer(kind=int64), intent(in) :: target, current_value, arr(:)
8 integer, intent(in) :: next_idx
9 character(len=20) :: str_1, str_2, concat_str
10 integer(kind=int64) :: concat_value
11 logical :: pass
12
13 if(next_idx > size(arr)) then
14 pass = current_value == target
15 return
16 end if
17
18 write(str_1, '(I0)') current_value
19 write(str_2, '(I0)') arr(next_idx)
20 concat_str = trim(str_1) // trim(str_2)
21 read(concat_str, '(I20)') concat_value
22
23 pass = test_values(arr, target, next_idx + 1, current_value + arr(next_idx)) .or. &
24 test_values(arr, target, next_idx + 1, current_value * arr(next_idx)) .or. &
25 test_values(arr, target, next_idx + 1, concat_value)
26 end function test_values
27 logical function is_calibrated(arr, target)
28 implicit none
29 integer(kind=int64), intent(in) :: target, arr(:)
30
31 is_calibrated = test_values(arr, target, 2, arr(1))
32 end function is_calibrated
33end module day_07_part_2_utils
34program day_07_part_2
35 use iso_fortran_env, only: int64
36 use day_07_part_2_utils
37 implicit none
38 integer(kind=int64) :: test_number, res
39 integer(kind=int64), allocatable:: work(:)
40 integer :: io, ios, idx, i, ct
41 character(len=200) :: line, work_line
42 logical :: pass
43 res = 0
44 open(newunit=io, file='./day_07_input.txt', status='old', action='read')
45 do
46 read(io, '(a)', iostat=ios) line
47 if (ios /= 0) exit
48 idx = index(line, ':')
49 if (idx > 0) then
50 read(line(1:idx-1), *) test_number
51 ct = 0
52 work_line = trim(line(idx+1:len(trim(line))))
53 do i = 1 , len(trim(work_line))
54 if(work_line(i:i) == ' ') then
55 ct = ct + 1
56 end if
57 end do
58 allocate(work(ct))
59 read(work_line, *) work(:)
60 end if
61 pass = is_calibrated(work, test_number)
62 if(pass) then
63 res = res + test_number
64 end if
65 deallocate(work)
66 end do
67 print*, "Result: ", res
68end program day_07_part_2