My yearly advent-of-code solutions

formatting and part 2 done

Changed files
+165 -161
2024
+36 -36
2024/day_01.f90
···
-
module sorting
-
! apparently you need to put the subroutine in a module
-
implicit none
-
contains
-
subroutine sort(arr)
!! a little insertion sort KISS
!! also yea we have no in built sorting
-
implicit none
-
integer, intent(inout) :: arr(1000)
-
integer :: i, j, key
-
do i = 2, 1000
-
key = arr(i)
-
j = i - 1
-
do while (j > 0 .and. arr(j) > key)
-
arr(j+1) = arr(j)
-
j = j - 1
end do
-
arr(j+1) = key
-
end do
-
end subroutine sort
end module sorting
program day_01
-
use sorting
-
implicit none
-
integer :: io, i, dist, sim, left(1000), right(1000) ! yea we are coding to the input file and not generic
-
open(newunit=io, file='./day_01_input.txt', status='old', action='read')
-
do i = 1, 1000
-
read(io, *) left(i), right(i) ! read both values in line
-
end do
-
close(10) ! close the file
-
call sort(left)
-
call sort(right)
-
! if we dont init these bad things happen on multiple runs
-
dist = 0
-
sim = 0
-
do i = 1, 1000
-
dist = dist + abs(left(i) - right(i))
-
sim = sim + left(i) * count(right == left(i))
-
end do
-
print*, "distance: ", dist
-
print*, "similarity: ", sim
end program day_01
···
+
module sorting
+
! apparently you need to put the subroutine in a module
+
implicit none
+
contains
+
subroutine sort(arr)
!! a little insertion sort KISS
!! also yea we have no in built sorting
+
implicit none
+
integer, intent(inout) :: arr(1000)
+
integer :: i, j, key
+
do i = 2, 1000
+
key = arr(i)
+
j = i - 1
+
do while (j > 0 .and. arr(j) > key)
+
arr(j+1) = arr(j)
+
j = j - 1
+
end do
+
arr(j+1) = key
end do
+
end subroutine sort
end module sorting
program day_01
+
use sorting
+
implicit none
+
integer :: io, i, dist, sim, left(1000), right(1000) ! yea we are coding to the input file and not generic
+
open(newunit=io, file='./day_01_input.txt', status='old', action='read')
+
do i = 1, 1000
+
read(io, *) left(i), right(i) ! read both values in line
+
end do
+
close(10) ! close the file
+
call sort(left)
+
call sort(right)
+
! if we dont init these bad things happen on multiple runs
+
dist = 0
+
sim = 0
+
do i = 1, 1000
+
dist = dist + abs(left(i) - right(i))
+
sim = sim + left(i) * count(right == left(i))
+
end do
+
print*, "distance: ", dist
+
print*, "similarity: ", sim
end program day_01
+49 -49
2024/day_02.f90
···
program day_02
-
implicit none
-
logical :: is_decrement, fail
-
integer :: io, i,x, spaces, res
-
integer, dimension(:), allocatable :: list
-
character(len=100) :: line
-
open(newunit=io, file='./day_02_input.txt', status='old', action='read')
-
res = 0
-
do i = 1, 1000
-
read(io, '(a)') line ! reading the line
-
spaces = 1 ! reset space count
-
do x = 1, len(trim(line))
-
! counting spaces to see how big of an array we need to allocate
-
if(iachar(line(x:x))== 32 ) then
-
spaces = spaces+1
-
end if
-
end do
-
allocate(list(spaces))
-
read(line, *) list !reading the ints into an array
-
fail = .false.
-
-
do x = 1, size(list) -1
-
if (list(x) == list(x+1)) then
-
fail = .true.
-
exit
-
end if
-
if(x == 1 .and. list(x) > list(x+1)) then
-
is_decrement = .true.
-
else if (x==1 .and. list(x) < list(x+1)) then
-
is_decrement = .false.
-
end if
-
-
if(is_decrement) then
-
if (list(x) < list(x+1) .or. abs(list(x) - list(x+1)) > 3) then
-
fail = .true.
-
exit
-
end if
-
else
-
if (list(x) > list(x+1) .or. abs(list(x) - list(x+1)) > 3) then
-
fail = .true.
-
exit
-
end if
-
end if
-
end do
-
if (fail .eqv. .false.) then
-
res = res + 1
-
endif
-
deallocate(list)
-
end do
-
print*, res
end program day_02
···
program day_02
+
implicit none
+
logical :: is_decrement, fail
+
integer :: io, i,x, spaces, res
+
integer, dimension(:), allocatable :: list
+
character(len=100) :: line
+
open(newunit=io, file='./day_02_input.txt', status='old', action='read')
+
res = 0
+
do i = 1, 1000
+
read(io, '(a)') line ! reading the line
+
spaces = 1 ! reset space count
+
do x = 1, len(trim(line))
+
! counting spaces to see how big of an array we need to allocate
+
if(iachar(line(x:x))== 32 ) then
+
spaces = spaces+1
+
end if
+
end do
+
allocate(list(spaces))
+
read(line, *) list !reading the ints into an array
+
fail = .false.
+
+
do x = 1, size(list) -1
+
if (list(x) == list(x+1)) then
+
fail = .true.
+
exit
+
end if
+
if(x == 1 .and. list(x) > list(x+1)) then
+
is_decrement = .true.
+
else if (x==1 .and. list(x) < list(x+1)) then
+
is_decrement = .false.
+
end if
+
+
if(is_decrement) then
+
if (list(x) < list(x+1) .or. abs(list(x) - list(x+1)) > 3) then
+
fail = .true.
+
exit
+
end if
+
else
+
if (list(x) > list(x+1) .or. abs(list(x) - list(x+1)) > 3) then
+
fail = .true.
+
exit
+
end if
+
end if
+
end do
+
if (fail .eqv. .false.) then
+
res = res + 1
+
endif
+
deallocate(list)
+
end do
+
print*, res
end program day_02
+80 -76
2024/day_02_part_2.f90
···
-
module day2_utils
-
implicit none
-
contains
-
subroutine has_fail_value(list, res)
-
implicit none
-
integer, allocatable, intent(in) :: list(:)
-
integer :: i
-
integer, intent(out):: res
-
logical is_decrement
-
res = -1
-
do i = 1, size(list) - 1
-
if (list(i) == list(i+1)) then
-
res= i
-
exit
-
end if
-
if(i == 1 .and. list(i) > list(i+1)) then
-
is_decrement = .true.
-
else if (i==1 .and. list(i) < list(i+1)) then
-
is_decrement = .false.
-
end if
-
-
if(is_decrement) then
-
if (list(i) < list(i+1) .or. abs(list(i) - list(i+1)) > 3) then
-
res = i
-
exit
-
end if
-
else
-
if (list(i) > list(i+1) .or. abs(list(i) - list(i+1)) > 3) then
-
res = i
-
exit
-
end if
end if
-
end do
-
end subroutine has_fail_value
end module day2_utils
program day_02_part_2
-
use day2_utils
-
implicit none
-
logical :: is_decrement
-
integer :: io, i,x,y, fail, spaces, res
-
integer, dimension(:), allocatable :: list, list2
-
character(len=100) :: line
-
open(newunit=io, file='./day_02_input.txt', status='old', action='read')
-
res = 0
-
do i = 1, 1000
-
read(io, '(a)') line ! reading the line
-
spaces = 1 ! reset space count
-
do x = 1, len(trim(line))
-
! counting spaces to see how big of an array we need to allocate
-
if(iachar(line(x:x))== 32 ) then
-
spaces = spaces+1
-
end if
-
end do
-
-
allocate(list(spaces))
-
read(line, *) list !reading the ints into an array
-
fail = -1
-
call has_fail_value(list, fail)
-
if (fail > 0) then
-
y = 1
-
allocate(list2(spaces -1))
-
do x = 1, size(list)
-
if(x /= fail) then
-
list2(y) = list(x)
-
y = y+1
-
end if
end do
-
fail = -1
-
call has_fail_value(list2, fail)
-
if(fail > 0) then
-
print*, list2(:)
-
end if
-
deallocate(list2)
-
end if
-
if (fail == -1) then
-
res = res + 1
-
endif
-
deallocate(list)
-
end do
-
print*, res
end program day_02_part_2
···
+
module day2_utils
+
implicit none
+
contains
+
subroutine is_safe(list, res)
+
implicit none
+
integer, allocatable, intent(in) :: list(:)
+
logical, intent(out):: res
+
integer :: i, diff
+
logical is_decrement
+
res = .true.
+
is_decrement = .false.
+
do i = 1, size(list) - 1
+
if(i == 1 .and. list(i) > list(i+1)) then
+
is_decrement = .true.
+
end if
+
diff = abs(list(i) - list(i+1))
+
if(is_decrement) then
+
if (list(i) < list(i+1) .or. diff > 3 .or. diff < 1) then
+
res = .false.
+
exit
+
end if
+
else
+
if (list(i) > list(i+1) .or. diff > 3 .or. diff < 1) then
+
res = .false.
+
exit
+
end if
+
end if
+
end do
+
end subroutine is_safe
+
subroutine safe_with_dampener(list, res)
+
implicit none
+
integer, allocatable, intent(in) :: list(:)
+
integer, allocatable :: work(:)
+
logical, intent(out):: res
+
integer :: i, x, idx
+
res = .true.
+
call is_safe(list, res)
+
if(.not. res) then
+
allocate(work(size(list)-1))
+
do i = 1, size(list)
+
idx = 1
+
do x = 1, size(list)
+
if (x /= i) then
+
work(idx) = list(x)
+
idx = idx + 1
+
end if
+
end do
+
res = .true.
+
call is_safe(work, res)
+
if(res) then
+
exit
+
end if
+
end do
end if
+
end subroutine safe_with_dampener
end module day2_utils
program day_02_part_2
+
use day2_utils
+
implicit none
+
logical :: is_decrement, safe
+
integer :: io, i, x, spaces, res
+
integer, dimension(:), allocatable :: list
+
character(len=100) :: line
+
open(newunit=io, file='./day_02_input.txt', status='old', action='read')
+
res = 0
+
do i = 1, 1000
+
read(io, '(a)') line ! reading the line
+
spaces = 1 ! reset space count
+
do x = 1, len(trim(line))
+
! counting spaces to see how big of an array we need to allocate
+
if(iachar(line(x:x))== 32 ) then
+
spaces = spaces+1
+
end if
end do
+
allocate(list(spaces))
+
read(line, *) list !reading the ints into an array
+
safe = .true. !set fail to false by default
+
call safe_with_dampener(list, safe) ! check if the array has a fail idx
+
if (safe) then
+
res = res + 1
+
endif
+
deallocate(list)
+
end do
+
print*, res
end program day_02_part_2