Advent of Code 2020

The Advent of Code 2020 is live. This is a set of programming puzzles, two each day, which can be implemented in any language you like - I chose Fortran. It starts out easy, some of the later ones are harder. I did last year’s all in Fortran, and plan to do so this year. It’s fun to see the discussion and examples where people used oddball languages (SQL!) in their solutions.

8 Likes

Should we set up a Fortran leaderboard?


Edit: I created a private leaderboard in case you want to make it more competitive. The code is 1058222-e9b511cc. Feel welcome to join!

2 Likes

I’m already on someone else’s private leaderboard, but it’s a fun thing to do.

Speaking of oddball languages, for day 2 a spreadsheet program can do the job fine:

I too had an O(n^3) solution to part 2 of day 1. The subreddit is full of suggestions for how to optimize (some practical, some not). The simplest for this problem was to skip cases where the first two values exceeded 2020.

When I did this last year, I had occasion to visit the subreddit for clues as to how to proceed. It’s entertaining to see what people come up with. Expect the problems to be harder as the month goes on.

1 Like

The way the private leaderboards seem to work is the first person to solve the puzzle, upon it becomes available, gets more points. In essence it means your time zone and sleeping habits are a dominant factor in the leaderboard. For the record my day 3 solution has c. 130 lines.

Yes, the earlier you solve it, the more points you get, both for private leaderboards and the global one. The subreddit has “megathread” pages for each day, where people post solutions. It doesn’t go live until at least “a significant number of people” have solved both puzzles. It tends to unlock minutes after the puzzle is put up (at least so far.)

My Fortran solution to Day 3 is 39 lines.

I just counted the second one - the first was shorter. I had to add a few lines to get the second.

Day 4, part 2… another string manipulation… I mean it is a good practice to refresh our string-skills, but it gets boring after a while. Hopefully, the next puzzles will have something new to offer. I am uploading my solutions so far to github, with the hope that others will follow as well. It would be very interesting and educational to see different approaches and technics.

You can find mine here: https://github.com/ivan-pi/adventofcode-2020

Edit: I was quite happy to learn how to use the string intrinsics, index, verify, and the new intrinsic split.

I used scan for the first time! The problems will get more complex.

1 Like

What programming language is this? Is that last line finding the missing seat by taking the difference of the product of smallest and largest seat id and the sum of all seat id’s?

My day 6 solutions made use of one of my favorite intrinsics:

popcnt

1 Like

Looks like Haskell. Any language is fine!

Here’s my Fortran solution to part 2 of Day 6. Part 1 was very similar.

program AOC06
implicit none
integer :: answers,group,total,i,ios
character(80) :: line

open (unit=1,file='input.txt', form='formatted', status='old')
total = 0
ios = 0
outer: do while (ios == 0)
    group = int(Z'03FFFFFF')
    inner: do
        read (1,'(A)', iostat=ios) line
        answers = 0 
        if ((ios /= 0) .or. (line == "")) exit inner
        do i=1,len_trim(line)
            answers = ibset(answers, ichar(line(i:i)) - ichar('a'))
        end do
        group = iand(group,answers)
    end do inner
    total = total + popcnt(group)
end do outer   
print *, total
end program AOC06

I also used popcnt. My program logic was similar, although perhaps less elegant…

module day6

  use, intrinsic :: iso_fortran_env, only: int32
  implicit none

  character(len=*), parameter :: lowercase = 'abcdefghijklmnopqrstuvwxyz'

contains

  subroutine process_forms(file,nyes_any,nyes_all)
    character(len=*), intent(in) :: file
    integer, intent(out) :: nyes_any, nyes_all

    integer :: unit, err, ngroup, i, ii, npeople
    character(len=100) :: buffer
    logical :: eof
    integer(int32) :: mask_or, mask_and, mask

    open(newunit=unit,file=file,action="read",status="old")

    nyes_any = 0
    nyes_all = 0

    ngroup = 0
    npeople = 0
    
    mask_or = 0
    mask_and = 0

    do
      read(unit,'(A)',iostat=err) buffer

      if (err < 0) eof = .true.

      if (len_trim(buffer) > 0) then
        npeople = npeople + 1
        mask = 0
        do i = 1, len_trim(buffer)
          ii = index(lowercase,buffer(i:i))
          if (ii > 0) mask = ibset(mask,ii-1)
        end do
        mask_or = ior(mask_or,mask)
        if (npeople == 1) then
          mask_and = mask
        else
          mask_and = iand(mask_and,mask)
        end if
      end if

      if (len_trim(buffer) == 0 .or. eof) then
        nyes_any = nyes_any + popcnt(mask_or)
        nyes_all = nyes_all + popcnt(mask_and)
        
        ngroup = ngroup + 1
        npeople = 0

        mask_or = 0
        mask_and = 0
      end if

      if (eof) exit

    end do

    close(unit)

  end subroutine

end module

Day 7 will be a tough one with Fortran! I am thinking of some recursive string function.

I’m working on this now. So far, I don’t need recursion, but I see in the megathread that others used it. I’m regretting deleting my “symbol table” code from last year - just recreated it.

I was able to solve part 1 with some nasty string lists…

Spoiler alert!
module day7

  implicit none

  type :: string
    character(len=:), allocatable :: s
  end type

contains

  logical function contains(list,str)
    type(string), intent(in) :: list(:)
    type(string), intent(in) :: str
    integer :: i

    contains = .false.
    do i = 1, size(list)
      if (list(i)%s == str%s) then
        contains = .true.
        return
      end if
    end do
  end function

  subroutine make_unique(slist,out)
    type(string), intent(in) :: slist(:)
    type(string), intent(out), allocatable :: out(:)

    integer :: i

    out = [slist(1)]
    do i = 2, size(slist)
      if (contains(out,slist(i))) cycle
      out = [out, slist(i)]
    end do
  end subroutine

  recursive subroutine collect_bags(unit,search_for,ph)
    integer, intent(in) :: unit
    type(string), intent(inout), allocatable :: search_for(:)
    integer, intent(inout) :: ph(2)

    type(string) :: bag
  
    character(len=1000) :: buffer
    integer :: ic, ib, pos
    integer :: i, nbags, stat

    nbags = 0
    do i = ph(1), ph(2)-1
      stat = 0
      do while (stat == 0)
        read(unit,'(A)', iostat=stat) buffer
        ic = index(buffer,'contain')
        ib = index(buffer,search_for(i)%s,back=.true.)
        ! print *, "ic = ", ic, " ib = ", ib
        if (ib > ic) then
          nbags = nbags + 1
          pos = index(buffer,' bags')
          bag%s = buffer(1:pos)
          search_for = [search_for, bag]
        end if
      end do
      rewind(unit)
    end do

    if (nbags > 0) then
      ph(1) = ph(2)
      ph(2) = size(search_for) + 1
      call collect_bags(unit,search_for,ph)
    end if
  end subroutine

end module

program main
  
  use day7
  implicit none
    
  integer :: unit
  integer :: i, ph(2)

  type(string), allocatable :: string_list(:), out(:)

  open(newunit=unit,file="input",action="read")

  string_list = [string('shiny gold')]

  ph = [1,2]
  call collect_bags(unit,string_list,ph)
  call make_unique(string_list(2:), out)

  do i = 1, size(out)
    print *, i, out(i)%s
  end do

  close(unit)
end program main

Day 8 was fun, another take on the “intcode” computer of 2019. I expect later days will build on this.