search Data.Tree.Zipper

Hi, There doesn't seem to be a function to search the tree so I come up with following function: searchTree :: (a -> Bool) -> TreeLoc a -> Maybe (TreeLoc a) searchTree pred rootLoc = if pred (getLabel rootLoc) then Just rootLoc else case firstChild rootLoc of Just loc -> case searchTree pred loc of Just loc -> Just loc Nothing -> case right loc of Just rLoc -> searchTree pred rLoc Nothing -> Nothing Nothing -> Nothing Which feels quite ugly. Any suggestions? Thanks. Jian

I haven't tested it, but I think you're looking for something like this:
searchTree2 :: (a -> Bool) -> TreeLoc a -> Maybe (TreeLoc a)
searchTree2 pred rootLoc =
if pred (getLabel rootLoc)
then Just rootLoc
else firstChild rootLoc >>= siblings
where siblings loc = searchTree2 pred loc `mplus`
(searchTree2 pred =<< right loc)
On Mon, Mar 8, 2010 at 1:11 PM, Jian Fan
Hi,
There doesn't seem to be a function to search the tree so I come up with following function:
searchTree :: (a -> Bool) -> TreeLoc a -> Maybe (TreeLoc a) searchTree pred rootLoc = if pred (getLabel rootLoc) then Just rootLoc else case firstChild rootLoc of Just loc -> case searchTree pred loc of Just loc -> Just loc Nothing -> case right loc of Just rLoc -> searchTree pred rLoc Nothing -> Nothing Nothing -> Nothing
Which feels quite ugly. Any suggestions? Thanks.
Jian
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks. `mplus` is the glue I was looking for. The original algorithm
has a bug. Following is what I have for now:
searchTree pred rootLoc
| pred (getLabel rootLoc) = Just rootLoc
| otherwise = (right rootLoc >>= searchTree pred)
`mplus` (firstChild rootLoc >>= searchTree pred)
Jian
MightyByte
I haven't tested it, but I think you're looking for something like this:
searchTree2 :: (a -> Bool) -> TreeLoc a -> Maybe (TreeLoc a) searchTree2 pred rootLoc = if pred (getLabel rootLoc) then Just rootLoc else firstChild rootLoc >>= siblings where siblings loc = searchTree2 pred loc `mplus` (searchTree2 pred =<< right loc)
On Mon, Mar 8, 2010 at 1:11 PM, Jian Fan
wrote: Hi,
There doesn't seem to be a function to search the tree so I come up with following function:
searchTree :: (a -> Bool) -> TreeLoc a -> Maybe (TreeLoc a) searchTree pred rootLoc = if pred (getLabel rootLoc) then Just rootLoc else case firstChild rootLoc of Just loc -> case searchTree pred loc of Just loc -> Just loc Nothing -> case right loc of Just rLoc -> searchTree pred rLoc Nothing -> Nothing Nothing -> Nothing
Which feels quite ugly. Any suggestions? Thanks.
Jian
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I think you want find :: Foldable t => (a -> Bool) -> t a -> Maybe a Jian Fan wrote:
Hi,
There doesn't seem to be a function to search the tree so I come up with following function:
searchTree :: (a -> Bool) -> TreeLoc a -> Maybe (TreeLoc a) searchTree pred rootLoc = if pred (getLabel rootLoc) then Just rootLoc else case firstChild rootLoc of Just loc -> case searchTree pred loc of Just loc -> Just loc Nothing -> case right loc of Just rLoc -> searchTree pred rLoc Nothing -> Nothing Nothing -> Nothing
Which feels quite ugly. Any suggestions? Thanks.
Jian
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I somehow cannot figure this out. Tree is Foldable so I
can use "find" on it. But how can I use find on TreeLoc?
Am I missing something obvious?
Dan Weston
I think you want
find :: Foldable t => (a -> Bool) -> t a -> Maybe a
Jian Fan wrote:
Hi,
There doesn't seem to be a function to search the tree so I come up with following function:
searchTree :: (a -> Bool) -> TreeLoc a -> Maybe (TreeLoc a) searchTree pred rootLoc = if pred (getLabel rootLoc) then Just rootLoc else case firstChild rootLoc of Just loc -> case searchTree pred loc of Just loc -> Just loc Nothing -> case right loc of Just rLoc -> searchTree pred rLoc Nothing -> Nothing Nothing -> Nothing
Which feels quite ugly. Any suggestions? Thanks.
Jian
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Jian Fan wrote:
I somehow cannot figure this out. Tree is Foldable so I can use "find" on it. But how can I use find on TreeLoc? Am I missing something obvious?
But what exactly is a "TreeLoc"? Hoogle doesn't know about it. If you created it yourself, you haven't showed us how you defined it or what you are using it for. In any case, below is one way to simplify the code you posted. It is only a small simplification, but it is about the best I can do without seeing the details of what you are trying to do. Try posting this kind of question to the "haskell-beginners" mailing list. There are people there who are much better at answering this kind of question. One thing that made it hard to follow your code was your repeated use of "loc", one shadowing the other. Try to avoid that. searchTree :: (a -> Bool) -> TreeLoc a -> Maybe (TreeLoc a) searchTree pre rootLoc | pred (getLabel rootLoc) = Just rootLoc | otherwise = do loc <- firstChild rootLoc searchTree pred loc `mplus` (right loc >>= searchTree pred) Regards, Yitz

Well, TreeLoc comes from Data.Tree.Zipper which comes from rosezipper
packge. Thank you and MightyByte. Its much improved now.
Jian
Yitzchak Gale
Jian Fan wrote:
I somehow cannot figure this out. Tree is Foldable so I can use "find" on it. But how can I use find on TreeLoc? Am I missing something obvious?
But what exactly is a "TreeLoc"? Hoogle doesn't know about it. If you created it yourself, you haven't showed us how you defined it or what you are using it for.
In any case, below is one way to simplify the code you posted. It is only a small simplification, but it is about the best I can do without seeing the details of what you are trying to do.
Try posting this kind of question to the "haskell-beginners" mailing list. There are people there who are much better at answering this kind of question.
One thing that made it hard to follow your code was your repeated use of "loc", one shadowing the other. Try to avoid that.
searchTree :: (a -> Bool) -> TreeLoc a -> Maybe (TreeLoc a) searchTree pre rootLoc | pred (getLabel rootLoc) = Just rootLoc | otherwise = do loc <- firstChild rootLoc searchTree pred loc `mplus` (right loc >>= searchTree pred)
Regards, Yitz
participants (4)
-
Dan Weston
-
Jian Fan
-
MightyByte
-
Yitzchak Gale