commit 6e1c74890e2ea7d8033c1e9494f1186ea8101022
parent ceba7e7870ce19112262f75caae9ae9437a8c39f
Author: Decay <decay@todayiwilllaunchmyinfantsonintoorbit.com>
Date: Wed, 7 Dec 2022 16:17:05 -0800
Oay 8 (Fortran 2008)
Diffstat:
A | 7/7.f08 | | | 263 | +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ |
1 file changed, 263 insertions(+), 0 deletions(-)
diff --git a/7/7.f08 b/7/7.f08
@@ -0,0 +1,263 @@
+! seven.f08 - Solution to day seven of AOC2022 in modern Fortran
+
+program seven
+ ! We're just going to use the same struct for directories and files and toggle
+ ! behavior based on file_size, which we declare to be -1 for directory nodes
+ type tree_node
+ type(tree_node), pointer :: parent => null() ! Tree parent
+ type(tree_node), pointer :: first_child => null() ! Children are structured as a linked list
+ type(tree_node), pointer :: next => null() ! Next sibling
+ character(len=:), allocatable :: name
+ integer :: file_size
+ end type tree_node
+
+ ! Variables
+ integer :: ios, n, pos, size, threshold
+ character(len=200) :: command, name
+ type(tree_node), pointer :: root, curr_node
+
+ root => null()
+
+ ! Initailize the root of the directory tree
+ call create_and_attach_dir_node(null(), '/', root)
+ curr_node => root
+
+ ! Open our input file for reading
+ open (unit = 9, file = 'input', status = 'old', access = 'stream', form = 'formatted', iostat = ios)
+
+ ! Loop over the lines in the input file and parse
+ n = 1
+ pos = 0
+ do
+ if (pos > 0) then
+ read (9, '(A)', iostat = ios, pos = pos) command
+ pos = 0
+ else
+ read (9, '(A)', iostat = ios) command
+ end if
+ if (ios /= 0) exit
+ if (command(1:2) == '$ ') then
+ call shell_command(9, command(3:len_trim(command)), curr_node, pos)
+ else
+ print *, 'Error, encountered a non-command string unexpectedly!'
+ error stop
+ end if
+ n = n + 1
+ end do
+
+ ! Close input file
+ close (9)
+
+ size = dir_size_dirs_under_100_000(root)
+ write (*,"(A,I8)") "Size of all dirs under 100000 bytes is ", size
+ size = 0
+ threshold = 30000000 - (70000000 - dir_size(root))
+ call smallest_dir_over_threshold(root, threshold, name, size)
+ if (size > 0) then
+ write (*,"(A,I7,A,A,A,I7,A)") "Smallest dir over threshold of ", threshold, " bytes is ", trim(name) , " (size ", size, ")"
+ else
+ print *, "Got nothing??"
+ end if
+
+contains
+ recursive subroutine smallest_dir_over_threshold(dir_node, threshold, name, size)
+ type(tree_node), intent(in) :: dir_node
+ integer, intent(in) :: threshold
+ character(len=*), intent(inout) :: name
+ integer, intent(inout) :: size
+
+ type(tree_node), pointer :: curr_node
+ character(len=:), allocatable :: temp_name
+ integer :: branch_size
+
+ ! Walk through child nodes looking for the smallest dir size over 30 million bytes
+ curr_node => dir_node%first_child
+ do
+ if (associated(curr_node) .eqv. .false.) exit
+ if (curr_node%file_size == -1) then
+ ! Recurse into child dirs
+ branch_size = dir_size(curr_node)
+ if (branch_size >= threshold) then
+ if (size == 0) then
+ size = branch_size
+ name = curr_node%name
+ else
+ if (branch_size < size) then
+ size = branch_size
+ name = curr_node%name
+ end if
+ end if
+ end if
+ call smallest_dir_over_threshold(curr_node, threshold, name, size)
+ end if
+ curr_node => curr_node%next
+ end do
+ end subroutine smallest_dir_over_threshold
+
+ recursive function dir_size_dirs_under_100_000(dir_node) result(size)
+ type(tree_node), intent(in) :: dir_node
+ integer :: size, branch_size
+ type(tree_node), pointer :: curr_node
+ character(len=:), allocatable :: name
+
+ ! Walk through child nodes accumulating file sizes
+ size = 0
+ branch_size = 0
+ curr_node => dir_node%first_child
+ do
+ if (associated(curr_node) .eqv. .false.) exit
+ if (curr_node%file_size == -1) then
+ ! Recurse into child dirs
+ branch_size = dir_size(curr_node)
+ if (branch_size <= 100000) size = size + branch_size
+ size = size + dir_size_dirs_under_100_000(curr_node)
+ end if
+ curr_node => curr_node%next
+ end do
+ end function dir_size_dirs_under_100_000
+
+ recursive function dir_size(dir_node) result(size)
+ type(tree_node), intent(in) :: dir_node
+ integer :: size
+ type(tree_node), pointer :: curr_node
+
+ ! Walk through child nodes accumulating file sizes
+ size = 0
+ curr_node => dir_node%first_child
+ do
+ if (associated(curr_node) .eqv. .false.) exit
+ if (curr_node%file_size == -1) then
+ ! Recurse into child dirs
+ size = size + dir_size(curr_node)
+ else
+ size = size + curr_node%file_size
+ end if
+ curr_node => curr_node%next
+ end do
+ end function dir_size
+
+ subroutine attach_child(parent, child)
+ type(tree_node), pointer, intent(in) :: parent
+ type(tree_node), pointer, intent(in) :: child
+ type(tree_node), pointer :: siblings
+
+ if (associated(parent) .eqv. .true.) then
+ if (associated(parent%first_child) .eqv. .true.) then
+ siblings => parent%first_child
+ do
+ if (associated(siblings%next)) then
+ siblings => siblings%next
+ else
+ siblings%next => child
+ exit
+ end if
+ end do
+ else
+ parent%first_child => child
+ end if
+ end if
+ end subroutine attach_child
+
+ subroutine create_and_attach_dir_node(parent, dir_name, node)
+ type(tree_node), pointer, intent(in) :: parent
+ character(len=*), intent(in) :: dir_name
+ type(tree_node), pointer, intent(out) :: node
+
+ allocate(node)
+ node%parent => parent
+ node%name = dir_name
+ node%file_size = -1
+ call attach_child(parent, node)
+ end subroutine create_and_attach_dir_node
+
+ subroutine create_and_attach_file_node(parent, file_name, file_size)
+ type(tree_node), pointer, intent(in) :: parent
+ character(len=*), intent(in) :: file_name
+ integer, intent(in) :: file_size
+ type(tree_node), pointer :: node
+
+ allocate(node)
+ node%parent => parent
+ node%name = file_name
+ node%file_size = file_size
+ call attach_child(parent, node)
+ end subroutine create_and_attach_file_node
+
+ subroutine change_directory(curr_node, path)
+ type(tree_node), pointer, intent(inout) :: curr_node
+ character(len=*), intent(in) :: path
+ type(tree_node), pointer :: maybe_node
+
+ if (path == '..') then
+ ! Up one dir if we're not already at the root
+ if (associated(curr_node%parent) .eqv. .true.) curr_node => curr_node%parent
+ else if (path == '/') then
+ ! All the way up
+ do
+ if (associated(curr_node%parent) .eqv. .false.) exit ! At the root
+ curr_node => curr_node%parent
+ end do
+ else
+ ! See if such a directory exists
+ maybe_node => curr_node%first_child
+ if (associated(maybe_node) .eqv. .true.) then
+ do
+ if (maybe_node%name == path) then
+ ! Found it
+ curr_node => maybe_node
+ exit
+ else if (associated(maybe_node%next) .eqv. .true.) then
+ maybe_node => maybe_node%next
+ else
+ print *, "No such directory as " // path
+ end if
+ end do
+ else
+ print *, "Current directory has no children"
+ end if
+ end if
+ end subroutine change_directory
+
+ subroutine shell_command(unit, command, curr_node, file_pos)
+ integer, intent(in) :: unit
+ character(len=*), intent(in) :: command
+ type(tree_node), pointer, intent(inout) :: curr_node
+ integer, intent(out) :: file_pos
+ character(len=8) :: path
+
+ character(len=200) :: input
+ integer :: idx, ios, file_size
+ type(tree_node), pointer :: new_node
+
+ file_pos = 0
+ idx = scan(command, " ") ! Find first space to determine the length of the base command
+ if (idx == 0) idx = len_trim(command) ! Atomic command with no parameters
+ if (command(1:idx) == 'cd ') then
+ ! Tree navigation
+ path = command(idx + 1:len_trim(command))
+ call change_directory(curr_node, path)
+ else if (command(1:idx) == 'ls') then
+ ! Collect the file info from the following lines
+ do
+ inquire (unit = unit, pos = file_pos) ! Save the file position before the next read
+ read (9, '(A)', iostat = ios) input
+ if (ios /= 0) then
+ file_pos = 0 ! No point in trying to backtrack
+ exit
+ end if
+ if (input(1:2) == '$ ') exit ! Read past the dir listing, return with the last file pos
+ idx = scan(input, " ") ! Find first space to split the size and type from the filename
+ if (input(1:idx - 1) == 'dir') then
+ call create_and_attach_dir_node(curr_node, input(idx+1:len_trim(input)), new_node)
+ else
+ read (input(1:idx - 1), *) file_size
+ call create_and_attach_file_node(curr_node, input(idx+1:len_trim(input)), file_size)
+ end if
+ end do
+ else
+ print *, "Error, encountered unknown command!"
+ error stop
+ end if
+ end subroutine shell_command
+
+end program seven