
Fancy some Codegolf? I wrote the following function for list diagonalization:
diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) [] where sel = foldr (\a b c -> id : mrg (a c) (b c)) (const []) . map (flip id)
mrg [] ys = ys mrg xs [] = xs mrg (x:xs) (y:ys) = (x.y) : mrg xs ys
Self explanatory, isn't it? Here is a test case: *Main> take 10 $ diag [[ (m,n) | n <- [1..]] | m <- [1..]] [(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)] I was trying to golf it down [^1] but my brain explodes. If you succeed in reducing keystrokes, I'd be happy to know! Cheers, Sebastian [^1]: http://codegolf.com/

If I understand the problem correctly... Prelude> let diag = concat . diags where diags ((x:xs):xss) = [x] : zipWith (:) xs (diags xss) Prelude> take 10 $ diag [[ (m,n) | n <- [1..]] | m <- [1..]] [(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)] Sebastian Fischer wrote on 15.04.2009 14:32:
Fancy some Codegolf?
I wrote the following function for list diagonalization:
diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) [] where sel = foldr (\a b c -> id : mrg (a c) (b c)) (const []) . map (flip id)
mrg [] ys = ys mrg xs [] = xs mrg (x:xs) (y:ys) = (x.y) : mrg xs ys
Self explanatory, isn't it? Here is a test case:
*Main> take 10 $ diag [[ (m,n) | n <- [1..]] | m <- [1..]] [(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]
I was trying to golf it down [^1] but my brain explodes. If you succeed in reducing keystrokes, I'd be happy to know!
Cheers, Sebastian
[^1]: http://codegolf.com/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Why not: diag = [(x, sum-x) | sum <- [2..], x <- [1 .. sum-1]] / Emil MigMit skrev:
If I understand the problem correctly...
Prelude> let diag = concat . diags where diags ((x:xs):xss) = [x] : zipWith (:) xs (diags xss) Prelude> take 10 $ diag [[ (m,n) | n <- [1..]] | m <- [1..]] [(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]
Sebastian Fischer wrote on 15.04.2009 14:32:
Fancy some Codegolf?
I wrote the following function for list diagonalization:
diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) [] where sel = foldr (\a b c -> id : mrg (a c) (b c)) (const []) . map (flip id)
mrg [] ys = ys mrg xs [] = xs mrg (x:xs) (y:ys) = (x.y) : mrg xs ys
Self explanatory, isn't it? Here is a test case:
*Main> take 10 $ diag [[ (m,n) | n <- [1..]] | m <- [1..]] [(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]
I was trying to golf it down [^1] but my brain explodes. If you succeed in reducing keystrokes, I'd be happy to know!
Cheers, Sebastian
[^1]: http://codegolf.com/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Prelude> let diag = concat . diags where diags ((x:xs):xss) = [x] : zipWith (:) xs (diags xss)
this has a different semantics on finite lists, so I should add a test case: *Main> diag [[1,2,3],[4,5,6],[7,8,9]] [1,2,4,3,5,7,6,8,9] Your version yields [1,2,4,3,5,7]. Actually, there are a number of implementations that implement the same behaviour as the original version, e.g., diag = concat . foldr diags [] where diags [] ys = ys diags (x:xs) ys = [x] : merge xs ys merge [] ys = ys merge xs@(_:_) [] = map (:[]) xs merge (x:xs) (y:ys) = (x:y) : merge xs ys I'd be interested if one can *derive* from the original version a simpler version using clever pointfree combinators. Cheers, Sebastian

What about diag [[1,2,3],[4],[5,6,7]] ? What it should be? Sebastian Fischer wrote on 15.04.2009 15:28:
Prelude> let diag = concat . diags where diags ((x:xs):xss) = [x] : zipWith (:) xs (diags xss)
this has a different semantics on finite lists, so I should add a test case:
*Main> diag [[1,2,3],[4,5,6],[7,8,9]] [1,2,4,3,5,7,6,8,9]
Your version yields [1,2,4,3,5,7].
Actually, there are a number of implementations that implement the same behaviour as the original version, e.g.,
diag = concat . foldr diags [] where diags [] ys = ys diags (x:xs) ys = [x] : merge xs ys
merge [] ys = ys merge xs@(_:_) [] = map (:[]) xs merge (x:xs) (y:ys) = (x:y) : merge xs ys
I'd be interested if one can *derive* from the original version a simpler version using clever pointfree combinators.
Cheers, Sebastian _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, On 15.04.2009, at 13:28, Sebastian Fischer wrote:
Actually, there are a number of implementations that implement the same behaviour as the original version, e.g.,
diag = concat . foldr diags [] where
diags [] ys = ys diags (x:xs) ys = [x] : merge xs ys
merge [] ys = ys merge xs@(_:_) [] = map (:[]) xs merge (x:xs) (y:ys) = (x:y) : merge xs ys
I think your first implementation is a slightly unreadable : ) implementation of this version but uses functional lists instead of standard lists. If we replace some of the lists by functional lists we get the following diag :: [[a]] -> [a] diag = toList . concatFL . foldr diags2 [] where diags [] ys = ys diags (x:xs) ys = (x:) : merge xs ys merge [] ys = ys merge xs@(_:_) [] = map (:) xs merge (x:xs) (y:ys) = ((x:) . y) : merge xs ys with the following definitions concatFL :: [[a] -> [a]] -> [a] -> [a] concatFL = foldr (.) id toList :: ([a] -> [a]) -> [a] toList fl = fl [] Additionally we can move the 'map (:)' in merge to diags diag :: [[a]] -> [a] diag = toList . concatFL . foldr diags [] where diags [] ys = ys diags (x:xs) ys = (x:) : merge (map (:) xs) ys merge [] ys = ys merge xs@(_:_) [] = xs merge (x:xs) (y:ys) = (x . y) : merge xs ys If we now replace toList and concatFL by its definitions it looks very similar to the original implementation. diag :: [[a]] -> [a] diag = foldr (.) id (foldr diags []) [] where diags [] ys = ys diags (x:xs) ys = (x:) : merge (map (:) xs) ys merge [] ys = ys merge xs@(_:_) [] = xs merge (x:xs) (y:ys) = (x . y) : merge xs ys
diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) [] where sel = foldr (\a b c -> id : mrg (a c) (b c)) (const []) . map (flip id)
mrg [] ys = ys mrg xs [] = xs mrg (x:xs) (y:ys) = (x.y) : mrg xs ys
I guess that we can inline diags and get the definition above but I am kind of stuck here. Cheers, Jan

I think this has the semantics you're looking for. (it would probably be somewhat prettier if "mappend" wasn't such an ugly identifier (compared to, say, (++)), but this is just me trying to sneak a shot in against the Monoid method's names ;) ghci> let diag = foldr (curry (prod mappend fst snd . uncurry (coprod mappend (splitAt 2) (splitAt 1)))) [] ghci> diag [[1,2,3],[4,5,6],[7,8,9]] [1,2,4,3,5,7,6,8,9] ghci> diag [[1,2,3],[4],[5,6,7]] [1,2,4,3,5,6,7] On Wed, Apr 15, 2009 at 5:32 AM, Sebastian Fischer < sebf@informatik.uni-kiel.de> wrote:
Fancy some Codegolf?
I wrote the following function for list diagonalization:
diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) [] where sel = foldr (\a b c -> id : mrg (a c) (b c)) (const []) . map (flip id)
mrg [] ys = ys mrg xs [] = xs mrg (x:xs) (y:ys) = (x.y) : mrg xs ys
Self explanatory, isn't it? Here is a test case:
*Main> take 10 $ diag [[ (m,n) | n <- [1..]] | m <- [1..]] [(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),(1,4),(2,3),(3,2),(4,1)]
I was trying to golf it down [^1] but my brain explodes. If you succeed in reducing keystrokes, I'd be happy to know!
Cheers, Sebastian
[^1]: http://codegolf.com/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

And i forgot to include the defs of (co)prod: coprod (<>) i1 i2 = (\a b -> i1 a <> i2 b) prod (><) p1 p2 = (\a -> p1 a >< p2 a) diag = foldr (curry (prod mappend fst snd . uncurry (coprod mappend (splitAt 2) (splitAt 1)))) [] Matt

ghci> let diag = foldr (curry (prod mappend fst snd . uncurry (coprod mappend (splitAt 2) (splitAt 1)))) []
nice :) thanks to the comments of Martijn and Jan we can replace prod and coprod by liftA2 and <fancy dots>:
let diag = foldr (curry (liftA2 mappend fst snd.uncurry (((flip.). (((.).).).(.)) mappend (splitAt 2) (splitAt 1)))) []
It works for the finite tests but, unfortunately, not for the infinite one :(
take 10 $ diag [[ (m,n) | n <- [1..]] | m <- [1..]] *** Exception: stack overflow

Hi, This one works for all 3 examples you gave: diag = concat . takeWhile (not.null) . foldr1 (flip $ zipWith (flip (++)) . ([]:)) . map ((++ repeat []) . map (:[])) or, using Matt Hellige's pointless fun http://matt.immute.net/content/pointless-fun diag = foldr1 (zipWith (++) $. id ~> ([]:) ~> id) $. map (++ repeat []) ~> takeWhile (not.null) $. (map.map) (:[]) ~> concat I think the second one is quite readable, thanks to Matt's notation. The essential part is up front, and the pre- and post-transformations that belong to each other can be grouped. greetings, -- Sjoerd Visscher sjoerd@w3future.com

On Apr 18, 2009, at 2:48 AM, Sjoerd Visscher wrote:
using Matt Hellige's pointless fun http://matt.immute.net/content/pointless-fun
diag = foldr1 (zipWith (++) $. id ~> ([]:) ~> id) $. map (++ repeat []) ~> takeWhile (not.null) $. (map.map) (:[]) ~> concat
pretty! Those seem to be exactly the combinators that I was looking for. Unfortunately, I still don't manage to mimic my version that uses functional lists and continuations (but no ++) mainly because I'm lacking an equivalent of the second line of the above solution which allows for the simpler 'zipWith (++)' instead of the merge function. Anyway, once you know what they mean, Matt's combinators are quite useful. Thanks for pointing that out! Cheers, Sebastian

This is one with functional lists: diag = foldr1 (zipWith (.) $. id ~> (id:) ~> id) $. map (++ repeat id) ~> takeWhile (not.null.($[])) $. (map.map) (:) ~> ($[]) . mconcat On Apr 20, 2009, at 1:48 PM, Sebastian Fischer wrote:
On Apr 18, 2009, at 2:48 AM, Sjoerd Visscher wrote:
using Matt Hellige's pointless fun http://matt.immute.net/content/pointless-fun
diag = foldr1 (zipWith (++) $. id ~> ([]:) ~> id) $. map (++ repeat []) ~> takeWhile (not.null) $. (map.map) (:[]) ~> concat
pretty! Those seem to be exactly the combinators that I was looking for.
Unfortunately, I still don't manage to mimic my version that uses functional lists and continuations (but no ++) mainly because I'm lacking an equivalent of the second line of the above solution which allows for the simpler 'zipWith (++)' instead of the merge function.
Anyway, once you know what they mean, Matt's combinators are quite useful. Thanks for pointing that out!
Cheers, Sebastian _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher sjoerd@w3future.com
participants (8)
-
Emil Axelsson
-
Jan Christiansen
-
Martijn van Steenbergen
-
Matt Morrow
-
MigMit
-
Miguel Mitrofanov
-
Sebastian Fischer
-
Sjoerd Visscher