ShareMyScreen/AdventOfCode/2022/16/ProboscideaVolcaniumJP

From J Wiki
Jump to navigation Jump to search

The Problem << >>

This problem cost me a lot of time, likely mostly because of my self-imposed stupidity of trying to solve all problems on my phone. The big problem was it would run out of memory. The second largest problem was me not being happy with the solution needing an entire minute to run.

Entire solution

i16=: freads '16.txt'
NB. part 1: What's the max amount of pressure you can release in 30 min?
0&T.@0^:(0>.([: {. 8&T.)-1&T.) ''                             NB. spin up as many threads as cores
NB. Parse to boxed table with columns pressure release; valve ; connected valves
par=: (".&.>@(6&{) , <@s:@(1&{) , [: <@s: (<,',')-.~12&}.)@;:;._2
NB. Reduce graph removing 0 flow-rate valves and do BFS
graph =: {{
  y=. (({~ , ({~ <^:3)) (<s:<'AA') i.~ 1&{"1) y               NB. AA first, then others.
  valves =. > 1&{"1 y                                         NB. All valves [sym]
  fr     =. > {."1 y                                          NB. flowrates  [num] for valves
  con    =. ; valves&i.&.> ,.&.>/ }.|:y                       NB. connections index pairs
  NB.  iterate shortest  add self con    1's at con into    NxN    $_  NB. self connections required for iteration
  dm     =.  (<./ .+~)^:_]   (*-.@:=@:i.@#)  1      con  }  (,~#valves)$_
  frnz   =. (#~ *) fr                                         NB. non-zero flowrates
  dm     =. (+-.@:=@:i.@#) dm ([{"1{)~ 0,I.fr>0               NB. only AA and non-0 fr's
  NB. from here, indices (into dm) refer to non-zero-fr valves whose flowrates are frnz.

  done    =. 0 2$a:                                           NB. final released values ,. finished paths
  NB. below nouns relate all to currently selected paths
  cur     =. ,. <: }. I._>{.dm                                NB. current paths from AA
  time    =. (#~ _&>) }.  {.dm                                NB. timesteps done for each path
  release =. (x-time) * frnz{~,cur                            NB. released for all paths
  NB. remove AA, because valves cannot be closed, so visiting and opening does not make sense.
  dm      =. }."1 }. dm                                       NB. remove first node AA: never a final dest.
  while. #cur do.
    NB. add connections to current (all reachable, but remove already open valves and valves further than time allotment).
    ncan    =. #&>cand =. time <@(] -.~ (x-[) I.@:> dm {~ {:@])"_1 cur
    NB. retire paths not having any further candidates
    md      =. ncan=0                                 NB. mask for done paths
    done    =. done, release ,.&<"_1&(md&#) cur       NB. add done paths to done
    'cur release time'=.(-.md)&#&.> cur;release;time  NB. remove done paths from cur, release and time
    ncan    =. (#~*)ncan NB. adjust for further treatment, not needed for cand, as these would not show anyhow using ; .
    NB. update cur, time, release and rates (order matters!)
    cur     =. (ncan#cur)    ,. rc=.;cand
    time    =. (ncan#time)   + dm {~ _2<@{."1 cur
    release =. (ncan#release)+(rc{frnz)*(x-time)
  end.
  NB. convert from indices to symbols, the path corresponding to the max release, returning release and symbolic path
  ]`({&(valves#~0<fr) &.>)"0 ({~ i.&1@(=>./)@:>@:({."1)) done
}}
part1=:0{::30&graph@par

NB. part 2: How much pressure release in 26m when helped by one elephant?
twoplayer =: {{
NB. make distance matrix, apply power to find all pairwise distances, remove AA and any non-0 flow-rate nodes, simulate paths through that reduced graph, rather than all nodes. Simulate per valve opening, as for part 1.
  y=. (({~ , (\: {."1)@({~ <^:3))  (<s:<'AA') i.~ 1&{"1) y    NB. AA first, then others
  valves =. > 1&{"1 y                                         NB. All valves [sym]
  fr     =. > {."1 y                                          NB. flowrates  [num] for valves
  con    =. ; valves&i.&.> ,.&.>/ }.|:y                       NB. connections index pairs
  dm     =.  (<./ .+~)^:_] (*-.@:=@:i.@#)  1 con} (,~#valves)$_ NB. distance matrix 
  frnz   =: ({. , (#~ *)@}.) fr                               NB. AA's and non-zero flowrates
  dm     =. (+-.@:=@:i.@#) dm ([{"1{)~ 0,I.fr>0               NB. only AA and non-0 fr's
  NB. from here, indices (into dm) refer to non-zero-fr valves whose flowrates are frnz.
  NB. convert dm to list (for each source) of lists of (for each dest):
  NB.    dest num; dest bitmap; dist (no fr, lookup in nfrz)
  destBmDist =: ({."1 (((, 32 b.&1)@{. , {:)"1)/. }."1) (4&$.,.5&$.) $. dm
  twosNZ =: 2#~#destBmDist                                    NB. 2's repeated for each state, for bitmask calculations
  NB. state access verbs for times, valves, bitmask (for all states in y).
  '`pr bm t0 v0 t1 v1'=: (0&{"1)`(1&{"1)`(2&{"1)`(3&{"1)`(4&{"1)`(5&{"1)
  timestab =: 2+2*<.-:i.#frnz                NB. multipliers for heuristic in updi
  NB. updi is internal update adv, taking x: applicable destBmDist states, y: current states acc. release, time, valve, bm; m is player to get data from/update
  updi=: {{
    my=. y {~ mm=.(0 1 2 3 ,:0 1 4 5) {~ m   NB. relevant fields for my player
    'd b t'=.|:x                             NB. dest, bitmap, time to get to new state
    bu=. b 20 b. 1{my                        NB. bitmap updated
    tu=. t -~ 2{my                           NB. time left updated
    pu=. (tu*d{frnz)+{.my                    NB. Pressure released updated
    hnn =. (tu>:0) *.  bestsc < pu +(tu >. y{~ 5-3*m) (] +/@,@:*  (- timestab {.~ #))"0 1 frnz #"1~ twosNZ#:bu
    if. bestsc < newbest=.>./ hnn#pu do.     NB. find new best if present
      bestsc =: newbest
    end.
    st=. (hnn #|:pu,bu,tu,:d) mm}"1 y i      NB. piece back states
    st=. (2&{. , [: ,@/:~ (2 3,:4 5)&{)"1 st NB. sort for later removal of semi-dupes, where p0 and 1 are swapped.
  }}
  avind=. I.@|.@(twosNZ&#:)@bm               NB. available valve indices (not yet open)
  NB. select rows from destBmDist available, i.e. where state not yet visited.
  sel0 =. avind (]#~(e.~ {."1)) destBmDist {~ v0
  sel1 =. avind (]#~(e.~ {."1)) destBmDist {~ v1
  NB. update verbs for p0 and p1, takes single state as y.
  upd0 =: (] (0 updi)~ sel0) f.
  upd1 =: (] (1 updi)~ sel1) f.
  NB. unpack/pack: unpack each state from single int, and reverse.
  pack   =: ([: 23 b./ (0 13 18 23 27 31)&(32 b.))@|:
  unpack =: ([: |: (<:(32 b.&1) 13 5 5 4 4 16) 17 b. (-0 13 18 23 27 31) 32 b./ ]) :. pack
  NB. Set up initial state
  ns =. #states=. pack ,: 0, (1-~twosNZ#.1), x,0,x,0
  bestsc=: 0
  while. *ns do.                             NB. Loop while eligible states
    new0 =. upd0&.unpack t.0"0 states        NB. new states by moving player 0
    ns =. #states =.~.@; (;@:(<@(upd1&.unpack"0))) t.0 &> new0 NB. new states by moving player 1, for each of the new0
  end.
  bestsc
}}
part2=:26&twoplayer@par
(part1;part2) i16       NB. returns solution

Data and parsing

The data looks like this:

tst=:{{)n
Valve AA has flow rate=0; tunnels lead to valves DD, II, BB
Valve BB has flow rate=13; tunnels lead to valves CC, AA
Valve CC has flow rate=2; tunnels lead to valves DD, BB
Valve DD has flow rate=20; tunnels lead to valves CC, AA, EE
Valve EE has flow rate=3; tunnels lead to valves FF, DD
Valve FF has flow rate=0; tunnels lead to valves EE, GG
Valve GG has flow rate=0; tunnels lead to valves FF, HH
Valve HH has flow rate=22; tunnel leads to valve GG
Valve II has flow rate=0; tunnels lead to valves AA, JJ
Valve JJ has flow rate=21; tunnel leads to valve II
}}

I parse it to a boxed array with a row for each valve containing: flow rates, valve names and connected valves.

par=: (".&.>@(6&{) , <@s:@(1&{) , [: <@s: (<,',')-.~12&}.)@;:;._2
   par tst
┌──┬───┬───────────┐
0 `AA`DD `II `BB
├──┼───┼───────────┤
13`BB`CC `AA    
├──┼───┼───────────┤
2 `CC`DD `BB    
├──┼───┼───────────┤
20`DD`CC `AA `EE
├──┼───┼───────────┤
3 `EE`FF `DD    
├──┼───┼───────────┤
0 `FF`EE `GG    
├──┼───┼───────────┤
0 `GG`FF `HH    
├──┼───┼───────────┤
22`HH`GG        
├──┼───┼───────────┤
0 `II`AA `JJ    
├──┼───┼───────────┤
21`JJ`II        
└──┴───┴───────────┘

Part 1

The valve network forms a graph, though it's not very connected, with a big chunk of the nodes only having two connections:

   (~. ,: #/.~) #&> {:"1 par i16
 2 5 4 3 1 NB. unique node degrees
44 6 2 3 1 NB. number of occurences

The distribution of zeros is also peculiar:

   (~. ,: #/.~) /:~ ; {."1 par i16
 0 3 4 9 10 11 12 13 17 18 19 21 22 23 24 25 NB. unique flow rates
41 1 1 1  1  1  1  1  1  1  1  1  1  1  1  1 NB. number of occurences

Valves with 0 flow rate are not useful, and should only ever be visited on the way to a more useful, non-zero flow rate valve. Removing them from the graph gets rid of 41 of the 50 nodes! Although this helps reduce the number of states, it does complicate the problem a little, as getting from one node to an other in the reduced graph will no longer take a single minute.

Let's turn this into a verb, I'll call graph:

graph =: {{
  y=. (({~ , ({~ <^:3)) (<s:<'AA') i.~ 1&{"1) y               NB. sort: AA, then descending flow rate (Improves perf)
  valves =. > 1&{"1 y                                         NB. All valves [sym]
  fr     =. > {."1 y                                          NB. flowrates  [num] for valves
  con    =. ; valves&i.&.> ,.&.>/ }.|:y                       NB. connections index pairs
  NB.       iterate shortest  add self con  1's at con into    NxN    $_  NB. self connections required for iteration
  dm     =.  (<./ .+~)^:_]   (*-.@:=@:i.@#) 1      con  }  (,~#valves)$_
  NB. ...

The first line puts AA is first (handy, because later we'll exclude it, but it is now required for the connections). After extracting valve symbols (for lookup) and flow rates, I get a list of connection indexes which should be connected in the distance matrix (i.e. have distance 1). The initial distance matrix has infinity for all distances, except directly connected ones (which have distance 1) and self-connections (having distance 0), which are required for the iterative finding of minimum distances between each node of the graph, which is explained in the first part of this essay on the Floyd-Warshall algorithm.

Now that dm contains all pairwise distances, I no longer need the entries of the zero flow rate valves, so I remove the corresponding columns and rows, and increase the distance for all but the self-connections to account for the time spent opening the valves.

  frnz   =. (#~ *) fr                                         NB. non-zero flowrates
  dm     =. (+-.@:=@:i.@#) dm ([{"1{)~ 0,I.fr>0               NB. only AA and non-0 fr's

As I'd like to remove the starting node AA from the distance matrix as well, I set up variables for the initial states, for each of which I keep - released pressure - time spent for each, because the different distances cause different states to reach the end count in a different amount of steps. - the path so far to keep track which states to visit in the future.

  done    =. 0 2$a:                                           NB. final released values ,. finished paths
  NB. below nouns relate all to currently selected paths
  cur     =. ,. <: }. I._>{.dm                                NB. current paths from AA
  time    =. (#~ _&>) }.  {.dm                                NB. timesteps done for each path
  release =. (x-time) * frnz{~,cur                            NB. released for all paths
  NB. remove AA, because valves cannot be closed, so visiting and opening does not make sense.
  dm      =. }."1 }. dm                                       NB. remove first node AA: never a final dest.

The breadth-first search finds possible candidates for each current state, that is, all destination valves that are still closed and within the 30 minutes (x, as I used this for debugging). The ones that have no candidates are done, kept (in the done variable) and removed from the state variables cur, release, and time varibles. The new candidates are added, until there are no more current states.

  while. #cur do.
    NB. add connections to current (all reachable, but remove already open valves and valves further than time allotment). Boxed candidates per current state.
    ncan    =. #&>cand =. time <@(] -.~ (x-[) I.@:> dm {~ {:@])"_1 cur
    NB. retire paths not having any further candidates
    md      =. ncan=0                                 NB. mask for done paths
    done    =. done, release ,.&<"_1&(md&#) cur       NB. add done paths to done
    'cur release time'=.(-.md)&#&.> cur;release;time  NB. remove done paths from cur, release and time
    ncan    =. (#~*)ncan NB. adjust for further treatment, not needed for cand, as these would not show anyhow using ; .
    NB. update cur, time, release and rates (order matters!)
    cur     =. (ncan#cur)    ,. rc=.;cand
    time    =. (ncan#time)   + dm {~ _2<@{."1 cur
    release =. (ncan#release)+(rc{frnz)*(x-time)
  end.

The last line converts the valve indices on the best path found to its symbols (as I thought it might prove useful for part 2 ... not the case). The final solution, part1, just extracts the pressure released:

  ]`({&(valves#~0<fr) &.>)"0 ({~ i.&1@(=>./)@:>@:({."1)) done
}}
part1 =: 0 {:: 30&graph@par

Just for curiosity, eventually, 204896 states are explored.

Part 2

So now, we have an elephant (player 1 or p1) helping us (player 0 or p0), moving around and opening valves independently, which increases the number of possible states enormously. Part 2 gave me major headaches. I managed to crank out a solution, in the same vein of part 1, with heavy optimisation and parallel processing, but I suspect a smarter solution exists. I didn't keep all iterations of the code, but below is the fastest, simplest version I came across.

The optimisations I added are:

  • parallel processing for state updates
  • a heuristic to discard states that cannot possibly lead to better results
  • the heuristic and best pressure release handling are performed right after state creation, within the worker threads, before adding it to the state to reduce communication of useless data between threads
  • encode visited states into a 16 bit bitmask (int)
  • pack states (normally 6 ints) into single int (which works only on 64bit J)

As I'm exploring states in parallel, enough threads (typicaly the same number as cores on the computer) have to be started:

0&T.@0^:(0>.([: {. 8&T.)-1&T.) ''

The construction of dm is mostly the same as in part 1 above, so I skip it here. The only difference is that I chose to include the initial valve AA into the reduced valve graph because setting up all "initial" states following valve AA (as in part 1) was too tedious for the two players in part 2, so frnz is set as:

frnz   =: ({. , (#~ *)@}.) fr NB. AA's and non-zero flowrates

I also changed the state representation to reduce required memory, keeping for every state the pressure released (index 0), the bitmask of closed (visitable) valves (index 1), time left (instead of elapsed) for both players (ind. 1, 3), the current valve for both players (ind. 2, 4). I now store the destinations, bitmasks and distances in a 3D array (source valve x destination valve x (valve num, bitmask, distance). No need for excluding valve AA in destBmDist, because the bitmask excludes it from being selected anyhow.

twoplayer =: {{
  NB. ... setting up dm mostly the same as in part 1
  NB. convert dm to list (for each source) of lists of (for each dest):
  NB.    dest num; dest bitmap; dist (no fr, lookup in nfrz)
  destBmDist =: ({."1 (((, 32 b.&1)@{. , {:)"1)/. }."1) (4&$.,.5&$.) $. dm
  twosNZ =: 2#~#destBmDist                   NB. 2's repeated for each state, for bitmask calculations

After this, I set up verbs for accessing different parts of states and an adverb for updating the states, for both players: updi is an adverb, yielding verbs for player m.

  NB. state access verbs for times, valves, bitmask (for all states in y).
  '`pr bm t0 v0 t1 v1'=: (0&{"1)`(1&{"1)`(2&{"1)`(3&{"1)`(4&{"1)`(5&{"1)
  timestab =: 2+2*<.-:i.#frnz                NB. multipliers for heuristic in updi
  NB. updi is internal update adv, taking x: applicable destBmDist states, y: current states acc. release, time, valve, bm; m is player to get data from/update
  updi=: {{
    my=. y {~ mm=.(0 1 2 3 ,:0 1 4 5) {~ m   NB. relevant fields for my player
    'd b t'=.|:x                             NB. dests, bitmaps, times to get to new states
    bu=. b 20 b. 1{my                        NB. bitmap updated
    tu=. t -~ 2{my                           NB. time left updated
    pu=. (tu*d{frnz)+{.my                    NB. Pressure released updated
    hnn =. (tu>:0) *.  bestsc < pu +(tu >. y{~ 5-3*m) (] +/@,@:*  (- timestab {.~ #))"0 1 frnz #"1~ twosNZ#:bu
    if. bestsc < newbest=.>./ hnn#pu do.     NB. find new best if present
      bestsc =: newbest
    end.
    st=. (hnn #|:pu,bu,tu,:d) mm}"1 y i      NB. piece back states
    st=. (2&{. , [: ,@/:~ (2 3,:4 5)&{)"1 st NB. sort for later removal of semi-dupes, where p0 and 1 are swapped.
  }}

This is doubtlessly the most important bit here: m is the current player; m updi yields a verb that, for player m (0/1), takes a visitable state on the left, and the current state on the right, and returns all sibling states that fulfill two conditions:

  1. their time left, tu is not less than zero
  2. an upper-bound guess of the possible final score is larger than the current best score.

The upper-bound guess is the updated pressure plus the sum of the valves (which are ordered by decreasing release order) multiplied by the highest time left (of the two players) minus 2 2 4 4 6 6 ... for as many valves remain. The idea is that going to and opening a valve takes at least two steps and the best result is thus that the two largest valves are opened after 2 steps, the next two after 4 and so on.

Another important consideration I made just before this write-up was that it is irrelevant which player is which: swapping players still results in a validly reached state. This leads to a lot of redundant states. To remove redundant states I sort the times/valves, so equivalent states are removed later on (by ~. in the loop at the end of the function twoplayer). This makes things a LOT faster.

To take a list of states and create the list of possible states for each, and run updi, I wrote the following:

  NB. available valve indices (not yet open) from state
  avind=. I.@|.@(twosNZ&#:)@bm
  NB. select from destBmDist the possible next states 
  sel0 =. avind (]#~(e.~ {."1)) destBmDist {~ v0
  sel1 =. avind (]#~(e.~ {."1)) destBmDist {~ v1
  NB. update verbs for p0 and p1, takes single state as y
  upd0 =: (] (0 updi)~ sel0) f.
  upd1 =: (] (1 updi)~ sel1) f.

Now for the last optimisation: packing and unpacking the 6 ints representing the state in a single integer. This works ONLY on 64 bit though, as 49 bits are needed:

PR: max 6006 :        13 bit
bm max 2^16=65536     16 bit
t0/v0 max 26, 16 ;5+5=10 bit 
t1/v1 max 26, 16 ;5+5=10 bit
total                 49 bits

pack operates on an entire list of states by doing a binary using 32 b. for binary rotation of each variable, and then ORing them together with 23 b./. unpack does the opposite, by shifting the number to the opposite side, and ORing them with appropriate bit masks. This again takes off a substantial chunk of execution time.

  pack   =: ([: 23 b./ (0 13 29 34 39 44)&(32 b.))@|:
  unpack =: ([: |: (<:(32 b.&1) 13 16 5 5 5 5) 17 b. (-0 13 29 34 39 44) 32 b./ ]) :. pack

After all this preparation, the eventual loop becomes rather simple:

  • Set up the initial state: 0 pressure released so far, all valves except AA to be visited, both players at AA with 26 minutes left.
  • Initialise best score bestsc to 0.
  • Loop while there are any states left:
    • Do, in parallel, all possible moves for all possible states by player 0
    • Do, in parallel, all possible moves for each of the states returned for player 0, try all possible states for player 1.
    • Join the results, filter unique. Given that updi already sorted the state, equivalent states (where only player roles are swapped) are removed as well.
  ns =. #states=. pack ,: 0, (1-~twosNZ#.1), x,0,x,0 NB. Set up initial state, pack, keep number.
  bestsc=: 0
  while. (*ns) *. ct<10 do.                  NB. Loop while eligible states
    new0 =. upd0&.unpack t.0"0 states        NB. new states by moving player 0
    ns =. #states =.~.@; ;@:(<@(upd1&.unpack"0)) t.0 &> new0 NB. new states by moving player 1, for each of the new0
  end.
  bestsc
}} NB. ends twoplayer
part2=:26&twoplayer@par

Note that updi runs in parallel without further synchronisation, which leads to more or less states being explored, based on the exact timing of bestsc being updated, but it is guaranteed not to produce bogus, i.e. values are are protected from changes once their name is looked up.

Eventually, this solution managed to complete in only 9 seconds while my earlier attempts took 58s, a result I was very happy with.