Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Accidentally backticking a non-binary function creates bizarre behaviour

Tags:

haskell

Here's the offending code (also on lpaste.net):

module Data.Graph.Dijkstra
       ( dijkstra
       , dijkstraPath
       ) where

-- Graph library import
import Data.Graph.Inductive hiding (dijkstra)

-- Priority queue import
import qualified Data.PQueue.Prio.Min as PQ

-- Standard imports
import Data.List (find)
import Data.Maybe (fromJust)
import Data.Monoid

-- Internal routine implementing Dijkstra's shortest paths
-- algorithm. Deemed internal because it needs to be kickstarted with
-- a singleton node queue. Based on FGL's current implementation of
-- Dijkstra.
dijkstraInternal ::
  (Graph gr, Ord b, Monoid b) => gr a b -> PQ.MinPQueue b [Node] -> [[Node]]
dijkstraInternal g q
  | PQ.null q = []
  | otherwise =
    case match v g of
      (Just cxt,g') -> p:dijkstraInternal  g' (PQ.unions (q' : expand cxt minDist p))
      (Nothing, g') -> dijkstraInternal g' q'
  where ((minDist,p@(v:_)), q') = PQ.deleteFindMin q
        expand (_,_,_,s) dist pathToC =
          map (\(edgeCost,n) -> PQ.singleton (dist `mappend` edgeCost) (n:pathToC)) s

-- Given a graph and a start node, returns a list of lists of nodes
-- corresponding to the shortest paths from the start to all other
-- nodes, where the edge costs are accumulated according to the Monoid
-- instance of the edge label type and costs are compared by the edge
-- label's Ord instance.
dijkstra :: (Graph gr, Ord b, Monoid b) => gr a b -> Node -> [[Node]]
dijkstra g start = dijkstraInternal g (PQ.singleton `mempty` [start])  -- !!!

dijkstraPath :: (Graph gr, Ord b, Monoid b) => gr a b -> Node -> Node -> [LNode a]
dijkstraPath g start goal =
  let paths = dijkstra g start
      pathNodes  = find ((goal ==) . head) paths -- Can paths be empty?
  in
   case pathNodes of
     Nothing -> []
     Just ps -> reverse $ map (\n -> (n, fromJust $ lab g n)) ps

The weirdness is in line 39, marked with the -- !!! comment. This code compiles, but the runtime error is that no matter what, the PQ.singleton function returns an empty priority queue. I realized I had accidentally added backticks to mempty, so when I removed those the code compiled and worked as expected.

This however struck me as strange. How could the code have correctly compiled with backticks around mempty, which is not a binary function at all (mempty :: a)?

After some very generous help on #haskell, I found that it had something to do with the Monoid instance for functions:

instance Monoid b => Monoid (a -> b)

I now have an extremely vague understanding of why this error successfully typechecked, but I still feel somehow morally wronged. Can someone explain exactly how this happened?

Additionally, I'd also like to direct attention to the priority queue's singleton function that I'm using: according to the source, it doesn’t return an empty queue. However, at line 24, that same priority queue immediately gets evaluated as being empty. (I verified this with trace calls.)

like image 888
giogadi Avatar asked Dec 05 '22 08:12

giogadi


2 Answers

So, in general, the code:

a `f` b

is just syntactic sugar for:

f a b

Therefore your code became:

mempty PQ.singleton [start]

So the type-checker inferred the type for that particular mempty:

mempty :: (k -> a -> PQ.MinPQueue k a) -> [Node] -> PQ.MinPQueue b [Node]

You correctly found the right instance that is the problem. Anything of type a -> b is a Monoid, provided that b is. So let's bracket that type above:

mempty :: (k -> a -> PQ.MinPQueue k a) -> ([Node] -> PQ.MinPQueue b [Node])

So, that type can be a Monoid if [Node] -> PQ.MinPQueue b [Node] is a Monoid. And by the same logic, [Node] -> PQ.MinPQueue b [Node] can be a Monoid if PQ.MinPQueue b [Node] is one. Which it is. So the type-checker is fine with this code.

Presumably the implementation of our troublesome instance is:

instance Monoid => Monoid (a -> b) where
  mempty = const mempty

So overall, you get an empty priority queue. So really, I think it comes down to a question of whether it was wise for the designers to include this instance at all. Its net effect is that any function returning a monoid can be a monoid, which should allow you to combine the results. The more useful case here is mappend, which can append two a -> b functions by applying them both and using mappend to combine the results. For example:

extremes = (return . minimum) `mappend` (return . maximum)

rather than:

extremes xs = [minimum xs, maximum xs]

Hmmm, maybe someone else can produce a sensible terser example.

like image 68
Neil Brown Avatar answered May 31 '23 05:05

Neil Brown


So backticks turn a binary function into an infix operator, making

x `op` y

equivalent to

op x y

So op needs to be of type a -> b -> c where x :: a and y :: b.

In your case, op was mempty, with the type Monoid m => m. But we know it to be of the form a -> b -> c, so substitute that and you get (this is no longer valid syntax) Monoid (a -> b -> c) => a -> b -> c, because we can substitute that m for anything as long as the constraint holds.

Now we know (due to the instance declaration) that any function of the form s -> t, where t is a Monoid, is a Monoid itself, and we also know that a -> b -> c is really a -> (b -> c), i.e. a function taking one argument and returning another function. So if we substitute a for s and (b -> c) for t, the we fulfill the Monoid instance, if t is a Monoid. Of course, t is (b -> c), so we can apply the same Monoid instance again (with s = b and t = c), so if c is a Monoid, we're good.

So what is c? The expression you had was

PQ.singleton `mempty` [start]

i.e.

mempty PQ.singleton [start]

The instance declaration for Monoid (a -> b) defines mempty _ = mempty, i.e. it's a function that ignores its argument and returns the empty element of the b Monoid. In other words, we can expand the call above to

mempty [start]

i.e. we ignore the argument and use mempty of the inner Monoid (which is b -> c). Then we repeat, ignoring the argument again:

mempty

So the expression you had is just equivalent to a single mempty, which has the type Monoid c => c, i.e. it can be any Monoid whatsoever.

In your case, the larger expression deduces c to be a PQ.MinPQueue. And MinPQueue is a Monoid instance with mempty being the empty queue.

This is how you end up with the result you're seeing.

like image 29
Sebastian Redl Avatar answered May 31 '23 06:05

Sebastian Redl