My yearly advent-of-code solutions

Compare changes

Choose any two refs to compare.

+2
.gitignore
···
+
input.txt
+
input_test.txt
+57
2024/day_07.f90
···
+
module day_07_utils
+
use iso_fortran_env, only: int64
+
implicit none
+
contains
+
recursive function test_values(arr, target, next_idx, current_value) result(pass)
+
implicit none
+
integer(kind=int64), intent(in) :: target, current_value, arr(:)
+
integer, intent(in) :: next_idx
+
logical :: pass
+
if(next_idx > size(arr)) then
+
pass = current_value == target
+
return
+
end if
+
pass = test_values(arr, target, next_idx + 1, current_value + arr(next_idx)) .or. &
+
test_values(arr, target, next_idx + 1, current_value * arr(next_idx))
+
end function test_values
+
logical function is_calibrated(arr, target)
+
implicit none
+
integer(kind=int64), intent(in) :: target, arr(:)
+
is_calibrated = test_values(arr, target, 2, arr(1))
+
end function is_calibrated
+
end module day_07_utils
+
program day_07
+
use iso_fortran_env, only: int64
+
use day_07_utils
+
implicit none
+
integer(kind=int64) :: test_number, res
+
integer(kind=int64), allocatable:: work(:)
+
integer :: io, ios, idx, i, ct
+
character(len=200) :: line, work_line
+
logical :: pass
+
res = 0
+
open(newunit=io, file='./day_07_input.txt', status='old', action='read')
+
do
+
read(io, '(a)', iostat=ios) line
+
if (ios /= 0) exit
+
idx = index(line, ':')
+
if (idx > 0) then
+
read(line(1:idx-1), *) test_number
+
ct = 0
+
work_line = trim(line(idx+1:len(trim(line))))
+
do i = 1 , len(trim(work_line))
+
if(work_line(i:i) == ' ') then
+
ct = ct + 1
+
end if
+
end do
+
allocate(work(ct))
+
read(work_line, *) work(:)
+
end if
+
pass = is_calibrated(work, test_number)
+
if(pass) then
+
res = res + test_number
+
end if
+
deallocate(work)
+
end do
+
print*, "Result: ", res
+
end program day_07
+68
2024/day_07_part_2.f90
···
+
module day_07_part_2_utils
+
use iso_fortran_env, only: int64
+
implicit none
+
contains
+
recursive function test_values(arr, target, next_idx, current_value) result(pass)
+
implicit none
+
integer(kind=int64), intent(in) :: target, current_value, arr(:)
+
integer, intent(in) :: next_idx
+
character(len=20) :: str_1, str_2, concat_str
+
integer(kind=int64) :: concat_value
+
logical :: pass
+
+
if(next_idx > size(arr)) then
+
pass = current_value == target
+
return
+
end if
+
+
write(str_1, '(I0)') current_value
+
write(str_2, '(I0)') arr(next_idx)
+
concat_str = trim(str_1) // trim(str_2)
+
read(concat_str, '(I20)') concat_value
+
+
pass = test_values(arr, target, next_idx + 1, current_value + arr(next_idx)) .or. &
+
test_values(arr, target, next_idx + 1, current_value * arr(next_idx)) .or. &
+
test_values(arr, target, next_idx + 1, concat_value)
+
end function test_values
+
logical function is_calibrated(arr, target)
+
implicit none
+
integer(kind=int64), intent(in) :: target, arr(:)
+
+
is_calibrated = test_values(arr, target, 2, arr(1))
+
end function is_calibrated
+
end module day_07_part_2_utils
+
program day_07_part_2
+
use iso_fortran_env, only: int64
+
use day_07_part_2_utils
+
implicit none
+
integer(kind=int64) :: test_number, res
+
integer(kind=int64), allocatable:: work(:)
+
integer :: io, ios, idx, i, ct
+
character(len=200) :: line, work_line
+
logical :: pass
+
res = 0
+
open(newunit=io, file='./day_07_input.txt', status='old', action='read')
+
do
+
read(io, '(a)', iostat=ios) line
+
if (ios /= 0) exit
+
idx = index(line, ':')
+
if (idx > 0) then
+
read(line(1:idx-1), *) test_number
+
ct = 0
+
work_line = trim(line(idx+1:len(trim(line))))
+
do i = 1 , len(trim(work_line))
+
if(work_line(i:i) == ' ') then
+
ct = ct + 1
+
end if
+
end do
+
allocate(work(ct))
+
read(work_line, *) work(:)
+
end if
+
pass = is_calibrated(work, test_number)
+
if(pass) then
+
res = res + test_number
+
end if
+
deallocate(work)
+
end do
+
print*, "Result: ", res
+
end program day_07_part_2
+142
2024/day_08.f90
···
+
module day_08_utils
+
implicit none
+
type node
+
character :: c
+
integer, allocatable :: x(:), y(:)
+
end type node
+
contains
+
subroutine append_to_integer_array(arr, val)
+
implicit none
+
integer, allocatable, intent(inout) :: arr(:)
+
integer, intent(in) :: val
+
integer, allocatable :: temp(:)
+
if(.not. allocated(arr)) then
+
ERROR STOP 'Array not allocated'
+
end if
+
allocate(temp(size(arr) + 1))
+
temp(1:size(arr)) = arr
+
temp(size(arr) + 1) = val
+
call move_alloc(temp, arr)
+
end subroutine append_to_integer_array
+
+
subroutine add_node(nodes, c, x, y)
+
type(node), allocatable, intent(inout) :: nodes(:)
+
type(node), allocatable :: temp(:)
+
character, intent(in) :: c
+
integer, intent(in) :: x, y
+
integer :: i
+
do i = 1, size(nodes)
+
if (nodes(i)%c == c) then
+
if(.not. allocated(nodes(i)%x)) then
+
allocate(nodes(i)%x(1))
+
nodes(i)%x(1) = x
+
else
+
call append_to_integer_array(nodes(i)%x, x)
+
end if
+
if(.not. allocated(nodes(i)%y)) then
+
allocate(nodes(i)%y(1))
+
nodes(i)%y(1) = y
+
else
+
call append_to_integer_array(nodes(i)%y, y)
+
end if
+
return
+
end if
+
end do
+
allocate(temp(size(nodes) + 1))
+
temp(1:size(nodes)) = nodes
+
allocate(temp(size(nodes) + 1)%x(1))
+
allocate(temp(size(nodes) + 1)%y(1))
+
temp(size(nodes) + 1)%c = c
+
temp(size(nodes) + 1)%x(1) = x
+
temp(size(nodes) + 1)%y(1) = y
+
call move_alloc(temp, nodes)
+
end subroutine add_node
+
end module day_08_utils
+
+
program day_08
+
use day_08_utils
+
implicit none
+
character(len=50) :: lines(50)
+
integer :: io, i, j, k, l, score, xdist, ydist
+
integer, allocatable :: anti_x(:), anti_y(:)
+
type(node), allocatable :: nodes(:)
+
logical :: found
+
+
open(newunit=io, file='day_08_input.txt', status='old', action='read')
+
read(io, '(A)') lines
+
score = 0
+
do i = 1, 50
+
do j = 1, 50
+
if(lines(i)(j:j) /= '.') then
+
if(.not. allocated(nodes)) then
+
allocate(nodes(1))
+
nodes(1)%c = lines(i)(j:j)
+
allocate(nodes(1)%x(1))
+
allocate(nodes(1)%y(1))
+
nodes(1)%x(1) = j
+
nodes(1)%y(1) = i
+
else
+
call add_node(nodes, lines(i)(j:j), j, i)
+
end if
+
end if
+
end do
+
end do
+
do i = 1, size(nodes)
+
do j = 1, size(nodes(i)%x)
+
do l = 1, size(nodes(i)%x)
+
if(nodes(i)%x(j) == nodes(i)%x(l) .and. nodes(i)%y(j) == nodes(i)%y(l)) cycle ! don't compare same values
+
xdist = nodes(i)%x(j) - nodes(i)%x(l)
+
ydist = nodes(i)%y(j) - nodes(i)%y(l)
+
if(nodes(i)%x(j) + xdist > 0 .and. nodes(i)%x(j) + xdist <= 50 .and. &
+
nodes(i)%y(j) + ydist > 0 .and. nodes(i)%y(j) + ydist <= 50) then
+
if(.not. allocated(anti_x)) then
+
allocate(anti_x(1))
+
anti_x(1) = nodes(i)%x(j) + xdist
+
allocate(anti_y(1))
+
anti_y(1) = nodes(i)%y(j) + ydist
+
score = score + 1
+
else
+
found = .false.
+
do k = 1, size(anti_x)
+
if(anti_x(k) == nodes(i)%x(j) + xdist .and. anti_y(k) == nodes(i)%y(j) + ydist) then
+
found = .true.
+
exit
+
end if
+
end do
+
if(.not. found) then
+
call append_to_integer_array(anti_x, nodes(i)%x(j) + xdist)
+
call append_to_integer_array(anti_y, nodes(i)%y(j) + ydist)
+
+
score = score + 1
+
end if
+
end if
+
end if
+
if(nodes(i)%x(l) - xdist > 0 .and. nodes(i)%x(l) - xdist <= 50 .and. &
+
nodes(i)%y(l) - ydist > 0 .and. nodes(i)%y(l) - ydist <= 50) then
+
if(.not. allocated(anti_x)) then
+
allocate(anti_x(1))
+
anti_x(1) = nodes(i)%x(l) - xdist
+
allocate(anti_y(1))
+
anti_y(1) = nodes(i)%y(l) - ydist
+
score = score + 1
+
else
+
found = .false.
+
do k = 1, size(anti_x)
+
if(anti_x(k) == nodes(i)%x(l) - xdist .and. anti_y(k) == nodes(i)%y(l) - ydist) then
+
found = .true.
+
exit
+
end if
+
end do
+
if(.not. found) then
+
call append_to_integer_array(anti_x, nodes(i)%x(l) - xdist)
+
call append_to_integer_array(anti_y, nodes(i)%y(l) - ydist)
+
+
score = score + 1
+
end if
+
end if
+
end if
+
end do
+
end do
+
end do
+
print*, "Total : ", score
+
end program day_08
+164
2024/day_08_part_2.f90
···
+
module day_08_utils
+
implicit none
+
type node
+
character :: c
+
integer, allocatable :: x(:), y(:)
+
end type node
+
contains
+
subroutine append_to_integer_array(arr, val)
+
implicit none
+
integer, allocatable, intent(inout) :: arr(:)
+
integer, intent(in) :: val
+
integer, allocatable :: temp(:)
+
if(.not. allocated(arr)) then
+
ERROR STOP 'Array not allocated'
+
end if
+
allocate(temp(size(arr) + 1))
+
temp(1:size(arr)) = arr
+
temp(size(arr) + 1) = val
+
call move_alloc(temp, arr)
+
end subroutine append_to_integer_array
+
+
subroutine add_node(nodes, c, x, y)
+
type(node), allocatable, intent(inout) :: nodes(:)
+
type(node), allocatable :: temp(:)
+
character, intent(in) :: c
+
integer, intent(in) :: x, y
+
integer :: i
+
do i = 1, size(nodes)
+
if (nodes(i)%c == c) then
+
if(.not. allocated(nodes(i)%x)) then
+
allocate(nodes(i)%x(1))
+
nodes(i)%x(1) = x
+
else
+
call append_to_integer_array(nodes(i)%x, x)
+
end if
+
if(.not. allocated(nodes(i)%y)) then
+
allocate(nodes(i)%y(1))
+
nodes(i)%y(1) = y
+
else
+
call append_to_integer_array(nodes(i)%y, y)
+
end if
+
return
+
end if
+
end do
+
allocate(temp(size(nodes) + 1))
+
temp(1:size(nodes)) = nodes
+
allocate(temp(size(nodes) + 1)%x(1))
+
allocate(temp(size(nodes) + 1)%y(1))
+
temp(size(nodes) + 1)%c = c
+
temp(size(nodes) + 1)%x(1) = x
+
temp(size(nodes) + 1)%y(1) = y
+
call move_alloc(temp, nodes)
+
end subroutine add_node
+
end module day_08_utils
+
+
program day_08
+
use day_08_utils
+
implicit none
+
character(len=50) :: lines(50)
+
integer :: io, i, j, k, l, score, xdist, ydist, next_x, next_y
+
integer, allocatable :: anti_x(:), anti_y(:)
+
type(node), allocatable :: nodes(:)
+
logical :: found
+
+
open(newunit=io, file='day_08_input.txt', status='old', action='read')
+
read(io, '(A)') lines
+
score = 0
+
do i = 1, 50
+
do j = 1, 50
+
if(lines(i)(j:j) /= '.') then
+
if(.not. allocated(nodes)) then
+
allocate(nodes(1))
+
nodes(1)%c = lines(i)(j:j)
+
allocate(nodes(1)%x(1))
+
allocate(nodes(1)%y(1))
+
nodes(1)%x(1) = j
+
nodes(1)%y(1) = i
+
else
+
call add_node(nodes, lines(i)(j:j), j, i)
+
end if
+
end if
+
end do
+
end do
+
do i = 1, size(nodes)
+
do j = 1, size(nodes(i)%x)
+
if(.not. allocated(anti_x)) then
+
allocate(anti_x(1))
+
anti_x(1) = nodes(i)%x(j)
+
allocate(anti_y(1))
+
anti_y(1) = nodes(i)%y(j)
+
score = score + 1
+
else
+
found = .false.
+
do k = 1, size(anti_x)
+
if(anti_x(k) == nodes(i)%x(j) .and. anti_y(k) == nodes(i)%y(j)) then
+
found = .true.
+
exit
+
end if
+
end do
+
if(.not. found) then
+
call append_to_integer_array(anti_x, nodes(i)%x(j))
+
call append_to_integer_array(anti_y, nodes(i)%y(j))
+
+
score = score + 1
+
end if
+
end if
+
do l = 1, size(nodes(i)%x)
+
if(nodes(i)%x(j) == nodes(i)%x(l) .and. nodes(i)%y(j) == nodes(i)%y(l)) cycle ! don't compare same values
+
xdist = nodes(i)%x(j) - nodes(i)%x(l)
+
ydist = nodes(i)%y(j) - nodes(i)%y(l)
+
next_x = nodes(i)%x(j) + xdist
+
next_y = nodes(i)%y(j) + ydist
+
do
+
if(next_x> 0 .and. next_x <= 50 .and. &
+
next_y > 0 .and. next_y <= 50) then
+
found = .false.
+
do k = 1, size(anti_x)
+
if(anti_x(k) == next_x .and. anti_y(k) == next_y) then
+
found = .true.
+
exit
+
end if
+
end do
+
if(.not. found) then
+
call append_to_integer_array(anti_x, next_x)
+
call append_to_integer_array(anti_y, next_y)
+
+
score = score + 1
+
end if
+
next_x = next_x + xdist
+
next_y = next_y + ydist
+
else
+
exit
+
end if
+
end do
+
next_x = nodes(i)%x(l) - xdist
+
next_y = nodes(i)%y(l) - ydist
+
do
+
if(next_x > 0 .and. next_x <= 50 .and. &
+
next_y > 0 .and. next_y <= 50) then
+
found = .false.
+
do k = 1, size(anti_x)
+
if(anti_x(k) == next_x .and. anti_y(k) == next_y) then
+
found = .true.
+
exit
+
end if
+
end do
+
if(.not. found) then
+
call append_to_integer_array(anti_x, next_x)
+
call append_to_integer_array(anti_y, next_y)
+
+
score = score + 1
+
end if
+
next_x = next_x - xdist
+
next_y = next_y - ydist
+
+
else
+
exit
+
end if
+
end do
+
end do
+
end do
+
end do
+
print*, "Total : ", score
+
end program day_08
+152
2024/day_09.f90
···
+
module day_09_utils
+
implicit none
+
contains
+
subroutine swap_to_first_positive_integer_from_end(arr, idx)
+
implicit none
+
integer, allocatable, intent(inout) :: arr(:)
+
integer, intent(in) :: idx
+
integer, allocatable :: temp(:)
+
integer :: i, res
+
do i = 0, size(arr) - 1
+
if(arr(size(arr) - i) > -1) then
+
arr(idx) = arr(size(arr) - i)
+
allocate(temp(size(arr) - (i +1)))
+
temp = arr(1:size(arr) - (i+1))
+
call move_alloc(temp, arr)
+
return
+
end if
+
end do
+
end subroutine swap_to_first_positive_integer_from_end
+
subroutine append_to_integer_array_times(arr, val, times)
+
implicit none
+
integer, allocatable, intent(inout) :: arr(:)
+
integer, intent(in) :: val, times
+
integer, allocatable :: temp(:)
+
if(.not. allocated(arr)) then
+
ERROR STOP 'Array not allocated'
+
end if
+
allocate(temp(size(arr) + times))
+
temp(1:size(arr)) = arr
+
temp(size(arr) + 1:size(temp)) = val
+
call move_alloc(temp, arr)
+
end subroutine append_to_integer_array_times
+
end module day_09_utils
+
program day_09
+
use iso_fortran_env, only: int64
+
use day_09_utils
+
implicit none
+
integer :: io, ios, i, j, block_n, ct, block_start, block_end, space_start, space_end
+
integer(kind=int64) :: res
+
character(len=1) :: c
+
integer, allocatable :: system(:), work(:), done(:)
+
logical :: is_space, space_block_start
+
+
open(newunit=io, file='./day_09_input.txt', status='old', action='read', access='stream')
+
is_space = .false.
+
block_n = 0
+
do
+
read(io, iostat=ios) c
+
if (ios /= 0) exit
+
read(c, *, iostat=ios) i
+
if(ios /= 0) exit
+
if (i == 0) then
+
is_space = .false.
+
cycle
+
end if
+
if (.not. allocated(system)) then
+
allocate(system(i))
+
system(1:i) = block_n
+
is_space = .true.
+
block_n = block_n + 1
+
else
+
if (is_space) then
+
call append_to_integer_array_times(system, -1, i)
+
is_space = .false.
+
else
+
call append_to_integer_array_times(system, block_n, i)
+
block_n = block_n + 1
+
is_space = .true.
+
end if
+
end if
+
end do
+
allocate(work(size(system)))
+
work = system
+
ct = count(work > -1)
+
outer: do
+
do i = 1, size(work)
+
if (i == ct) exit outer ! we are done
+
if(work(i) < 0) then
+
call swap_to_first_positive_integer_from_end(work, i)
+
exit
+
end if
+
end do
+
end do outer
+
res = 0
+
do i = 1, size(work)
+
if(work(i) > -1) then
+
res = res + ((i-1) * work(i))
+
else
+
end if
+
end do
+
print *, res
+
! start_part_2
+
res = 0
+
deallocate(work)
+
allocate(work(size(system)))
+
work = system
+
block_n = -1
+
block_start = -1
+
block_end = -1
+
do i = size(work), 1, -1
+
if(block_n == -1 .and. work(i) /= -1) then
+
! we are starting a block
+
block_end = i
+
block_n = work(i)
+
if(allocated(done) .and. count(done == block_n) > 0) then
+
block_n = -1
+
block_start = -1
+
block_end = -1
+
cycle
+
else if(.not. allocated(done)) then
+
allocate(done(1))
+
done(1) = block_n
+
else
+
call append_to_integer_array_times(done, block_n, 1)
+
end if
+
else if (block_n /= -1 .and. block_n /= work(i)) then
+
! we are ending the block
+
block_start = i
+
+
! lets try to move the block
+
space_block_start = .true.
+
do j = 1, size(work)
+
if (j > block_start) exit
+
if(space_block_start .and. work(j) == -1) then
+
space_start = j
+
space_block_start = .false.
+
else if (.not. space_block_start .and. work(j) /= -1) then
+
space_end = j
+
space_block_start = .true.
+
if(space_end - space_start >= block_end - block_start) then
+
work(space_start:space_start + (block_end - (block_start +1))) = block_n
+
work(block_start+1:block_end) = -1
+
exit
+
end if
+
space_end = -1
+
space_start = -1
+
end if
+
end do
+
block_n = work(i)
+
block_end = i
+
block_start = -1
+
end if
+
end do
+
do i = 1, size(work)
+
if(work(i) /= -1) then
+
res = res + ((i-1) * work(i))
+
end if
+
end do
+
print *, res
+
end program day_09
+
+
+51
2025/day_01.cbl
···
+
IDENTIFICATION DIVISION.
+
PROGRAM-ID. day_01.
+
AUTHOR. Trey Bastian.
+
ENVIRONMENT DIVISION.
+
INPUT-OUTPUT SECTION.
+
FILE-CONTROL.
+
SELECT input-file ASSIGN TO "./input.txt"
+
ORGANIZATION IS LINE SEQUENTIAL.
+
DATA DIVISION.
+
FILE SECTION.
+
FD input-file.
+
01 input-line.
+
02 direction PIC X.
+
02 move-text PIC XXX.
+
WORKING-STORAGE SECTION.
+
01 dial-position PIC 9(2) VALUE 50.
+
01 move-num PIC S9(3).
+
01 zero-count PIC 9(4) VALUE ZEROS.
+
01 eof PIC X.
+
88 eof-y VALUE "Y".
+
88 eof-n VALUE "N".
+
+
+
PROCEDURE DIVISION.
+
OPEN INPUT input-file.
+
SET eof-n to TRUE.
+
PERFORM UNTIL eof-y
+
READ input-file AT END
+
SET eof-y to TRUE
+
NOT AT END
+
MOVE FUNCTION NUMVAL(move-text) TO move-num
+
IF direction = "L"
+
COMPUTE move-num = 0 - move-num
+
END-IF
+
+
COMPUTE dial-position = FUNCTION MOD(dial-position +
+
move-num, 100)
+
+
if dial-position < 0
+
ADD 100 to dial-position
+
END-IF
+
+
if dial-position = 0
+
ADD 1 to zero-count
+
END-IF
+
END-READ
+
END-PERFORM.
+
CLOSE input-file.
+
DISPLAY zero-count.
+
STOP-RUN.
+
+67
2025/day_01_part2.cbl
···
+
IDENTIFICATION DIVISION.
+
PROGRAM-ID. day_01_part2.
+
AUTHOR. Trey Bastian.
+
ENVIRONMENT DIVISION.
+
INPUT-OUTPUT SECTION.
+
FILE-CONTROL.
+
SELECT input-file ASSIGN TO "./input.txt"
+
ORGANIZATION IS LINE SEQUENTIAL.
+
DATA DIVISION.
+
FILE SECTION.
+
FD input-file.
+
01 input-line.
+
02 direction PIC X.
+
02 move-text PIC XXX.
+
WORKING-STORAGE SECTION.
+
01 dial-position PIC 9(2) VALUE 50.
+
01 new-position PIC 9(2).
+
01 move-num PIC S9(3).
+
01 zero-count PIC 9(4) VALUE ZEROS.
+
01 eof PIC X.
+
88 eof-y VALUE "Y".
+
88 eof-n VALUE "N".
+
+
+
PROCEDURE DIVISION.
+
OPEN INPUT input-file.
+
SET eof-n to TRUE.
+
PERFORM UNTIL eof-y
+
READ input-file AT END
+
SET eof-y to TRUE
+
NOT AT END
+
MOVE FUNCTION NUMVAL(move-text) TO move-num
+
IF move-num > 99
+
COMPUTE zero-count = zero-count + (move-num / 100)
+
END-IF
+
+
IF direction = "L"
+
COMPUTE move-num = 0 - move-num
+
END-IF
+
+
COMPUTE new-position = FUNCTION MOD(dial-position +
+
move-num, 100)
+
+
if new-position < 0
+
ADD 100 to new-position
+
END-IF
+
+
EVALUATE new-position
+
WHEN 0
+
ADD 1 to zero-count
+
WHEN < dial-position AND direction = "R" AND
+
dial-position <> 0
+
ADD 1 to zero-count
+
WHEN > dial-position AND direction = "L" AND
+
dial-position <> 0
+
ADD 1 to zero-count
+
END-EVALUATE
+
+
+
MOVE new-position TO dial-position
+
+
END-READ
+
END-PERFORM.
+
CLOSE input-file.
+
DISPLAY zero-count.
+
STOP-RUN.
+
+76
2025/day_02.cbl
···
+
IDENTIFICATION DIVISION.
+
PROGRAM-ID. day_02.
+
AUTHOR. Trey Bastian.
+
ENVIRONMENT DIVISION.
+
INPUT-OUTPUT SECTION.
+
FILE-CONTROL.
+
SELECT input-file ASSIGN TO "./input.txt"
+
ORGANIZATION IS LINE SEQUENTIAL.
+
DATA DIVISION.
+
FILE SECTION.
+
FD input-file.
+
01 input-line PIC X(4096).
+
WORKING-STORAGE SECTION.
+
01 ptr PIC 9(4) Value 1.
+
01 len PIC 9(4).
+
01 left-val PIC 9(32).
+
01 right-val PIC 9(32).
+
01 grouping PIC X(65).
+
+
01 val-string PIC Z(32).
+
01 val-string-len PIC 9(2).
+
01 val-string-start-idx PIC 9(2).
+
01 val-string-half PIC 9(2).
+
01 result PIC 9(32) VALUE ZEROS.
+
+
01 eof PIC X.
+
88 eof-y VALUE "Y".
+
88 eof-n VALUE "N".
+
PROCEDURE DIVISION.
+
OPEN INPUT input-file.
+
SET eof-n to TRUE.
+
PERFORM UNTIL eof-y
+
READ input-file AT END
+
SET eof-y to TRUE
+
NOT AT END
+
INSPECT input-line TALLYING len FOR CHARACTERS BEFORE
+
SPACE
+
+
PERFORM UNTIL ptr > len
+
UNSTRING input-line DELIMITED BY "," INTO grouping WITH
+
POINTER ptr
+
END-UNSTRING
+
+
UNSTRING grouping DELIMITED BY "-" INTO left-val,
+
right-val
+
END-UNSTRING
+
+
PERFORM VARYING left-val FROM left-val BY 1 UNTIL
+
left-val > right-val
+
MOVE left-val TO val-string
+
+
COMPUTE val-string-len = FUNCTION LENGTH(FUNCTION
+
TRIM(val-string))
+
IF FUNCTION MOD(val-string-len, 2) = 0
+
+
COMPUTE val-string-start-idx =
+
(FUNCTION LENGTH(val-string) - val-string-len ) + 1
+
COMPUTE val-string-half = val-string-len / 2
+
+
IF val-string(val-string-start-idx:val-string-half)
+
= val-string(val-string-start-idx +
+
val-string-half:val-string-half)
+
+
ADD left-val TO result
+
END-IF
+
END-IF
+
END-PERFORM
+
+
END-PERFORM
+
+
END-READ
+
END-PERFORM.
+
CLOSE input-file.
+
DISPLAY result.
+
STOP-RUN.
+
+103
2025/day_02_part2.cbl
···
+
IDENTIFICATION DIVISION.
+
PROGRAM-ID. day_02_part2.
+
AUTHOR. Trey Bastian.
+
ENVIRONMENT DIVISION.
+
INPUT-OUTPUT SECTION.
+
FILE-CONTROL.
+
SELECT input-file ASSIGN TO "./input.txt"
+
ORGANIZATION IS LINE SEQUENTIAL.
+
DATA DIVISION.
+
FILE SECTION.
+
FD input-file.
+
01 input-line PIC X(4096).
+
WORKING-STORAGE SECTION.
+
01 ptr PIC 9(4) Value 1.
+
01 len PIC 9(4).
+
01 left-val PIC 9(32).
+
01 right-val PIC 9(32).
+
01 grouping PIC X(65).
+
+
01 val-string PIC Z(32).
+
01 val-string-len PIC 9(2).
+
01 val-string-start-idx PIC 9(2).
+
01 val-string-half PIC 9(2).
+
01 val-window PIC 9(2) VALUE 1.
+
01 c-idx PIC 9(2).
+
01 s-left PIC Z(16).
+
01 s-right PIC Z(16).
+
01 no-match PIC X VALUE "N".
+
01 result PIC 9(32) VALUE ZEROS.
+
+
01 eof PIC X.
+
88 eof-y VALUE "Y".
+
88 eof-n VALUE "N".
+
PROCEDURE DIVISION.
+
OPEN INPUT input-file.
+
SET eof-n to TRUE.
+
PERFORM UNTIL eof-y
+
READ input-file AT END
+
SET eof-y to TRUE
+
NOT AT END
+
INSPECT input-line TALLYING len FOR CHARACTERS BEFORE
+
SPACE
+
+
PERFORM UNTIL ptr > len
+
UNSTRING input-line DELIMITED BY "," INTO grouping WITH
+
POINTER ptr
+
END-UNSTRING
+
+
UNSTRING grouping DELIMITED BY "-" INTO left-val,
+
right-val
+
END-UNSTRING
+
+
PERFORM VARYING left-val FROM left-val BY 1 UNTIL
+
left-val > right-val
+
MOVE left-val TO val-string
+
+
COMPUTE val-string-len = FUNCTION LENGTH(FUNCTION
+
TRIM(val-string))
+
+
COMPUTE val-string-start-idx =
+
(FUNCTION LENGTH(val-string) - val-string-len ) + 1
+
+
COMPUTE val-string-half = val-string-len / 2
+
+
PERFORM VARYING val-window FROM 1 BY 1
+
UNTIL val-window > val-string-half
+
COMPUTE c-idx = val-string-start-idx + val-window
+
MOVE "N" to no-match
+
PERFORM VARYING c-idx
+
FROM c-idx
+
BY val-window
+
UNTIL c-idx
+
> FUNCTION LENGTH(val-string)
+
+
MOVE val-string(val-string-start-idx:val-window)
+
TO s-left
+
+
IF (c-idx + val-window
+
> FUNCTION LENGTH(val-string))
+
MOVE val-string(c-idx:) TO s-right
+
ELSE
+
MOVE val-string(c-idx:val-window) TO s-right
+
END-IF
+
+
IF NOT s-left = s-right
+
MOVE "Y" to no-match
+
EXIT PERFORM
+
END-IF
+
END-PERFORM
+
IF no-match = "N"
+
ADD left-val to result
+
EXIT PERFORM
+
END-IF
+
END-PERFORM
+
END-PERFORM
+
END-PERFORM
+
+
END-READ
+
END-PERFORM.
+
CLOSE input-file.
+
DISPLAY result.
+
STOP-RUN.
+
+63
2025/day_03.cbl
···
+
IDENTIFICATION DIVISION.
+
PROGRAM-ID. day_03.
+
AUTHOR. Trey Bastian.
+
ENVIRONMENT DIVISION.
+
INPUT-OUTPUT SECTION.
+
FILE-CONTROL.
+
SELECT input-file ASSIGN TO "./input.txt"
+
ORGANIZATION IS LINE SEQUENTIAL.
+
DATA DIVISION.
+
FILE SECTION.
+
FD input-file.
+
01 input-line PIC Z(4096).
+
WORKING-STORAGE SECTION.
+
01 idx PIC 9(4).
+
01 idx-2 PIC 9(4).
+
01 len PIC 9(4).
+
+
01 maxim PIC 9 VALUE 0.
+
01 digit PIC 9 VALUE 0.
+
+
01 joltage PIC XX.
+
01 result PIC 9(10) VALUE 0.
+
+
+
01 eof PIC X.
+
88 eof-y VALUE "Y".
+
88 eof-n VALUE "N".
+
+
PROCEDURE DIVISION.
+
OPEN INPUT input-file.
+
SET eof-n to TRUE.
+
PERFORM UNTIL eof-y
+
READ input-file AT END
+
SET eof-y to TRUE
+
NOT AT END
+
MOVE FUNCTION LENGTH(FUNCTION TRIM(input-line)) TO len
+
MOVE 0 TO maxim
+
*first pass leave something on the right
+
PERFORM VARYING idx FROM 1 UNTIL idx > len - 1
+
MOVE FUNCTION NUMVAL(input-line(idx:1)) TO digit
+
IF maxim < digit
+
MOVE digit TO maxim
+
MOVE idx TO idx-2
+
END-IF
+
END-PERFORM
+
* need the next index
+
MOVE maxim TO joltage(1:1)
+
MOVE 0 TO maxim
+
ADD 1 TO idx-2
+
PERFORM VARYING idx-2 FROM idx-2 UNTIL idx-2 > len
+
MOVE FUNCTION NUMVAL(input-line(idx-2:1)) TO digit
+
IF maxim < digit
+
MOVE digit TO maxim
+
END-IF
+
END-PERFORM
+
MOVE maxim TO joltage(2:1)
+
ADD FUNCTION NUMVAL(joltage) TO result
+
END-READ
+
END-PERFORM.
+
CLOSE input-file.
+
DISPLAY result.
+
STOP-RUN.
+
+64
2025/day_03_part2.cbl
···
+
IDENTIFICATION DIVISION.
+
PROGRAM-ID. day_03_part2.
+
AUTHOR. Trey Bastian.
+
ENVIRONMENT DIVISION.
+
INPUT-OUTPUT SECTION.
+
FILE-CONTROL.
+
SELECT input-file ASSIGN TO "./input.txt"
+
ORGANIZATION IS LINE SEQUENTIAL.
+
DATA DIVISION.
+
FILE SECTION.
+
FD input-file.
+
01 input-line PIC Z(4096).
+
WORKING-STORAGE SECTION.
+
01 idx PIC 9(4) VALUE 1.
+
01 idx-2 PIC 9(4).
+
01 len PIC 9(4).
+
+
01 maxim PIC 9 VALUE 0.
+
01 digit PIC 9 VALUE 0.
+
01 remaining PIC 99 VALUE 12.
+
01 rem-idx PIC 99 VALUE 1.
+
+
01 joltage PIC X(12).
+
01 result PIC 9(32) VALUE 0.
+
+
+
01 eof PIC X.
+
88 eof-y VALUE "Y".
+
88 eof-n VALUE "N".
+
+
PROCEDURE DIVISION.
+
OPEN INPUT input-file.
+
SET eof-n to TRUE.
+
PERFORM UNTIL eof-y
+
READ input-file AT END
+
SET eof-y to TRUE
+
NOT AT END
+
MOVE FUNCTION LENGTH(FUNCTION TRIM(input-line)) TO len
+
MOVE 1 TO idx
+
MOVE 12 TO remaining
+
MOVE 1 TO rem-idx
+
PERFORM UNTIL remaining < 1
+
MOVE 0 TO maxim
+
PERFORM VARYING idx FROM idx UNTIL idx >
+
(len - remaining + 1)
+
MOVE FUNCTION NUMVAL(input-line(idx:1)) to digit
+
IF maxim < digit
+
MOVE digit TO maxim
+
MOVE idx TO idx-2
+
END-IF
+
END-PERFORM
+
MOVE maxim TO joltage(rem-idx:1)
+
ADD 1 TO rem-idx
+
SUBTRACT 1 FROM remaining
+
MOVE idx-2 TO idx
+
ADD 1 TO idx
+
END-PERFORM
+
ADD FUNCTION NUMVAL(joltage) TO result
+
END-READ
+
END-PERFORM.
+
CLOSE input-file.
+
DISPLAY result.
+
STOP-RUN.
+
+5 -2
README.md
···
# Advent of Code Repo
This repository contains my solutions to the Advent of Code challenges.
-
I stream all my solutions live on Twitch at [twitch.tv/treybastian](https://twitch.tv/treybastian).
+
## 2025 - COBOL
+
You'll need to install GNUCobol to run these solutions.
+
+
On MacOS you can install it with Homebrew: `brew install gnucobol`
## 2024 - Fortran
You'll need GNUFortran to run these solutions.
-
On MacOS, you can install it with Homebrew with `brew install gcc`.
+
On MacOS, you can install it with Homebrew: `brew install gcc`.