Hi All,

In the best spirit of Haskelling, I thought I'd try dropping in a
completely different data structure in a spot where I thought the
existing one was (1) ugly (2) leaking memory. In particular, I wrote a
Trie implementation. Now the point is actually not much to do with the
data structure itself, but code layout. I mention this particular data
structure only because it is the one I was working on, but it seems to
come up quite often.

Consider the following function:

data Trie t = Empty | Trie (TriePtr t) (MaybePtr t) (TriePtr t)
type TriePtr t = TVar (Trie t)
type MaybePtr t = TVar (Maybe t)

data Bit = Zero | One
   deriving Show

dmin p = do
   mv <- dmin' p
   case mv of
       Nothing -> error "dmin: no values"
       Just (v,_) -> return v

dmin' p = do
   t <- readTVar p
   case t of
       Empty -> return Nothing
       Trie l m r -> do
           mv <- dmin' l
           case mv of
               Nothing -> do
                   mv <- readTVar m
                   case mv of
                       Nothing -> do
                           mv <- dmin' r
                           case mv of
                               Nothing -> error "emit nasal daemons"
                               Just (v,e) -> do
                                   if e
                                       then writeTVar p Empty
                                       else return ()
                                   return mv
                       Just v -> do
                           re <- null r
                           case re of
                               False -> writeTVar m Nothing
                               True  -> writeTVar p Empty
                           return (Just (v,re))
               Just (v,e) -> do
                   case e of
                       True -> do
                           me <- empty m
                           re <- null r
                           case me && re of
                               False -> writeTVar m Nothing
                               True  -> writeTVar p Empty
                           return (Just (v,me && re))
                       False -> return mv
   where
   empty m = do
       v <- readTVar m
       case v of
           Nothing -> return True
           Just _  -> return False

All that case analysis causes indentation to creep, and lots of
vertical space "feels" wasted. Is that just a fact of life, or is
there Haskellmagic that I still need to learn?

cheers,
T.
--
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to