On 14.07.2013 13:20, Niklas Hambüchen wrote:
I've taken the Ord-based O(n * log n) implementation from yi using a Set:

   ordNub :: (Ord a) => [a] -> [a]
   ordNub l = go empty l
     where
       go _ []     = []
       go s (x:xs) = if x `member` s then go s xs
                                     else x : go (insert x s) xs

(The benchmark also shows some other potential problem: Using a state
monad to keep the set instead of a function argument can be up to 20
times slower. Should that happen?)

I cannot say whether this should happen, but your code about can be straight-forwardly refactored using a *Reader* monad.

import Control.Monad.Reader

import Data.Functor ((<$>))
import qualified Data.Set as Set

-- ifM still not in Control.Monad
ifM mc md me = do { c <- mc; if c then md else me }

ordNub :: (Ord a) => [a] -> [a]
ordNub l = runReader (go l) Set.empty
  where
    go []     = return []
    go (x:xs) = ifM ((x `Set.member`) <$> ask)
                    (go xs)
                    ((x :) <$> local (Set.insert x) (go xs))

test = ordNub [1,2,4,1,3,5,2,3,4,5,6,1]

Of course, this does not lend itself to an application of filterM.

In fact, your implementation is already in the (Set a ->) reader monad, in normalized form. It looks already optimal to me.

Cheers,
Andreas

--
Andreas Abel  <><      Du bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to