My yearly advent-of-code solutions
1module day_04_utils
2 implicit none
3contains
4 recursive function find_xmas(arr, row, col,row_dir, col_dir, search_letter) result(found)
5 implicit none
6 character(len=140), intent(in), allocatable :: arr(:)
7 character(len=1), intent(in) :: search_letter
8 integer, intent(in) :: row, col, row_dir, col_dir
9 integer :: new_row, new_col
10 logical :: found
11
12 if(arr(row)(col:col) == search_letter) then
13 if(search_letter == 'S') then
14 found = .true.
15 else
16 new_row = row + row_dir
17 new_col = col + col_dir
18 if(new_row > len(arr(row)) .or. new_row < 1 .or. new_col > size(arr) .or. new_col < 1) then
19 found = .false.
20 else
21 select case(search_letter)
22 case('M')
23 found = find_xmas(arr, new_row, new_col, row_dir, col_dir, 'A')
24 case('A')
25 found = find_xmas(arr, new_row, new_col, row_dir, col_dir, 'S')
26 end select
27 end if
28 end if
29 else
30 found = .false.
31 end if
32 end function find_xmas
33end module day_04_utils
34program day_04
35 use day_04_utils
36 implicit none
37 character(len=140) , allocatable :: lines(:)
38 integer :: io, row, col, score, z
39 logical :: found
40
41 score = 0
42 open(newunit=io, file='./day_04_input.txt', status='old', action='read')
43 allocate(lines(140))
44 read(io, '(a)') lines
45 do row = 1, size(lines)
46 do col = 1, len(lines(row))
47 if (lines(row)(col:col) == 'X') then
48 do z = 1, 8
49 found = .false.
50 select case (z)
51 case(1)
52 found = find_xmas(lines, row, col-1, 0, -1, 'M')
53 case(2)
54 found = find_xmas(lines, row-1, col-1, -1, -1, 'M')
55 case(3)
56 found = find_xmas(lines, row-1, col, -1, 0, 'M')
57 case(4)
58 found = find_xmas(lines, row-1, col+1, -1, 1, 'M')
59 case(5)
60 found = find_xmas(lines, row, col+1, 0, 1, 'M')
61 case(6)
62 found = find_xmas(lines, row+1, col+1, 1, 1, 'M')
63 case(7)
64 found = find_xmas(lines, row+1, col, 1, 0, 'M')
65 case(8)
66 found = find_xmas(lines, row+1, col-1, 1, -1, 'M')
67 end select
68 if(found) then
69 score = score + 1
70 end if
71 end do
72 end if
73 end do
74 end do
75 deallocate(lines)
76 print*, score
77
78end program day_04