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