Advent of Code 2022

Advent of Code is an Advent calendar of small programming puzzles for a variety of skill sets and skill levels that can be solved in any programming language you like.

The first puzzles will unlock on December 1st at midnight EST (UTC-5). See you then!

https://adventofcode.com/

9 Likes

We should create a leaderboard for Fortran-lang again.

Or we can use one of the previous years:

2 Likes

nahh, we need one for 2022

1 Like

I’m looking forward to participating in this again.

3 Likes

Let’s use the same leaderboard as last year. Every year gets a separate score, and you can still see the scores from previous years. The leaderboard code is 1510956-4380811b and you have to enter it here (you need to be logged in, otherwise you’ll get redirected elsewhere).

1 Like

One can find Fortran solutions for the 2021 edition on GitHub with Search · aoc-2021-in-fortran · GitHub. I suggest that the analogous topic be used for the 2022 edition.

2 Likes

While overengineering today’s AOC tasks, I stumbled into some limitations of Fortran (or maybe limitations of my Fortran skills?).
The task is to parse a list of integers, sum up each group and find the maximum. The way I tried to do it was a kind of parser. The general structure of function calls looks like this:

call graph
max_calories
    -> get_next_sum
        -> get_next_integer
            -> get_next_line
                -> intrinsic read

The first problem I had was the fact, that there is no straightforward way of handling exceptions. If the innermost read hits eof, this information has somehow to be handed back to the outermost function.
I tried to do this by returning allocatable integers, where an unallocated integer would have meant, the file has reached eof. Unfortunately, Fortran cannot return this kind of information, so I had to add an logical :: eof to my reader class. Similar to this, I needed a way to handle empty lines. In this case, I can simply return 0, but I’m asking myself if there is a better solution, especially when the parser logic would be more complex. Would I require an eof equivalent for each level of abstraction/function (or a more general status variable)?

Another problem I found is inheritance of class constructors. I use two classes, a task specific “calories parser” and a more general file reader (which can read integers). The file reader opens the file and stores the file unit in the constructor function. The calories parser extends the file reader with the next_calories method, which basically returns the next sum of contiguous integer lines. Now if I want to create a new calories parser, I want to use the constructor of the file reader, but I didn’t manage to find a way that made me happy. My last approach is a member subroutine in the file reader, which acts as constructor and can be called by another constructor function, which has to be defined for each child class.

constructor diagram
type(calories_reader_t) :: cr
cr = calories_reader_t(filename)
      -> interface calories_reader_t
          -> calories_reader_constructor
              -> call cr%constructor(filename)
                  -> file_reader%constructor(filename)

Funfact: In contrast to this highly overengineered Fortran solution, you can solve the puzzle with one line of “shell” or Python:

Shell and Python one-liner
cat input.txt | tr '\n' '+' | sed 's/++/\n/g;s/+$/\n/' | bc | sort --numeric-sort --reverse | head -3 | tr '\n' '+' | sed 's/+$/\n/' | bc
sum(sorted(map(lambda _:eval(_.replace('\n','+')),open("input.txt").read()[:-1].split(2*'\n')))[-3:])

That does seem like overengineering, but that can be fun. I started out simple.

I wrote a simple program that seem to do the work

program day1

    implicit none
    integer :: ios
    integer, parameter :: read_unit = 99
    integer, allocatable :: numbers(:)
    character(len=200) :: line
    integer :: n, i, count, number

    open(unit=read_unit, file='calories.txt', iostat=ios)
    if ( ios /= 0 ) stop "Error opening file data.dat"

    n = 0

    do
        read(read_unit, '(A)', iostat=ios) line
        if (ios /= 0) exit
        if (len(trim(line)) == 0 ) n = n + 1
    end do

    print*, "File contains ", n, "blanks line"

    allocate(numbers(n+1))

    rewind(read_unit)
    count = 0
    i = 0

    do 
        read(read_unit, '(A)', iostat=ios) line
        if (ios /= 0) exit   
        if (len(trim(line)) == 0 ) then
            i = i + 1
            numbers(i) = count
            count = 0
        else
            read (line,'(I10)') number
            count = count + number
        endif
    end do

    numbers(n+1) = count
    print*, "highest calories value carried by an elf is: ", maxval(numbers)

    close(read_unit)

end program day1

I am probably going to do most of them in awk again, much fun. Maybe I’ll also do some in Fortran.

This is an expensive way to look for a blank line. The trim() function must first scan the line to look for the last nonspace character, then allocate memory, then copy characters into that new memory. Then the len() function looks to see the length of that new character string. The len_trim() function just does the first step, it scans the line and returns the integer result. Of course, a compiler might recognize the dead code in the len(trim(line)) expression and do the right things anyway, maybe with some level of optimization being specified, but why depend on that when len_trim() is right there?

However, there might be other ways to answer the question, and I’m not sure which is best. The expression line==' ', returns .true. for a blank line. Character string comparisons in fortran test the leading characters for equality, in this case a single space, and then ensure that the rest of the line has only trailing spaces. That might be more efficient since the compiler can do those tests on multiple bytes at a time. Also, that expression arguably looks simpler to a human reading the code. That comparison also works with a zero-length string, '', but I usually compare to a single space out of habit (f77 did not allow zero-length strings).

The best solution to this would be for the read statement to tell you how many characters it read, so you could limit the subsequent comparisons to just those characters. This was a feature of 1970s-era DEC VAX I/O, but unfortunately it never made it into any fortran standard.

1 Like

Actually, it did.

The SIZE= specifier in an input statement causes the variable specified to become defined with the count of the characters transferred from the file by data edit descriptors during the input operation. Blanks inserted as padding are not counted.

1 Like

I took the challenge of doing this with the shortest possible code.

I’ve just found the shortest way of dealing with blanks is:

read(iunit,'(i10)',blank='ZERO',iostatn=ios) meal

So far I’m at 18 lines EDIT: 15 lines

program aoc_2022_01
    use iso_fortran_env
    integer, allocatable :: eat(:)
    open(newunit=iunit,file='input.txt',form='formatted',iostat=ios)
    allocate(eat(1),source=0)
    do while (.not.is_iostat_end(ios))
        read(iunit,'(i10)',blank='ZERO',iostat=ios) meal
        if (meal==0) then
            eat = [eat,meal]
        else
            eat(size(eat)) = eat(size(eat))+meal
        end if
    end do
    print "(*(a,:,i0))", 'elf ',maxloc(eat),' of ',size(eat),' ate ',maxval(eat),' calories'
end program

Maybe I should use FORTRAN77, that would save further bloat…

3 Likes

For Day 2, I got really nice mileage out of the INDEX intrinsic, to look up values in a 3x3 payoff matrix.

Understandable, you have basically awk in your name: AWvwgK :smiley:

If you want to shorten the code, then remove the FileName parameter and place the name literal directly in the open statement. Remove the declarations to unit, ios, meal since they are implicit integer anyway. You can remove the close() statement since the file will be closed anyway at the program end.

Also, if you just want to reduce the number of lines, then put the entire program on one line with the statements separated with semicolons.

1 Like

I have some ideas to save more lines:

  • don’t use program, end es enough
  • you don’t need an else and if can then be one line
  • iso_fortran_env isn’t used
1 Like

nice trick I didn’t know about! I was also thinking of replacing if/then/else with an arithmetic if.
EDIT: the whole program could be refactored as

integer, allocatable :: eat(:)
open(newunit=iunit,file='input.txt',form='formatted')
allocate(eat(1),source=0)
1 read(iunit,'(i10)',blank='ZERO',err=5,end=5) meal
2 if (meal) 3,3,4
3 eat = [eat,meal]; goto 1
4 eat(size(eat)) = eat(size(eat))+meal; goto 1
5 print "(*(a,:,i0))", 'elf ',maxloc(eat),' of ',size(eat),' ate ',maxval(eat),' calories'
end program

now down to 9 lines!

1 Like

For day 2 (second part) I used FINDLOC instead of INDEX. I thought what I ended up with was rather elegant.

@FedericoPerini , did you test your code? Was not the task the one listed here i.e., on the penultimate line in the link?

If you care to strive for some code readability, a level of correctness, and the fewest characters in code as opposed to fewest lines which makes little sense, you might consider the following:

Click to reveal code
   open(7,file='input.txt',form='formatted') ; n = 1 ; m = 0 ; k = 0 ; mtk1 = -1; mtk2 = -1; mtk3 = -1; nk = 0 
   do ; read(7,fmt='(bn,i9)',iostat=i) k ; if (i > 0) then ; print *, i ; stop ; end if ; if ( i < 0 ) exit
      if (k == 0) then ; if (mtk1 < nk) then ; m = n ; mtk1 = nk ; else if (mtk2 < nk) then ; mtk2 = nk
                         else if (mtk3 < nk) then ; mtk3 = nk ; end if
         n = n + 1; nk = 0 ; cycle ; end if
      nk = nk + k ; end do
   if (m > 0) then ; print "(*(g0))", " elf #", m, " is carrying ", mtk1, " calories."
       print "(*(g0))", " Top 3 elves are carrying ", mtk1+mtk2+mtk3, " calories." ; end if
end
C:\temp>gfortran p.f90 -o p.exe

C:\temp>p.exe
 elf #69 is carrying 71023 calories.
 Top 3 elves are carrying 203942 calories.