
There are many ways you can do it. Here are two. The first uses the Transform List Comp extensions introduced in 6.10. http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#ge... The second uses more normal Haskell. The second version is probably not the best 'normal' Haskell implementation though. {-# LANGUAGE TransformListComp #-} import Data.Function (on) import Data.List (groupBy) import GHC.Exts test :: (Ord a) => [(a, b)] -> [(a, [b])] test l = [ (the f, s) | (f,s) <- l , then group by f ] ex1 = test [('a',1),('a',2),('a',3),('b',1),('b',2)] test2 :: (Ord a) => [(a, b)] -> [(a, [b])] test2 l = map (\grp -> (fst (head grp), map snd grp)) ((groupBy ((==) `on` fst)) l) ex2 = test [('a',1),('a',2),('a',3),('b',1),('b',2)] On Oct 24, 2009, at 5:27 PM, spot135 wrote:
Ok maybe a noob question, but hopefully its an easy one.
This is what I've got so far:
test :: x->[a] -> (b,[b]) test x arrlist = let test1 = x a = filter (\n -> fst n == test1) arrlist test2 = map snd a in (test1, [test2])
so basically I have a list say [(a,1),(a,2),(a,3),(b,1),(b,2)] etc So I give the function a x value (a or b) in this case and it return (a,[1,2,3])
which is all gravy
But, Is there a way that i dont have to supply the a or b ie i call the function and it gives me the list [(a,[1,2,3]),(b,[1,2])...
I presume i need another layer of recursion but I cant figure out how to do it.
Any help would be gratefully received :-)
-- View this message in context: http://www.nabble.com/bit-of-a-noob-question-tp26043671p26043671.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe