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:
usi
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 ex
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
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 :
> let diag = foldr (curry (liftA2 mappend fst snd.uncurry (((flip.).
(((.).).).(.))
Hi,
On 16.04.2009, at 05:08, Matt Morrow wrote:
And i forgot to include the defs of (co)prod:
prod (><) p1 p2 = (\a -> p1 a >< p2 a)
I think this one is liftM2 of the ((->) a) Monad instance.
Cheers, Jan
___
Haskell-Cafe mailing list
Haskell-C
Matt Morrow wrote:
And i forgot to include the defs of (co)prod:
coprod (<>) i1 i2 = (\a b -> i1 a <> i2 b)
lambdabot> pl \f i1 i2 -> (\a b -> i1 a `f` i2 b)
(flip .) . (((.) .) .) . (.)
Muhahaha. :-D Too bad the flip is still in there. :-)
Martijn.
_
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
(spli
*..against Monoid's method names.
On Wed, Apr 15, 2009 at 9:59 PM, Matt Morrow wrote:
> ... against the Monoid method's names.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
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 .
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] :
diag [[1,2,3],[4],[5,6,7]]
What it should be?
*Main> diag [[1,2,3],[4],[5,6,7]]
[1,2,4,3,5,6,7]
it's basically just "skipping holes":
1 2 3
4
5 6 7
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell
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
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 nu
Sorry, I misread the task :)
/ Emil
Emil Axelsson skrev:
Why not:
diag = [(x, sum-x) | sum <- [2..], x <- [1 .. sum-1]]
/ Emil
___
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)
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.200
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)
17 matches
Mail list logo