Advent of Code 2020

Day 9 was interesting. Part 1 was entirely different from Part 2 - I reused nothing. My Part 2 solution was also far shorter.

program AOC09B
implicit none

integer(8), parameter :: result = 552655238
integer(8) :: current,total,smallest,largest
integer :: curpos,ios

open (unit=1,file='input.txt', form='formatted', access='stream')   
inquire (unit=1,pos=curpos)

outer: do
    total = 0
    read (1,*,pos=curpos,end=900) current
    inquire (unit=1,pos=curpos)
    total = current; smallest = current; largest = current
    inner: do
        read (1,*,iostat=ios) current
        if (ios < 0) cycle outer
        if (current < smallest) smallest = current
        if (current > largest) largest = current
        total = total + current
        if (total == result) then
            print *, smallest, largest, smallest+largest
            stop
        else if (total > result) then
            exit inner
        end if
    end do inner
end do outer

900 print *, "Fail"    

end program AOC09B

Day 10 was crazy-simple, but I needed hints from the Solutions thread, not being a math major. As seems often the case here, the task description has a subtle clue that simplifies the problem.

10.2 didn’t require recursion - once you saw the pattern it was quite linear. Here’s my Fortran version:

program AOC10A
    use ifport
    implicit none
    
    integer, allocatable :: list(:), diffs(:)
    integer :: ios, jolts, i,diff, maxjolt,seq
    integer :: count
    
    open (unit=1,file='input.txt', form='formatted', status='old')
    count = 2
    maxjolt = 0
    do 
        read (1,*,iostat=ios) jolts
        if (ios < 0) exit
        count = count + 1
        if (jolts > maxjolt) maxjolt = jolts
    end do
    allocate (list(count),diffs(count))
    rewind (1)
    list(1) = 0
    list(count) = maxjolt + 3
    read (1,*) list(2:count-1)
    call qsort (list, count, 4, compare)
    diffs = 0
    seq = 0
    do i=2,count
        diff = list(i) - list(i-1)
        if (diff == 1) then
            seq = seq + 1
        else if (seq > 0) then
            diffs(seq) = diffs(seq) + 1
            seq = 0
        end if    
    end do
    print *, (2_8**diffs(2)) * (4_8**diffs(3)) * (7_8**diffs(4))

    contains
    
    integer(2) function compare (arg1,arg2)
    integer, intent(in) :: arg1,arg2
    
    compare = arg1 - arg2
    return
    end function compare
    
    end program AOC10A

I spent far too long on 12.2 today going off in the entirely wrong direction, looking for a “transform matrix” or some such. I missed such a big clue in the problem description, but at least I figured it out myself without peeking at hints.

program AOC12A
implicit none

integer :: val
integer :: ship(2),waypoint(2) ! NS, EW
real :: radius, angle
character :: cmd
integer, parameter, dimension(2) :: N=[1,0],S=[-1,0],E=[0,1],W=[0,-1]

ship = [0,0]; waypoint = [1,10]
open (unit=1, file='input.txt', form='formatted', status='old')
do
    read (1,'(A1,I4)',end=900) cmd,val
    select case (cmd)
    case ('N')
        waypoint = waypoint + (val * N)
    case ('S')
        waypoint = waypoint + (val * S)
    case ('E')
        waypoint = waypoint + (val * E)
    case ('W')
        waypoint = waypoint + (val * W)
    case ('F')
        ship = ship + (val * waypoint)
    case ('R','L')
        radius = sqrt(real((waypoint(1)**2)+(waypoint(2)**2)))
        angle = atan2d(real(waypoint(1)),real(waypoint(2))) 
        if (cmd == 'R') then
            angle = angle - real(val)
        else
            angle = angle + real(val)
        end if
        waypoint = [nint(radius * sind(angle)),nint(radius * cosd(angle))]     
    case default
        error stop
    end select
end do
900 print *, sum(abs(ship))    
            
end program AOC12A

Part 2 of Day 16 was fun - got to use a lot of bit intrinsics I don’t normally consider. My solution was much faster than I expected, completed in less than a millisecond.

I’ve dropped out - have too much else going on. I’ll pick it up again next year.