[Haskell-cafe] Looking for suggestions to improve my algorithm

Ryan Ingram ryani.spam at gmail.com
Wed Aug 29 19:39:16 EDT 2007


The algorithm I would use:

Treat the problem as a directed graph of 1 million vertices where each
vertex has at most 1 outgoing edge.  Each vertex is labeled with a
number N(v).

For each vertex v, if sum(divisors(N(v))) <= 1 million, that vertex has an
outgoing edge to vertex v', where N(v') == sum(divisors(N(v))).

Call this graph G0.

1) No vertex with 0 incoming edges can be part of an amicable chain.
2) No vertex with 0 outgoing edges can be part of an amicable chain.

If there are any such vertices in the graph, you can remove them.  Call this
new graph G1.

Lemma 3) G1 is a directed graph where every vertex has at most one outgoing
edge.
Proof) G0 has this property and we have only deleted vertices from G0, which
can only remove the

You can repeat this process until no such vertices remain.  Call the final
resultant graph Gn.

Lemma 4) Each vertex in Gn has exactly 1 incoming edge and exactly 1
outgoing edge.
Proof:
   1) No vertex has 0 incoming edges or else we would have removed it above.
   2) Pidgeonhole principle:  There are exactly as many edges as vertices.
If any vertex had 2 incoming edges, there must be at least one vertex with 0
incoming vertices.

Leamma 5) Each vertex in Gn is part of exactly one cycle.
Proof) Follow the outgoing vertex chain from a vertex.  Since Gn is finite
and each vertex has exactly 1 incoming & 1 outgoing edge, eventually you
will return to that vertex.  This forms a cycle and there were no other
possible edges to follow.

Therefore: Algorithm:
1) Generate G0
2) Iteratively remove vertices from G0 to create G1, G2, etc. until there
are no vertices with 0 incoming or outgoing edges.  Let this graph be Gn
3) Split the vertices of Gn into equivalence classes where each class
represents a cycle
4) Find the largest equivalence class.
5) Find the smallest label in that equivalence class.

As to how to profile:
> ghc --make -auto-all -prof -O2 main.hs
> main +RTS -p
will generate a profile report in main.prof.  I've found that functions that
do a large amount of allocation tend to be the easiest to optimize.  Adding
additional strictness annotations (seq) sometimes helps.

For constructing graphs, you may want to look at
http://www.haskell.org/haskellwiki/Tying_the_Knot

as an alternative to the "IsSeen" maps that you might use to iteratively
construct a graph.

I'd probably use something like this:

type Graph a = Map a Vertex
data Vertex a = Vertex a [Vertex a]

instance Eq a => Eq (Vertex a) where
  Vertex a _ == Vertex b _ = a == b

then:
constructGraph :: Ord a => (a -> Graph a -> [Vertex a]) -> [a] -> Graph a
constructGraph mkEdges labels = graph where
  graph = Map.fromList [(label, Vertex label (mkEdges label graph)) | label
<- labels]

Notice that graph is used in its own definition!

You can picture this as first creating a map like this:
1 -> Vertex 1 _
2 -> Vertex 2 _
3 -> Vertex 3 _
...

Then when you query the map for the edges of Vertex 2, only then does the
mkEdges get called, with the constructed graph as input, updating the "_"
with pointers to the actual vertices.

 -- ryan
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070829/49a237ef/attachment.htm


More information about the Haskell-Cafe mailing list