MathGroup Archive 2009

[Date Index] [Thread Index] [Author Index]

Search the Archive

Re: Re: Re: mergeSort with ReplaceRepeated

  • To: mathgroup at smc.vnet.net
  • Subject: [mg100849] Re: [mg100826] Re: [mg100820] Re: mergeSort with ReplaceRepeated
  • From: Leonid Shifrin <lshifr at gmail.com>
  • Date: Tue, 16 Jun 2009 21:50:58 -0400 (EDT)
  • References: <h0vtii$737$1@smc.vnet.net> <200906150121.VAA11576@smc.vnet.net>

Hi Luca,

I already replied to your post some days ago with a complete implementation.
In case you did not see it, I repeat it here:

Clear[toLinkedList];
toLinkedList[x_List] := Fold[{#2, #1} &, {}, Reverse[x]];


Module[{h, lrev},
  mergeLinked[x_h, y_h] :=
   Last[{x, y,
      h[]} //. {{fst : h[hA_, tA_h], sec : h[hB_, tB_h], e_h} :>
       If[hA > hB, {tA, sec, h[hA, e]}, {fst, tB, h[hB, e]}], {fst :
         h[hA_, tA_h], h[], e_h} :> {tA, h[], h[hA, e]}, {h[],
        sec : h[hB_, tB_h], e_h} :> {h[], tB, h[hB, e]}}];

  lrev[set_] :=
   Last[h[set, h[]] //. h[h[hd_, tl_h], acc_h] :> h[tl, h[hd, acc]]];

  sort[lst_List] :=
   Flatten[Map[h[#, h[]] &, lst] //.
     x_List :>
      Flatten[{toLinkedList@x, {}} //. {{hd1_, {hd2_, tail_List}},
          accum_List} :> {tail, {accum, lrev@mergeLinked[hd1, hd2]}}],
     Infinity, h]];


It uses linked list structure {a,{b,{c,{...}}}} to achieve expected N log N
complexity, that you won't achieve by naive pattern matching like you did in
your attempts, since lists are implemented as arrays in Mathematica  and the
whole array is copied at each pattern match for patterns like
{first_,rest___}. Here is, for example, a naive implementation of merge,
which will work if your lists' elements are not lists themselves (this
limitation can be easily removed if needed):

Clear[merge];
merge[x_List, y_List] :=
 Block[{merge},
  Flatten[merge[x, y] //. {merge[{a_, b___}, {c_, d___}] :>
      If[a < c, {a, merge[{b}, {c, d}]}, {c, merge[{a, b}, {d}]}],
     merge[{}, {a__}] :> {a}, merge[{a__}, {}] :> {a}}]]

which uses more or less the pattern - matching you tried ( I used Block
trick to avoid using separate names for a function and rule pattern). You
can do simple benchmarks with sorted random lists to see that it has awful
performance (assuming N = Length[x] and M = Length[y], I expect something
like O(N^2+M^2)).

For details on the linked list - based implementation, look at the previous
post of mine, or another recent one on a related topic of recursive Select
implementation. To get familiar with linked lists in Mathematica, look at
the book of David Wagner (our of print alas), online notes on efficient data
structures in Mathematica by Daniel Lichtblau, and at my book (
http://mathprogramming-intro.org/book/node525.html), or you can ask more
specific questions and I  or other people here will try to answer.

Generally one must be careful with ReplaceRepeated not to produce
inefficient solutions. You  can look for instance at

http://mathprogramming-intro.org/book/node153.html,
http://mathprogramming-intro.org/book/node245.html

in my book, where efficiency issues related to ReplaceRepeated are
discussed. At the same  time, I think it is a good exercise to make several
RR - based implementations of some standard problems like mergesort - this
may enable you to better understand the rule-based layer of Mathematica,
which is IMO its most important and fundamental layer (as compared to
functional and imperative ones).


Regards,
Leonid



On Mon, Jun 15, 2009 at 2:36 AM, Luca Bedogni <bedogni.luca at gmail.com>wrote:

> Well, it is not really an homework. I'm trying to understand Mathematica,
> and now I want to learn the replacerepeated mechanism. Googling around, I
> found some exercises, and one is to make a mergesort function using
> replacerepeated, and that was my question.
>
> Thank you
> --
> Luca Bedogni
>
>
> 2009/6/15 Sjoerd C. de Vries <sjoerd.c.devries at gmail.com>
>
> > Judging from your June 6 post, this is a homework assignment of yours.
> > I guess that given the code below you haven't learned enough of the
> > Mathematica language to come even close to solving it.
> >
> > Since it is not the goal of this group to make your homework, I can
> > only advise you to learn the basics using the documentation included
> > with Mathematica before you endeavour in the more complicated stuff.
> >
> > The code below doesn't work for one thing because it doesn't contain
> > an actual function definition. This is usually done using Set (=) or
> > SetDelayed (:=). Look them up in the documentation.
> >
> > Cheers -- Sjoerd
> >
> > On Jun 13, 12:04 pm, Luca Bedogni <bedogni.l... at gmail.com> wrote:
> > > Hi
> > >    I'm writing an implementation of mergesort using replacerepeated.
> > > This is actually the code:
> > > merge[{a1, arest___}, b : {b1, ___}] /; a1 >= b1 //. {merge[a1, arest,
> =
> > b1]
> > > :> merge[b1, a1, arest] };
> > > but it doesn't work, and I don't know why, because I'm really new to
> > > Mathematica.
> > >
> > > Any clue?
> > >
> > > Regards
> > > --
> > > Luca Bedogni
> >
>


  • Prev by Date: Re: weird escaping problem with StringPattern inside Module[]
  • Next by Date: Re: What should be a simple task....
  • Previous by thread: Re: mergeSort with ReplaceRepeated
  • Next by thread: Re: MergeSort with replacerepeated - a follow-up