[Haskell-cafe] Why is this strict in its arguments?

Paulo J. Matos pocm at soton.ac.uk
Wed Dec 5 11:41:32 EST 2007


On Dec 5, 2007 1:51 PM, Luke Palmer <lrpalmer at gmail.com> wrote:
>
> On Dec 4, 2007 9:41 PM, Paulo J. Matos <pocm at soton.ac.uk> wrote:
> > Hello all,
> >
> > As you might have possibly read in some previous blog posts:
> > http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10
> > http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11
> >
> > we (the FPSIG group) defined:
> > data BTree a = Leaf a
> >                    | Branch (BTree a) a (BTree a)
> >
> > and a function that returns a list of all the paths (which are lists
> > of node values) where each path element makes the predicate true.
> > findAllPath :: (a -> Bool) -> (BTree a) -> Maybe [[a]]
> > findAllPath pred (Leaf l) | pred l = Just [[l]]
> >                           | otherwise = Nothing
> > findAllPath pred (Branch lf r rt) | pred r = let lfpaths = findAllPath pred lf
> >                                                  rtpaths = findAllPath pred rt
> >                                              in
> >                                                if isNothing lfpaths &&
> > isNothing rtpaths
> >                                                then Nothing
> >                                                else
> >                                                    if isNothing lfpaths
> >                                                    then Just (map (r:)
> > $ fromJust rtpaths)
> >                                                    else
> >                                                        if isNothing rtpaths
> >                                                        then Just (map
> > (r:) $ fromJust lfpaths)
> >                                                        else Just (map
> > (r:) $ fromJust rtpaths ++ fromJust lfpaths)
> >                                   | otherwise = Nothing
>
> I don't think this evaluates the whole tree every time, but it
> certainly evaluates more than it needs to.  It has to do with an extra
> check.  Here's a very operational description:
>
> First note that if findAllPath returns Nothing, then it has evaluated
> the tree down to the contour where all the preds are false.  Let's
> suppose that this is the best possible case, where there is a path
> down the left side of the tree with no backtracking where all nodes
> are true.
>
> findAllPath pred (Leaf l) = Just [[l]]
>
> Now:
>
> if isNothing lfpaths && ...   -- false already, lfpaths is a Just, go
> to else branch
> else if isNothing lfpaths ... -- false again, go to else branch
> else if isNothing rtpaths ...
>
> To check this, you have to evaluate rtpaths down to its false contour
> before you can proceed.  You didn't need to do this.  Instead, writing
> the last else as:
>
> else Just (map (r:) $ fromJust lfpaths ++ fromMaybe [] rtpaths)
>
> Will get you behavior -- I think -- equivalent to the original.
> Except for that it will return paths in leftmost order rather than
> rightmost.  But changing the order of some of those checks will get
> you back the original rightmost behavior and lazy semantics.  Left as
> an exercise for the OP :-)
>

Oh, ok! :)

I think I got it now!
Thank you!

Cheers,

Paulo Matos

> Luke
>
> > Later on we noticed that this could be simply written as:
> > findAllPath :: (a -> Bool) -> (BTree a) -> [[a]]
> >       findAllPath pred = g where
> >           g (Leaf l) | pred l = [[l]]
> >           g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred
> > lf) ++ (findAllPath pred rt)
> >           g _  = []
> >
> > without even using maybe. However, 2 questions remained:
> > 1 - why is the first version strict in its arguments?
> > 2 - if it really is strict in its arguments, is there any automated
> > way to know when a function is strict in its arguments?
> >
> > Cheers,
> >
> > --
> > Paulo Jorge Matos - pocm at soton.ac.uk
> > http://www.personal.soton.ac.uk/pocm
> > PhD Student @ ECS
> > University of Southampton, UK
>
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
>
>



-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK


More information about the Haskell-Cafe mailing list