[Haskell-cafe] Re: inversion lists

Daniel Fischer daniel.is.fischer at web.de
Tue Dec 1 19:12:23 EST 2009


Am Dienstag 01 Dezember 2009 23:31:10 schrieb Ted Zlatanov:
> On Fri, 20 Nov 2009 15:30:49 -0600 Ted Zlatanov <tzz at lifelogs.com> wrote:
>
> TZ> A nice property of inversion lists is that inverting them simply
> TZ> requires removing or adding the minimum possible value at the beginning
> TZ> of the list.  A membership test requires traversal but since the list
> is TZ> sorted we know when to stop if it doesn't exist.  Set union and TZ>
> difference are pretty tricky but at least can stop early if one of two TZ>
> sets is finite.  As I learn more Haskell I'll try implementing these TZ>
> step by step.  Is there any interest in making this an actual module or TZ>
> is it not very useful in the context of Haskell?
>
> OK, here's my current state.  The first two functions are not mine, of
> course (the original invlist' was called h, that's all).
>
> invlist_negate just appends 0 or removes it.  I think the first
> condition (on an empty list) is not necessary.  Should I keep it for
> clarity?

I don't think it's necessary.
As Sjoerd mentioned, the use of 0 is problematic.

>
> For invlist_member I basically pass the current state down into the
> recursion chain on invlist_member'.  The function will end early if it
> can, or it will scan all the way down the list in the worst case (when
> the goal value is greater than the last interval marker).  I think I
> could do it with a foldl but I wasn't able to figure it out.
>
> Any suggestions are welcome.  I can definitely reimplement the invlist
> function similarly to invlist_member, by passing an exclusion state
> boolean down, which will make the code longer.  I'm not sure if it will
> be bad for performance.  I think it will be better because I'll be able
> to do it lazily as opposed to the foldr below which needs a finite list.

No, quite the opposite. foldr is wonderful for lazy list processing.
I just need to make my function a wee bit lazier:

Prelude> let h x zs = x:case zs of { (y:ys) | x+1 == y -> ys; _ -> (x+1):zs; }
Prelude> let invlist xs = foldr h [] xs
Prelude> invlist [1,2,3,7,8,12,13,14,20]
[1,4,7,9,12,15,20,21]
Prelude> take 10 $ invlist [2,5 .. ]
[2,3,5,6,8,9,11,12,14,15]
Prelude> take 10 $ invlist [2,4 .. ]
[2,3,4,5,6,7,8,9,10,11]
Prelude> take 10 $ invlist [2 .. ]
[2^CInterrupted.
Prelude> take 10 $ invlist [2 :: Data.Int.Int16 .. ]
[2,-32768]
-- That's a problem here

Hadn't thought about infinite (or even long) lists when I wrote it.

> Can I do it with a direct foldl instead?

No, foldl cannot produce anything before the whole list has been traversed, so it can't 
deal with infinite lists at all.

> I need to look at it
> carefully but maybe someone has a suggestion.
>
> I plan to do set operations after I get the basics right :)
>
> This should really have been in comp.lang.haskell.beginner.  Sorry for
> the elementary stuff, I'm keeping the thread in c.l.h.cafe only to avoid
> double postings at this point.
>
> Thanks
> Ted
>
> invlist' :: Num a => a -> [a] -> [a]
> invlist' x (y:ys)
>
>          | x+1 == y = x:ys
>
> invlist' x zs = x:(x+1):zs

invlist' :: Integral a => a -> [a] -> [a]
invlist' x zs = x:ws
    where
      ws = case zs of
              (y:ys) | x+1 == y -> ys
              _ -> (x+1):zs

-- we could use Num here, but for an implementation of sets via inversion lists,
-- Integral is the appropriate setting. Perhaps even better use Integral and Bounded

invlist' :: (Integral a, Bounded a) => a -> [a] -> [a]
invlist' x _
    | x == maxBound = [x]
invlist' x zs = x:ws
    where
      ws = case zs of
              (y:ys) | x+1 == y -> ys
              _ -> (x+1):zs


Now:
Prelude> invlist [2 :: Data.Int.Int8 .. ]
[2]

:D
>
Don't forget a type signature here. Otherwise you'll get bitten by the monomorphism 
restriction.
invlist :: (Integral a, Bounded a) => [a] -> [a]
> invlist = foldr invlist' []
>

Problem. That is only sensible if we only consider sets of nonnegative numbers.
For Integral and Bounded,

invlist_negate (x:xs)
    | x == minBound = xs
invlist_negate xs = minBound:xs

> invlist_negate [] = [0]
> invlist_negate (0:xs) = xs
> invlist_negate xs = 0:xs
>
> invlist_member _ [] = False
>
> -- bootstrap membership test with a False exclusion state (an inversion
> list begins with the first included value) invlist_member goal (x:xs) =
> invlist_member' goal False (x:xs)
>
> invlist_member' goal exclude (x:xs) =
>     if goal < x then
>        exclude
>     else
>         invlist_member' goal (not exclude) xs -- flip the exclusion state
> of the list
>
> invlist_member' _ exclude _ = exclude       -- if we can't match one more
> element, return the current exclusion state

invlist_member :: (Integral a, Bounded a) => a -> [a] -> Bool
invlist_member goal = foldr (\n b -> if goal < n then False else not b) False

*maybe* I'll think about unions, intersections and other set operations as foldr's.



More information about the Haskell-Cafe mailing list