
Hi David, Thanks a lot for the code! foldr is indeed elegant. In general is it advisable to use auxiliary functions or foldr/foldl variations. Does it have any performance benefits or ghc would generate same core language for both the functions? Regards, Apoorv
On Jul 11, 2017, at 15:40, David Ringo
wrote: Hi Apoorv,
There is indeed a left fold:
foldlpart :: [Int] -> [a] -> [[a]] foldlpart ds ps = result where result | null remaining = initial | otherwise = initial ++ [remaining] (initial, remaining) = foldl aux ([], ps) ds aux (l, xs) d = case xs of [] -> (l, xs) _ -> let (f,s) = splitAt d xs in (l ++ [f], s)
I'm sure someone else can put something better together though.
I much prefer this right fold, since it avoids quadratic behavior incurred with (++) above:
foldrpart :: [Int] -> [a] -> [[a]] foldrpart ds ps = myFunc ps where myFunc = foldr buildMyFunc (: []) ds buildMyFunc digit func = \ps -> case ps of [] -> [] _ -> let (first, last) = splitAt digit ps in first : func last
If it's unclear, buildMyFunc is basically composing a bunch of functions which know (from the fold on the list of Ints) how many elements to take from some list.
Hope this is useful.
- David
On Tue, Jul 11, 2017 at 3:30 PM Apoorv Ingle
mailto:apoorv.ingle@gmail.com> wrote: Hi, I am trying to write a partition function where we pass group sizes and the list we want to partition into groups as arguments and get back a list of groups (or list of lists in this case). My first attempt was by using an auxiliary inner function
{-# LANGUAGE ScopedTypeVariables #-}
module Partition where
partition :: [Int] -> [a] -> [[a]] partition ds ps = reverse $ paux ds ps [] where paux :: [Int] -> [a] -> [[a]] -> [[a]] paux [] [] ps' = ps' paux [] ps ps' = [ps] ++ ps’ paux _ [] ps' = ps' paux (d:ds') ps ps' = paux ds' (snd (splitAt d ps)) ([fst (splitAt d ps)] ++ ps')
——————
*Partition> partition [2, 3] [1,2,3,4,5] [[1,2],[3,4,5]] *Partition> partition [1, 2] [1,2,3,4,5] [[1],[2,3],[4,5]] *Partition> partition [1, 2, 5] [1,2,3,4,5] [[1],[2,3],[4,5]]
I was speculating if we could write the same function using foldl function but haven’t been able to figure it out. I would really appreciate if you can give me pointers on how we can implement it.
partition' :: [Int] -> [a] -> [[a]] partition' [] ds = [ds] partition' ps ds = foldl ??? ???' ???''
contrary to my speculation is it even possible to write such a function using foldl if so why not?
Regards, Apoorv Ingle Graduate Student, Computer Science apoorv.ingle@ku.edu mailto:apoorv.ingle@ku.edu_______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners