[Haskell-cafe] List fusion of nested lists

2011-12-01 Thread Joachim Breitner
Dear Cafe,

I’m trying to exploit list fusion as provided by GHC (build/foldr). One
function that I want to get fusable is this, it splits a list of
integeres into maximal monotonous subsequences:

streaks :: [Integer] - [[Integer]]
streaks [] = []
streaks (x:xs) = let (this,rest) = oneStreak (x:xs)
 in this:streaks rest

oneStreak :: [Integer] - ([Integer], [Integer])
oneStreak [x] = ([x],[])
oneStreak l@(x:y:_) = splitWhile2 (\a b - a `compare` b == x `compare` y) l

splitWhile2 :: (Integer - Integer - Bool) - [Integer] - ([Integer], 
[Integer])
splitWhile2 p [x] = ([x],[])
splitWhile2 p (x:y:xs) | p x y = let (s,r) = splitWhile2 p (y:xs) in (x:s,r)
   | otherwise = ([x],y:xs) 


Now I’d like to implement streaks in terms of build and foldr such that
it is subject to list fusion. Especially, when used in
concatMap (streaks . func) :: [X] - [[Integer]]
where
func :: X - [Integer]
is implemented with buildr, this should ideally remove all intermediate
lists.

Can this be done with list fusion at all? How would I go about it?

If the above example is too complicated, known how it would work for
Data.List.group would help me already a lot.

Greetings,
Joachim


-- 
Joachim nomeata Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List fusion of nested lists

2011-12-01 Thread Joachim Breitner
Hi,

Am Donnerstag, den 01.12.2011, 11:28 +0100 schrieb Joachim Breitner:
 Now I’d like to implement streaks in terms of build and foldr such that
 it is subject to list fusion.

one half of the task is quite doable:

streaks' :: [Integer] - [[Integer]]
streaks' xs = foldr streaksF [] xs

streaksF :: Integer - [[Integer]] - [[Integer]]
streaksF i [] = [[i]]
streaksF i ([x]:ys) = [i,x]:ys
streaksF i ((x1:x2:xs):ys) = if i `compare` x1 == x1 `compare`
x2
 then (i:x1:x2:xs):ys
 else [i]:(x1:x2:xs):ys

so I can make streaks a somewhat well-behaving consumer. The task to
create the lists using build remains.

(The function only works correctly on lists where no two adjacent
elements are the same, and it behaves differently than the code in the
first mail on [2,1,2]; it builds [[2],[1,2]] instead of [[2,1],2]. That
is ok for my purposes.)

Greetings,
Joachim

-- 
Joachim nomeata Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List fusion of nested lists

2011-12-01 Thread Joachim Breitner
Hi again,

Am Donnerstag, den 01.12.2011, 11:38 +0100 schrieb Joachim Breitner:
 Am Donnerstag, den 01.12.2011, 11:28 +0100 schrieb Joachim Breitner:
  Now I’d like to implement streaks in terms of build and foldr such that
  it is subject to list fusion.
 
 one half of the task is quite doable:
 
 streaks' :: [Integer] - [[Integer]]
 streaks' xs = foldr streaksF [] xs
 
 streaksF :: Integer - [[Integer]] - [[Integer]]
 streaksF i [] = [[i]]
 streaksF i ([x]:ys) = [i,x]:ys
 streaksF i ((x1:x2:xs):ys) = if i `compare` x1 == x1 `compare`
 x2
  then (i:x1:x2:xs):ys
  else [i]:(x1:x2:xs):ys
 
 so I can make streaks a somewhat well-behaving consumer. The task to
 create the lists using build remains.

isn’t it always nice how posting questions help you think differently
about the problem? Here is the next step in the construction; ensure
that at least the outer list is subject to list fusion:

streaks'' :: [Integer] - [[Integer]]
streaks'' xs = build $ \c n -
uncurry c $ foldr (streaksF' c) ([],n) xs

streaksF' :: ([Integer] - b - b) - Integer - ([Integer],b) - 
([Integer],b)
streaksF' c i ([],ys) = ([i],ys)
streaksF' c i ([x],ys) = ([i,x],ys)
streaksF' c i ((x1:x2:xs),ys) = if i `compare` x1 == x1 `compare` x2
then (i:x1:x2:xs, ys)
else ([i], (x1:x2:xs) `c` ys)

It seems that the next steps are:
 1. Add information to the accumulator of the foldr that carries the
information that is currently obtained by pattern matching (as
we cannot look a fusioned list any more).
 2. Somehow replace the : and [] of the inner list by the functions
given by build. But have doubts that this is possible, these can
only be used inside the argument of build.

Greetings,
Joachim


-- 
Joachim Breitner
  e-Mail: m...@joachim-breitner.de
  Homepage: http://www.joachim-breitner.de
  Jabber-ID: nome...@joachim-breitner.de


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe