[fixed some typos, mainly missing primes]

  superset xs = superset' x . sort
    where
    x = sort xs

    _      `superset'`  []     = True
    []     `superset'`  _      = False
    (x:xs) `superset'` (y:ys)
        | x == y    = xs `superset'` ys
        | x <  y    = xs `superset'` (y:ys)
        | otherwise = False

del y = del_acc []
   where del_acc _ []              = mzero
         del_acc v (x:xs) | x == y = return (v++xs)
         del_acc v (x:xs)          = del_acc (x:v) xs

The algorithm is correct but it's not faster, xs `super` ys  takes
O(n*m) time whereas superset takes O(n * log n + m * log m) time given a
proper sorting algorithm. Here, n = length xs and m = length ys.

Of course, you are right. In worst case super is much slower than superset. In average case (for some assumptions about the inputs) it could perform quite well because of the chance to detect non-subset words early.

2) Put xs into a good data structure and achieve a O(m * log n) time for
multiple ys.

You mean something along

supermap xs =
    let mx      = Map.fromListWith (+) [ (x,1) | x <- xs ]
        ins _ 1 = Nothing
        ins _ v = Just (v-1)
        upd m y = case Map.updateLookupWithKey ins y m of
                   (Nothing,_ ) -> mzero
                   (_      ,m') -> return m'
    in not . null . foldM upd mx

Thanks for your time,

BR,

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to