[Haskell-cafe] Re: Indentation Creep

apfelmus apfelmus at quantentunnel.de
Sat Jul 14 06:42:23 EDT 2007


Thomas Conway wrote:
> The motivation for this structure is that I wanted a queue, from which
> I could remove elements from the middle efficiently,
>
> Anyway, the point of the original post was to find tricks for avoiding
> indentation creep, rather than the trie itself.

Knowing that it's a trie to be used as priority queue makes things a lot
easier, no need to figure out myself what exactly  dmin  does :)

Dan Doel wrote:
> newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
>
> instance Monad m => MonadPlus (MaybeT m) where
>     mzero = MaybeT $ return Nothing
>     m1 `mplus` m2 = MaybeT $ liftM2 mplus (runMaybeT m1) (runMaybeT m2)

  lift :: Monad m => m a -> MaybeT m a
  lift = MaybeT . liftM Just

The Maybe monad transformer does the job, `mplus` is what you want:

  deletemin :: TVar (Trie t) -> STM (Maybe t)
  deletemin = runMaybeT delmin'
    where

    delminMaybe p = readTVar p >>= \t -> case t of
       Nothing    -> mzero
       Just v     -> (lift $ writeTVar p Nothing) >> return v

    delmin'     p = readTVar p >>= \t -> case t of
       Empty      -> mzero
       Trie l m r ->
            delmin' l `mplus` delminMaybe m `mplus` delmin' r
         `mplus` (lift (writeTVar p Empty) >> mzero)

Note that the step of replacing a trie with empty children with the
constructor Empty is delayed since this is nicer to write down :)

Regards,
apfelmus



More information about the Haskell-Cafe mailing list