
Hi all, I have this function which combines (zip) list of sorted lists into a sorted list (sorted by sum). The function works with infinite list and seems to give correct result. But after I see the code for the Hamming sequence from the Wiki, I wonder if it can be written better, or more clearly, or succint? import Data.List comb [] = [] comb (a:as) = foldl f2 (f1 a) as where f1 :: [Int] -> [[Int]] f1 [] = [] f1 (a:as) = [a] : f1 as f2 :: [[Int]] -> [Int] -> [[Int]] f2 la [] = [] f2 [] lb = [] f2 la@(a:as) lb@(b:bs) = (a ++ [b]) : (f3 (f2 [a] bs) (f2 as lb)) f3 :: [[Int]] -> [[Int]] -> [[Int]] f3 [] lb = lb f3 la [] = la f3 la lb = let a = head la b = head lb in if sum a <= sum b then a : f3 (tail la) lb else b : f3 la (tail lb) t1 = take 500 (comb [[1,2..],[1,23..],[1,5..],[1,9..]]) t2 = take 500 (sortBy (\x y -> compare (sum x) (sum y)) [[a,b,c,d] | a<-[1,2..80],b<-[1,23..80], c<-[1,5..80],d<-[1,9..80]]) --t3 = take 500 (sortBy (\x y -> compare (sum x) (sum y)) -- [[a,b,c,d] | a<-[1,2..],b<-[1,23..], -- c<-[1,5..],d<-[1,9..]]) main = print (show ((map sum t1) == (map sum t2))) -- thanks for looking, -- Quan

Hi
f1 :: [Int] -> [[Int]] f1 [] = [] f1 (a:as) = [a] : f1 as
f1 is simply a map
f3 la lb = let a = head la b = head lb in if sum a <= sum b then a : f3 (tail la) lb else b : f3 la (tail lb)
Why not use pattern matching to split up la and lb, rather than head/tail? I would have thought the whole function could be written as a nice foldr merge, where merge :: [Int] -> [Int] -> [Int]. Thats only a guess at the top of my head though, not worked out properly. Is this homework? If so its useful to state when you post the question :) Thanks Neil

On 12/29/06, Neil Mitchell
Hi
f1 :: [Int] -> [[Int]] f1 [] = [] f1 (a:as) = [a] : f1 as
f1 is simply a map
f3 la lb = let a = head la b = head lb in if sum a <= sum b then a : f3 (tail la) lb else b : f3 la (tail lb)
Why not use pattern matching to split up la and lb, rather than head/tail?
I would have thought the whole function could be written as a nice foldr merge, where merge :: [Int] -> [Int] -> [Int]. Thats only a guess at the top of my head though, not worked out properly.
Is this homework? If so its useful to state when you post the question :)
Hi Neil, I am not sure how to express f1 with map? how do I say (lambda (ls) (map (lambda (x) (list x)) ls)) in Haskell? map ([]) ? Here is my new f3: f3 :: [[Int]] -> [[Int]] -> [[Int]] f3 [] lb = lb f3 la [] = la f3 la@(a:as) lb@(b:bs) = if sum a <= sum b then a : f3 as lb else b : f3 la bs (btw, yes this is homework assigned by prof. Quan in quantum computing class :)) Thanks, Quan

Hi Quan
I am not sure how to express f1 with map? how do I say (lambda (ls) (map (lambda (x) (list x)) ls)) in Haskell? map ([]) ?
map (:[]), :[] takes a single element and puts it into a list. Some people refer to this as "box" The final f3 clause can be made a bit neater:
f3 la@(a:as) lb@(b:bs) | sum a <= sum b = a : f3 as lb | otherwise = b : f3 la bs
Additionally, if it was me I'd refer to a:as on the RHS, rather than giving it a name with the @ pattern, but thats a personal question of style. Thanks Neil

Sorry to Neil for multiple copies.
On 29/12/06, Neil Mitchell
I am not sure how to express f1 with map? how do I say (lambda (ls) (map (lambda (x) (list x)) ls)) in Haskell? map ([]) ?
map (:[]), :[] takes a single element and puts it into a list. Some people refer to this as "box"
You can pretty much directly translate your Lisp: \ls -> map (\x -> [x]) ls Which eta-reduces to: map (\x -> [x]) Now the inner lambda can be written as: \x -> x : [] Or, (: []) That's a section on the ':' operator. So the whole thing becomes: map (:[]) Hope that helps. -- -David House, dmhouse@gmail.com

I am not sure how to express f1 with map? how do I say (lambda (ls) (map (lambda (x) (list x)) ls)) in Haskell? map ([]) ?
map (:[]), :[] takes a single element and puts it into a list. Some people refer to this as "box"
Another way to express f1 with map is: f1 xs = map (\x -> [x]) xs The (\x -> [x]) is a lambda that takes an x and puts it in a list. This is semantically the same as (\x -> x:[]), where (:) puts x at the front of the empty list ([]). So, this is where Niel gets his method (:[]) -- ie, just like (\x -> x+1) is semantically the same as (+1), so (\x -> x:[]) is semantically the same as (:[]). Bryan

On 12/29/06, Neil Mitchell
map (:[]), :[] takes a single element and puts it into a list. Some people refer to this as "box"
The final f3 clause can be made a bit neater:
f3 la@(a:as) lb@(b:bs) | sum a <= sum b = a : f3 as lb | otherwise = b : f3 la bs
Hi Neal,
Neat tricks on both counts - thanks! Thanks, Quan
participants (4)
-
Bryan Burgers
-
David House
-
Neil Mitchell
-
Quan Ta