advent2022

Advent of Code 2022 Solutions
git clone https://todayiwilllaunchmyinfantsonintoorbit.com/advent2022.git
Log | Files | Refs

7.f08 (8998B)


      1 ! seven.f08 - Solution to day seven of AOC2022 in modern Fortran
      2 
      3 program seven
      4   ! We're just going to use the same struct for directories and files and toggle
      5   ! behavior based on file_size, which we declare to be -1 for directory nodes
      6   type tree_node
      7      type(tree_node), pointer :: parent => null() ! Tree parent
      8      type(tree_node), pointer :: first_child => null() ! Children are structured as a linked list
      9      type(tree_node), pointer :: next => null() ! Next sibling
     10      character(len=:), allocatable :: name
     11      integer :: file_size
     12   end type tree_node
     13 
     14   ! Variables
     15   integer :: ios, n, pos, size, threshold
     16   character(len=200) :: command, name
     17   type(tree_node), pointer :: root, curr_node
     18 
     19   root => null()
     20 
     21   ! Initailize the root of the directory tree
     22   call create_and_attach_dir_node(null(), '/', root)
     23   curr_node => root
     24   
     25   ! Open our input file for reading
     26   open (unit = 9, file = 'input', status = 'old', access = 'stream', form = 'formatted', iostat = ios)
     27 
     28   ! Loop over the lines in the input file and parse
     29   n = 1
     30   pos = 0
     31   do
     32      if (pos > 0) then
     33         read (9, '(A)', iostat = ios, pos = pos) command
     34         pos = 0
     35      else
     36         read (9, '(A)', iostat = ios) command
     37      end if
     38      if (ios /= 0) exit
     39      if (command(1:2) == '$ ') then
     40         call shell_command(9, command(3:len_trim(command)), curr_node, pos)
     41      else
     42         print *, 'Error, encountered a non-command string unexpectedly!'
     43         error stop
     44      end if
     45      n = n + 1
     46   end do
     47 
     48   ! Close input file
     49   close (9)
     50 
     51   size = dir_size_dirs_under_100_000(root)
     52   write (*,"(A,I8)") "Size of all dirs under 100000 bytes is ", size
     53   size = 0
     54   threshold = 30000000 - (70000000 - dir_size(root))
     55   call smallest_dir_over_threshold(root, threshold, name, size)
     56   if (size > 0) then
     57      write (*,"(A,I7,A,A,A,I7,A)") "Smallest dir over threshold of ", threshold,  " bytes is ", trim(name) , " (size ", size, ")"
     58   else
     59      print *, "Got nothing??"
     60   end if
     61 
     62 contains
     63   recursive subroutine smallest_dir_over_threshold(dir_node, threshold, name, size)
     64     type(tree_node), intent(in) :: dir_node
     65     integer, intent(in) :: threshold
     66     character(len=*), intent(inout) :: name
     67     integer, intent(inout) :: size
     68 
     69     type(tree_node), pointer :: curr_node
     70     character(len=:), allocatable :: temp_name
     71     integer :: branch_size
     72 
     73     ! Walk through child nodes looking for the smallest dir size over 30 million bytes
     74     curr_node => dir_node%first_child
     75     do
     76        if (associated(curr_node) .eqv. .false.) exit
     77        if (curr_node%file_size == -1) then
     78           ! Recurse into child dirs
     79           branch_size = dir_size(curr_node)
     80           if (branch_size >= threshold) then
     81              if (size == 0) then
     82                 size = branch_size
     83                 name = curr_node%name
     84              else
     85                 if (branch_size < size) then
     86                    size = branch_size
     87                    name = curr_node%name
     88                 end if
     89              end if
     90           end if
     91           call smallest_dir_over_threshold(curr_node, threshold, name, size)
     92        end if
     93        curr_node => curr_node%next
     94     end do
     95   end subroutine smallest_dir_over_threshold
     96   
     97   recursive function dir_size_dirs_under_100_000(dir_node) result(size)
     98     type(tree_node), intent(in) :: dir_node
     99     integer :: size, branch_size
    100     type(tree_node), pointer :: curr_node
    101     character(len=:), allocatable :: name
    102 
    103     ! Walk through child nodes accumulating file sizes
    104     size = 0
    105     branch_size = 0
    106     curr_node => dir_node%first_child
    107     do
    108        if (associated(curr_node) .eqv. .false.) exit
    109        if (curr_node%file_size == -1) then
    110           ! Recurse into child dirs
    111           branch_size = dir_size(curr_node)
    112           if (branch_size <= 100000) size = size + branch_size
    113           size = size + dir_size_dirs_under_100_000(curr_node)
    114        end if
    115        curr_node => curr_node%next
    116     end do
    117   end function dir_size_dirs_under_100_000
    118 
    119   recursive function dir_size(dir_node) result(size)
    120     type(tree_node), intent(in) :: dir_node
    121     integer :: size
    122     type(tree_node), pointer :: curr_node
    123 
    124     ! Walk through child nodes accumulating file sizes
    125     size = 0
    126     curr_node => dir_node%first_child
    127     do
    128        if (associated(curr_node) .eqv. .false.) exit
    129        if (curr_node%file_size == -1) then
    130           ! Recurse into child dirs
    131           size = size + dir_size(curr_node)
    132        else
    133           size = size + curr_node%file_size
    134        end if
    135        curr_node => curr_node%next
    136     end do
    137   end function dir_size
    138 
    139   subroutine attach_child(parent, child)
    140     type(tree_node), pointer, intent(in) :: parent
    141     type(tree_node), pointer, intent(in) :: child
    142     type(tree_node), pointer :: siblings
    143 
    144     if (associated(parent) .eqv. .true.) then
    145        if (associated(parent%first_child) .eqv. .true.) then
    146           siblings => parent%first_child
    147           do
    148              if (associated(siblings%next)) then
    149                 siblings => siblings%next
    150              else
    151                 siblings%next => child
    152                 exit
    153              end if
    154           end do
    155        else
    156           parent%first_child => child
    157        end if
    158     end if
    159   end subroutine attach_child
    160 
    161   subroutine create_and_attach_dir_node(parent, dir_name, node)
    162     type(tree_node), pointer, intent(in) :: parent
    163     character(len=*), intent(in) :: dir_name
    164     type(tree_node), pointer, intent(out) :: node
    165 
    166     allocate(node)
    167     node%parent => parent
    168     node%name = dir_name
    169     node%file_size = -1
    170     call attach_child(parent, node)
    171   end subroutine create_and_attach_dir_node
    172 
    173   subroutine create_and_attach_file_node(parent, file_name, file_size)
    174     type(tree_node), pointer, intent(in) :: parent
    175     character(len=*), intent(in) :: file_name
    176     integer, intent(in) :: file_size
    177     type(tree_node), pointer :: node
    178 
    179     allocate(node)
    180     node%parent => parent
    181     node%name = file_name
    182     node%file_size = file_size
    183     call attach_child(parent, node)
    184   end subroutine create_and_attach_file_node
    185 
    186   subroutine change_directory(curr_node, path)
    187     type(tree_node), pointer, intent(inout) :: curr_node
    188     character(len=*), intent(in) :: path
    189     type(tree_node), pointer :: maybe_node
    190 
    191     if (path == '..') then
    192        ! Up one dir if we're not already at the root
    193        if (associated(curr_node%parent) .eqv. .true.) curr_node => curr_node%parent
    194     else if (path == '/') then
    195        ! All the way up
    196        do
    197           if (associated(curr_node%parent) .eqv. .false.) exit ! At the root
    198           curr_node => curr_node%parent
    199        end do
    200     else
    201        ! See if such a directory exists
    202        maybe_node => curr_node%first_child
    203        if (associated(maybe_node) .eqv. .true.) then
    204           do          
    205              if (maybe_node%name == path) then
    206                 ! Found it
    207                 curr_node => maybe_node
    208                 exit
    209              else if (associated(maybe_node%next) .eqv. .true.) then
    210                 maybe_node => maybe_node%next
    211              else
    212                 print *, "No such directory as " // path
    213              end if
    214           end do
    215        else
    216           print *, "Current directory has no children"
    217        end if
    218     end if
    219   end subroutine change_directory
    220 
    221   subroutine shell_command(unit, command, curr_node, file_pos)
    222     integer, intent(in) :: unit
    223     character(len=*), intent(in) :: command
    224     type(tree_node), pointer, intent(inout) :: curr_node
    225     integer, intent(out) :: file_pos
    226     character(len=8) :: path
    227 
    228     character(len=200) :: input
    229     integer :: idx, ios, file_size
    230     type(tree_node), pointer :: new_node
    231 
    232     file_pos = 0
    233     idx = scan(command, " ") ! Find first space to determine the length of the base command
    234     if (idx == 0) idx = len_trim(command) ! Atomic command with no parameters
    235     if (command(1:idx) == 'cd ') then
    236        ! Tree navigation
    237        path = command(idx + 1:len_trim(command))
    238        call change_directory(curr_node, path)
    239     else if (command(1:idx) == 'ls') then
    240        ! Collect the file info from the following lines
    241        do
    242           inquire (unit = unit, pos = file_pos) ! Save the file position before the next read
    243           read (9, '(A)', iostat = ios) input
    244           if (ios /= 0) then
    245              file_pos = 0 ! No point in trying to backtrack
    246              exit
    247           end if
    248           if (input(1:2) == '$ ') exit ! Read past the dir listing, return with the last file pos
    249           idx = scan(input, " ") ! Find first space to split the size and type from the filename
    250           if (input(1:idx - 1) == 'dir') then
    251              call create_and_attach_dir_node(curr_node, input(idx+1:len_trim(input)), new_node)
    252           else
    253              read (input(1:idx - 1), *) file_size
    254              call create_and_attach_file_node(curr_node, input(idx+1:len_trim(input)), file_size)
    255           end if
    256        end do
    257     else
    258        print *, "Error, encountered unknown command!"
    259        error stop
    260     end if
    261   end subroutine shell_command
    262 
    263 end program seven