• 0 Posts
  • 148 Comments
Joined 2 years ago
cake
Cake day: July 1st, 2023

help-circle





  • Assuming your vpn provides a stable remote IP, your client connection needs to use that. Try “whatsmyip” or similar over the vpn. The remote address almost certainly won’t appear in the local output of ip a.

    Locally, listen on the “this host”, 0.0.0.0.

    You may need to check your firewall locally.

    You don’t need to run your http service to troubleshoot - simple tools like netcat can listen for incoming requests - nc -l 0.0.0.0 8000 or what-have-you.

    Finally: you might want to look at using a shell host as the client rather than targeting your vpn ip from your local host, just to take hairpin connections out of consideration when troubleshooting.


  • Generic-ish. It’ll fit any of the input problems I think. You could fool it by using a non-canonical circuit, because it knows nothing about the equivalence of boolean expressions; and it also relies on one swap sufficing to fix an output, so I didn’t go particularly far into turning it into a generic search. Either of those problem extensions would take much more effort from a solver, so my expectation is that they were deliberately avoided.


  • Haskell part 2, much better solution

    Okay, here’s the outline again - this one ran instantly.

    Rather than probing with example values, I took a different approach, debugging the structure. I only really care about inputs and outputs, so I wrote something that turns the “wiring diagram” into a map of label -> Expr, where

    data Expr = EInput String
              | EAnd Expr Expr
              | EOr Expr Expr
              | EXor Expr Expr
      deriving (Show, Ord)
    

    (the Eq instance is stable in symmatric expressions, eg (==) (EAnd a b) (Eand c d) = a == c && b == d || a == d && b == c)

    The expressions are grounded in “inputs” (“x00”…“x44”, “y00”…“y44”) - that is, they just expand out all of the intermediary labelled things.

    Then I constructed a circuit that I was after by building a non-swapped 44/45-bit full adder, and produced the same set of expressions for those.

    Then: for each output, z00…z45, check the “spec” expression against the actual one. If they’re identical, move on.

    Otherwise, find some candidate pairs to swap. For these, I considered all possible labelled outputs except “stable” ones - that is, those that were input depdendencies of z_(i-1) - ie, don’t swap any outputs involved in the computation that’s validated thus far.

    searchForSwap :: Exprs -> Layout -> String -> Set.Set String -> [(String, String, Layout, Exprs)]
    searchForSwap eSpec actual zz stable =
      let
        vals = Map.keysSet actual & (`Set.difference` stable) & Set.toList
        ds = dependencies actual
      in do
        k1 <- vals
        k2 <- vals
        guard $ k1 < k2
        guard $ k1 `Set.notMember` (ds Map.! k2)    -- don't create any loops
        guard $ k2 `Set.notMember` (ds Map.! k1)
        let actual' = swapPair k1 k2 actual
            eAct' = exprsForLayout actual'
        guard $ eSpec Map.! zz == eAct' Map.! zz
        pure (k1, k2, actual', eAct')
    

    Taking the new layout with swapped outputs and its corresponding set of expressions, carry on searching as before.

    A linear scan over the output bits was all that was required - a unique answer poped out without any backtracking.

    Anyway, happy Christmas all.

    PS. My other version worked (eventually) - it was following this approach that led me to realise that my “spec” full adder was broken too :-D Never skip the unit tests.

    (@CameronDev@programming.dev you were asking about alternatives to graphviz-style approaches I recall)


  • Haskell, programmatic solution

    I spent an entire day on this because I didn’t write a unit test to check my “swap outputs” function, which effectively did nothing.

    In any case: the approach (which may be more interesting than the code, I know people were interested) involved probing the addition circuit with some example additions - that is, I wrote something that’d let me give alternative inputs from x & y and compute the result using the circuit. I then gave it some simple pairs of values that’d exercise the add and carry bits (ie, pairs chosen from {i << n, n <- {1..43}, i <- {1, 3}}). That gave me some breaking trials.

    Because the errors were relatively sparse, I then scanned over pairs of outputs, swapping those that didn’t introduce a data dependency and checking (a) that no new errors were introduced over the trial sets, (b) for any reduction in the number of errors found. I got a bunch fo outputs like this:

    swap of ("ccp","mnh") improves matters
    bad trial count reduced from 346 to 344
    

    which found the pairs for me. The search could be improved by more carefully tying the probe inputs to the outputs’ dependencies (ie, if the first error comes from the (xi, yi) input bits, then look for swaps of the dependencies introduced by zi) - but in any case, it finds the answer. Phew.



  • Haskell bits and pieces

    The nice thing about Haskell’s laziness (assuming you use Data.Map rather than Data.Map.Strict) is that the laziness can do a ton of the work for you - you might’ve spotted a few Haskell solutions in earlier days’ threads that use this kind of trick (eg for tabling/memoisation). Here’s my evaluation function:

    eval l =
      let
        v = l & Map.map (\case
                           Const x -> x
                           And a b -> v Map.! a && v Map.! b
                           Or a b  -> v Map.! a || v Map.! b
                           Xor a b -> v Map.! a /= v Map.! b)
      in v
    

    For part 2, we know what the graph should look like (it’s just a binary adder); I think this is a maximal common subgraph problem, but I’m still reading around that at the mo. I’d love to know if there’s a trick to this.






  • Thanks. It was the third thing I tried - began by looking for mostly-symmetrical, then asked myself “what does a christmas tree look like?” and wiring together some rudimentary heuristics. When those both failed (and I’d stopped for a coffee) the alternative struck me. It seems like a new avenue into the same diophantine fonisher that’s pretty popular in these puzzles - quite an interesting one.

    This day’s puzzle is clearly begging for some inventive viaualisations.



  • Haskell, alternative approach

    The x and y coordinates of robots are independent. 101 and 103 are prime. So, the pattern of x coordinates will repeat every 101 ticks, and the pattern of y coordinates every 103 ticks.

    For the first 101 ticks, take the histogram of x-coordinates and test it to see if it’s roughly randomly scattered by performing a chi-squared test using a uniform distrobution as the basis. [That code’s not given below, but it’s a trivial transliteration of the formula on wikipedia, for instance.] In my case I found a massive peak at t=99.

    Same for the first 103 ticks and y coordinates. Mine showed up at t=58.

    You’re then just looking for solutions of t = 101m + 99, t = 103n + 58 [in this case]. I’ve a library function, maybeCombineDiophantine, which computes the intersection of these things if any exist; again, this is basic wikipedia stuff.

    day14b ls =
      let
        rs = parse ls
        size = (101, 103)
        positions = map (\t -> process size t rs) [0..]
    
        -- analyse x coordinates. These should have period 101
        xs = zip [0..(fst size)] $ map (\rs -> map (\(p,_) -> fst p) rs & C.count & chi_squared (fst size)) positions
        xMax = xs & sortOn snd & last & fst
    
        -- analyse y coordinates. These should have period 103
        ys = zip [0..(snd size)] $ map (\rs -> map (\(p,_) -> snd p) rs & C.count & chi_squared (snd size)) positions
        yMax = ys & sortOn snd & last & fst
    
        -- Find intersections of: t = 101 m + xMax, t = 103 n + yMax
        ans = do
          (s,t) <- maybeCombineDiophantine (fromIntegral (fst size), fromIntegral xMax)
                                           (fromIntegral (snd size), fromIntegral yMax)
          pure $ minNonNegative s t
      in
        trace ("xs distributions: " ++ show (sortOn snd xs)) $
        trace ("ys distributions: " ++ show (sortOn snd ys)) $
        trace ("xMax = " ++ show xMax ++ ", yMax = " ++ show yMax) $
        trace ("answer could be " ++ show ans) $
        ans