Let GHC implement folds for you!

Hi all! Long time Haskell user, first post on this site. Just wanna show a simple yet fun idea as a way to say hello.

The other day I wrote a puzzle solver and crawled some puzzles from various websites, and I ended up having something like this stored in JSON:

type Bundle = (M.Map (Int, T.Text) Puzzle, IM.IntMap (IM.IntMap Puzzle))

Now to test my solver, I need to traverse and solve all these puzzles. Then I realized, if I have a newtype, GHC can do that for me!

newtype Bundle2 a
  = Bundle2 (Bundle a)
  deriving stock (Functor, Foldable)
  deriving newtype (FromJSON) -- too lazy to pack/unpack, let aeson do it.

type Bundle a = (M.Map (Int, T.Text) a, IM.IntMap (IM.IntMap a))

-- I wish local type synonym is a thing
solveBundle2 :: forall i. i ~ Sum Int => Bundle2 Puzzle -> IO ()
solveBundle2 bd = do
  let
    (Sum solved, Sum partial, Sum failed) =
      foldMap @_ @(i, i, i) go bd
      where
        go pz = fromMaybe (0, 0, 1) do
          ss0 <- Solver.prepare pz
          (done, _ss1) <- Solver.solve ss0
          pure if done then (1, 0, 0) else (0, 1, 0)
  printf "solved: %d, partial: %d, failed: %d\n" solved partial failed

testSolver :: FilePath -> IO ()
testSolver fp = do
  Just bd <- decodeFileStrict' @(Bundle2 Puzzle) fp
  solveBundle2 bd

… and that’s it.

In retrospect, this is probably one of the intended use of newtype - I’m getting too used to thinking typeclasses as just smart interfaces. In this case however, newtype is more of a “vessel” that GHC can fill in the obvious instance implementation for you, if the typeclass is deriving-able.

Cheers!

9 Likes

Hi Javran,
That looks very interesting to me. Would you mind posting a link to the complete program so that I could take a look at it and understand it better.
Best wishes,
Henry Laxen

2 Likes

Thanks for your interest in this Henry! The code is in a private repo, but I suppose I can move the solver part to somewhere public.

Thanks Javran, yes if you wouldn’t mind. I’l like to study the solver.

Here’s the full program: puzzle-solving-collection/kakuro-solver at ab2068900bdce32940cad8189508aee152b2f510 · Javran/puzzle-solving-collection · GitHub

This is a solver for Kakuro.

(As the repo name suggests I have a bunch of solvers of logic puzzles in the same repo, you may enjoy those as well)

Unfortunately as I refactor it to get some time measurements, I found it more convenient to discard invalid parse results early, so the only relevant part is toList as opposed to foldMap in the original post: