My yearly advent-of-code solutions
1module day2_utils
2 implicit none
3 contains
4 subroutine has_fail_value(list, res)
5 implicit none
6 integer, allocatable, intent(in) :: list(:)
7 integer :: i
8 integer, intent(out):: res
9 logical is_decrement
10
11 res = -1
12 do i = 1, size(list) - 1
13 if (list(i) == list(i+1)) then
14 res= i
15 exit
16 end if
17 if(i == 1 .and. list(i) > list(i+1)) then
18 is_decrement = .true.
19 else if (i==1 .and. list(i) < list(i+1)) then
20 is_decrement = .false.
21 end if
22
23 if(is_decrement) then
24 if (list(i) < list(i+1) .or. abs(list(i) - list(i+1)) > 3) then
25 res = i
26 exit
27 end if
28 else
29 if (list(i) > list(i+1) .or. abs(list(i) - list(i+1)) > 3) then
30 res = i
31 exit
32 end if
33 end if
34 end do
35 end subroutine has_fail_value
36end module day2_utils
37
38program day_02_part_2
39 use day2_utils
40 implicit none
41 logical :: is_decrement
42 integer :: io, i,x,y, fail, spaces, res
43 integer, dimension(:), allocatable :: list, list2
44 character(len=100) :: line
45
46 open(newunit=io, file='./day_02_input.txt', status='old', action='read')
47
48 res = 0
49 do i = 1, 1000
50 read(io, '(a)') line ! reading the line
51 spaces = 1 ! reset space count
52 do x = 1, len(trim(line))
53 ! counting spaces to see how big of an array we need to allocate
54 if(iachar(line(x:x))== 32 ) then
55 spaces = spaces+1
56 end if
57 end do
58
59 allocate(list(spaces))
60 read(line, *) list !reading the ints into an array
61 fail = -1
62 call has_fail_value(list, fail)
63 if (fail > 0) then
64 y = 1
65 allocate(list2(spaces -1))
66 do x = 1, size(list)
67 if(x /= fail) then
68 list2(y) = list(x)
69 y = y+1
70 end if
71 end do
72 fail = -1
73 call has_fail_value(list2, fail)
74 if(fail > 0) then
75 print*, list2(:)
76 end if
77 deallocate(list2)
78
79 end if
80 if (fail == -1) then
81 res = res + 1
82 endif
83 deallocate(list)
84 end do
85 print*, res
86end program day_02_part_2