Operations on sublists - list

I am currently wondering on an approach to split a list in sub-lists according to a given criteria. Because of the didactic purpose of this work, I do not use built-in functions.
IE, the following program should, given a list, return a list of lists, where each sub-list does not have duplicates and is in ascending order:
increment [4;4;10;20;5;30;6;10] = [[4;10;20];[5;30];[6;10]]
increment [5;6;4;3;2;1] = [[5;6];[4];[3];[2];[1]]
My best attempt so far is based on this chunk of code I produced:
let rec increment li [lo] =
match li with
|[] -> [lo]
|[x] -> [x]::[lo]
|x::y::xs -> if x = y then
increment (y::xs) [lo]
elif x < y then
x::(increment (y::xs) [lo])
else
(x::(increment xs [lo]))::[lo]
Unfortunately, I fail in creating the list of lists. The principle is correct. It is based on the function I built, that correctly isolates an ascending list if present:
let rec incrementAux li =
match li with
|[] -> []
|[x] -> [x]
|x::y::xs -> if x = y then
incrementAux (y::xs)
elif x < y then
x::(incrementAux (y::xs))
else
x::(incrementAux [])
Any suggestion would be highly appreciated!

If you want to do this without using the built-in functions on the List module (purely as a learning exercise), then you just need to understand map and fold so you can implement them yourself. I would start with this wikipedia article. Conveniently, you can easily implement rev in terms of fold, so that shouldn't be a problem. Once you understand what each function does, you can implement them yourself like so:
let rec fold f state = function
| [] -> state
| head::tail -> fold f (f state head) tail
let map f list =
[for item in list -> f item]
let rev list =
fold (fun acc cur -> cur::acc) [] list
Then, you can just substitute your own functions for the built-in functions in Szer's solution:
let input = [4;4;10;20;5;30;6;10]
let output = [[4;10;20];[5;30];[6;10]]
let increment =
fold (fun (last::rest as total) x ->
match last with
| [] -> [x] :: rest
| h::_ as last ->
if x > h then (x::last)::rest
else if x = h then total
else [x]::total) [[]]
>> map rev
>> rev
let testOutput = increment input
testOutput = output
Note, this implementation of fold is different from how F# List does it. This is based on the simple Haskell example in the wikipedia article. The functionality is the same, but the implementation is quite different, as F# actually uses a mutable accumulator and a for-loop.

You could do it without recursion. List.fold with a little bit of memory could help:
let input = [4;4;10;20;5;30;6;10]
let output = [[4;10;20];[5;30];[6;10]]
let increment =
List.fold (fun (last::rest as total) x ->
match last with
| [] -> [x] :: rest
| h::_ as last ->
if x > h then (x::last)::rest
else if x = h then total
else [x]::total) [[]]
>> List.map List.rev
>> List.rev
let testOutput = increment input
testOutput = output // true

Related

Implementing Haskell's `take` function using `foldl`

Implementing Haskell's take and drop functions using foldl.
Any suggestions on how to implement take and drop functions using foldl ??
take x ls = foldl ???
drop x ls = foldl ???
i've tried these but it's showing errors:
myFunc :: Int -> [a] -> [a]
myFunc n list = foldl func [] list
where
func x y | (length y) > n = x : y
| otherwise = y
ERROR PRODUCED :
*** Expression : foldl func [] list
*** Term : func
*** Type : a -> [a] -> [a]
*** Does not match : [a] -> [a] -> [a]
*** Because : unification would give infinite type
Can't be done.
Left fold necessarily diverges on infinite lists, but take n does not. This is so because left fold is tail recursive, so it must scan through the whole input list before it can start the processing.
With the right fold, it's
ntake :: Int -> [a] -> [a]
ntake 0 _ = []
ntake n xs = foldr g z xs 0
where
g x r i | i>=n = []
| otherwise = x : r (i+1)
z _ = []
ndrop :: Int -> [a] -> [a]
ndrop 0 xs = xs
ndrop n xs = foldr g z xs 0 xs
where
g x r i xs#(_:t) | i>=n = xs
| otherwise = r (i+1) t
z _ _ = []
ndrop implements a paramorphism nicely and faithfully, up to the order of arguments to the reducer function g, giving it access to both the current element x and the current list node xs (such that xs == (x:t)) as well as the recursive result r. A catamorphism's reducer has access only to x and r.
Folds usually encode catamorphisms, but this shows that right fold can be used to code up a paramorphism just as well. It's universal that way. I think it is beautiful.
As for the type error, to fix it just switch the arguments to your func:
func y x | ..... = .......
The accumulator in the left fold comes as the first argument to the reducer function.
If you really want it done with the left fold, and if you're really sure the lists are finite, two options:
ltake n xs = post $ foldl' g (0,id) xs
where
g (i,f) x | i < n = (i+1, f . (x:))
| otherwise = (i,f)
post (_,f) = f []
rltake n xs = foldl' g id xs r n
where
g acc x = acc . f x
f x r i | i > 0 = x : r (i-1)
| otherwise = []
r _ = []
The first counts from the left straight up, potentially stopping assembling the prefix in the middle of the full list traversal that it does carry to the end nevertheless, being a left fold.
The second also traverses the list in full turning it into a right fold which then gets to work counting down from the left again, being able to actually stop working as soon as the prefix is assembled.
Implementing drop this way is bound to be (?) even clunkier. Could be a nice exercise.
I note that you never specified the fold had to be over the supplied list. So, one approach that meets the letter of your question, though probably not the spirit, is:
sillytake :: Int -> [a] -> [a]
sillytake n xs = foldl go (const []) [1..n] xs
where go f _ (x:xs) = x : f xs
go _ _ [] = []
sillydrop :: Int -> [a] -> [a]
sillydrop n xs = foldl go id [1..n] xs
where go f _ (_:xs) = f xs
go _ _ [] = []
These each use left folds, but over the list of numbers [1..n] -- the numbers themselves are ignored, and the list is just used for its length to build a custom take n or drop n function for the given n. This function is then applied to the original supplied list xs.
These versions work fine on infinite lists:
> sillytake 5 $ sillydrop 5 $ [1..]
[6,7,8,9,10]
Will Ness showed a nice way to implement take with foldr. The least repulsive way to implement drop with foldr is this:
drop n0 xs0 = foldr go stop xs0 n0
where
stop _ = []
go x r n
| n <= 0 = x : r 0
| otherwise = r (n - 1)
Take the efficiency loss and rebuild the whole list if you have no choice! Better to drive a nail in with a screwdriver than drive a screw in with a hammer.
Both ways are horrible. But this one helps you understand how folds can be used to structure functions and what their limits are.
Folds just aren't the right tools for implementing drop; a paramorphism is the right tool.
You are not too far. Here are a pair of fixes.
First, note that func is passed the accumulator first (i.e. a list of a, in your case) and then the list element (an a). So, you need to swap the order of the arguments of func.
Then, if we want to mimic take, we need to add x when the length y is less than n, not greater!
So we get
myFunc :: Int -> [a] -> [a]
myFunc n list = foldl func [] list
where
func y x | (length y) < n = x : y
| otherwise = y
Test:
> myFunc 5 [1..10]
[5,4,3,2,1]
As you can see, this is reversing the string. This is because we add x at the front (x:y) instead of at the back (y++[x]). Or, alternatively, one could use reverse (foldl ....) to fix the order at the end.
Also, since foldl always scans the whole input list, myFunc 3 [1..1000000000] will take a lot of time, and myFunc 3 [1..] will fail to terminate. Using foldr would be much better.
drop is more tricky to do. I don't think you can easily do that without some post-processing like myFunc n xs = fst (foldl ...) or making foldl return a function which you immediately call (which is also a kind of post-processing).

Applying Fold function in F#

let list_min_fold = List.fold (fun acc -> List.min acc ) 0 lst
printfn"Using regular List.fold function:\n The minimum is: %A\n"
(list_min_fold)
When I execute my code this error displays:
error FS0001: The type '('a -> 'b)' does not support the 'comparison' constraint. For example, it does not support the 'System.IComparable' interface
Why? Please help :(
Are you trying to find the smallest number in a list? If so, you need to use the min function (which takes just two arguments) rather than List.min (which takes a list of arguments):
To keep the code the most similar to your example, you can write (note also that starting with 0 is not going to work, so I used System.Int32.MaxValue instead):
let lst = [4;3;1;2;5;]
let list_min_fold = List.fold (fun acc -> min acc) System.Int32.MaxValue lst
It is also worth noting that the function you pass to fold takes two arguments - the state acc and the current value:
let list_min_fold = List.fold (fun acc v -> min acc v) System.Int32.MaxValue lst
But thanks to partial function application you can omit one of them (as you did), or both of them:
let list_min_fold = List.fold min System.Int32.MaxValue lst
as always Tomas answer is spot on so I have but a small remark:
as you probably saw it makes no sense to try to find the minimum of an empty list (so the function probably should be of type 'a option and when you have an non-empty list it's very easy to use List.reduce (which is basically just a fold for binary operations and min is a great candidate for such an operation):
let list_min xs =
match xs with
| [] -> None
| _ -> List.reduce min xs
|> Some
this way you get:
> list_min [2;1;5;3];;
val it : int option = Some 1
> list_min [2;1;5;3;0];;
val it : int option = Some 0
> list_min ([] : int list);;
val it : int option = None
ok it's a fair point that the question was about fold - so if it has to be exactly List.fold you can of course do (as TheInnerLight remarked):
let list_min xs =
match xs with
| [] -> None
| (x::xs) -> List.fold min x xs
|> Some

Removing consecutive duplicates from a list without recursion

I'm supposed to remove consecutive duplicates from an int list without using recursion and using only List.fold, map, filter, fold_left, fold_right.
I almost got it, but the problem with my code is that it checks if each element equals the 2nd element, and not the next element.
For example if let z = int list [3;1;4;5;5;1;1] my code will return [3;4;5] and not [3;1;4;5;1]. I'm not sure how to change it so filter uses a dynamically changing list parameter and not simply the original one (so it doesn't compare each element to the second element (1 in this case) each time):
let dupe (ls: int list) : int list =
List.filter (fun x -> if List.length ls = 0 then true else if x = List.hd (List.tl xs) then false else true) ls
The type of List.filter is this:
# List.filter;;
- : ('a -> bool) -> 'a list -> 'a list = <fun>
Notably, the filter function can see only one element of the list at a time. You need to see two consecutive elements to decide what to do, so I'd say List.filter won't do the job.
You're going to have to use map or one of the folds, I'd say. You can figure out which one(s) will work, with similar reasoning.
(I assume this is the sort of reasoning the assignment is supposed to illustrate. So I'm going to leave it there.)
Without rec
let remove = function
[] -> []
| x::tl ->
let (_,lxRes)=
List.fold_left (
fun (xPrec,lxRes) xCour ->
if xPrec=xCour then
(xCour,lxRes)
else
(xCour,lxRes#[xCour])
) (x+1,[]) (x::tl)
in
lxRes
Test:
# remove [3;1;4;5;5;1;1];;
- : int list = [3; 1; 4; 5; 1]
# remove [1;1];;
- : int list = [1]
# remove [1;1;1;1;2;2;3;4;5;5];;
- : int list = [1; 2; 3; 4; 5]
With rec (just for information)
let rec remove =
function
| [] -> []
| x::[] -> x::[]
| x::y::tl ->
if x=y then remove (y::tl)
else x::remove (y::tl)
Using just List.fold_left can be a little bit more concise than the previous answer. Of course, this will build up the list in reverse order, so we need to reverse the result.
let remove lst =
List.(
lst
|> fold_left
(fun acc x ->
match acc with
| [] -> [x]
| hd::_ when x = hd -> acc
| _ -> x::acc)
[]
|> rev
)
Of course, if you're not allowed to use List.rev we can reimplement it easily using List.fold_left, List.cons and Fun.flip.
let rev lst =
List.fold_left (Fun.flip List.cons) [] lst

Haskell: return the "list" result of a function as a "list of lists" without using an empty list "[]:foo"

What would be the syntax (if possible at all) for returning the list of lists ([[a]]) but without the use of empty list ([]:[a])?
(similar as the second commented guard (2) below, which is incorrect)
This is a function that works correctly:
-- Split string on every (shouldSplit == true)
splitWith :: (Char -> Bool) -> [Char] -> [[Char]]
splitWith shouldSplit list = filter (not.null) -- would like to get rid of filter
(imp' shouldSplit list)
where
imp' _ [] = [[]]
imp' shouldSplit (x:xs)
| shouldSplit x = []:imp' shouldSplit xs -- (1) this line is adding empty lists
-- | shouldSplit x = [imp' shouldSplit xs] -- (2) if this would be correct, no filter needed
| otherwise = let (z:zs) = imp' shouldSplit xs in (x:z):zs
This is the correct result
Prelude> splitWith (== 'a') "miraaaakojajeja234"
["mir","koj","jej","234"]
However, it must use "filter" to clean up its result, so I would like to get rid of function "filter".
This is the result without the use of filter:
["mir","","","","koj","jej","234"]
If "| shouldSplit x = imp' shouldSplit xs" is used instead the first guard, the result is incorrect:
["mirkojjej234"]
The first guard (1) adds empty list so (I assume) compiler can treat the result as a list of lists ([[a]]).
(I'm not interested in another/different solutions of the function, just the syntax clarification.)
.
.
.
ANSWER:
Answer from Dave4420 led me to the answer, but it was a comment, not an answer so I can't accept it as answer. The solution of the problem was that I'm asking the wrong question. It is not the problem of syntax, but of my algorithm.
There are several answers with another/different solutions that solve the empty list problem, but they are not the answer to my question. However, they expanded my view of ways on how things can be done with basic Haskell syntax, and I thank them for it.
Edit:
splitWith :: (Char -> Bool) -> String -> [String]
splitWith p = go False
where
go _ [] = [[]]
go lastEmpty (x:xs)
| p x = if lastEmpty then go True xs else []:go True xs
| otherwise = let (z:zs) = go False xs in (x:z):zs
This one utilizes pattern matching to complete the task of not producing empty interleaving lists in a single traversal:
splitWith :: Eq a => (a -> Bool) -> [a] -> [[a]]
splitWith f list = case splitWith' f list of
[]:result -> result
result -> result
where
splitWith' _ [] = []
splitWith' f (a:[]) = if f a then [] else [[a]]
splitWith' f (a:b:tail) =
let next = splitWith' f (b : tail)
in if f a
then if a == b
then next
else [] : next
else case next of
[] -> [[a]]
nextHead:nextTail -> (a : nextHead) : nextTail
Running it:
main = do
print $ splitWith (== 'a') "miraaaakojajeja234"
print $ splitWith (== 'a') "mirrraaaakkkojjjajeja234"
print $ splitWith (== 'a') "aaabbbaaa"
Produces:
["mir","koj","jej","234"]
["mirrr","kkkojjj","jej","234"]
["bbb"]
The problem is quite naturally expressed as a fold over the list you're splitting. You need to keep track of two pieces of state - the result list, and the current word that is being built up to append to the result list.
I'd probably write a naive version something like this:
splitWith p xs = word:result
where
(result, word) = foldr func ([], []) xs
func x (result, word) = if p x
then (word:result,[])
else (result, x:word)
Note that this also leaves in the empty lists, because it appends the current word to the result whenever it detects a new element that satisfies the predicate p.
To fix that, just replace the list cons operator (:) with a new operator
(~:) :: [a] -> [[a]] -> [[a]]
that only conses one list to another if the original list is non-empty. The rest of the algorithm is unchanged.
splitWith p xs = word ~: result
where
(result, word) = foldr func ([], []) xs
func x (result, word) = if p x
then (word ~: result, [])
else (result, x:word)
x ~: xs = if null x then xs else x:xs
which does what you want.
I guess I had a similar idea to Chris, I think, even if not as elegant:
splitWith shouldSplit list = imp' list [] []
where
imp' [] accum result = result ++ if null accum then [] else [accum]
imp' (x:xs) accum result
| shouldSplit x =
imp' xs [] (result ++ if null accum
then []
else [accum])
| otherwise = imp' xs (accum ++ [x]) result
This is basically just an alternating application of dropWhile and break, isn't it:
splitWith p xs = g xs
where
g xs = let (a,b) = break p (dropWhile p xs)
in if null a then [] else a : g b
You say you aren't interested in other solutions than yours, but other readers might be. It sure is short and seems clear. As you learn, using basic Prelude functions becomes second nature. :)
As to your code, a little bit reworked in non-essential ways (using short suggestive function names, like p for "predicate" and g for a main worker function), it is
splitWith :: (Char -> Bool) -> [Char] -> [[Char]]
splitWith p list = filter (not.null) (g list)
where
g [] = [[]]
g (x:xs)
| p x = [] : g xs
| otherwise = let (z:zs) = g xs
in (x:z):zs
Also, there's no need to pass the predicate as an argument to the worker (as was also mentioned in the comments). Now it is arguably a bit more readable.
Next, with a minimal change it becomes
splitWith :: (Char -> Bool) -> [Char] -> [[Char]]
splitWith p list = case g list of ([]:r)-> r; x->x
where
g [] = [[]]
g (x:xs)
| p x = case z of []-> r; -- start a new word IF not already
_ -> []:r
| otherwise = (x:z):zs
where -- now z,zs are accessible
r#(z:zs) = g xs -- in both cases
which works as you wanted. The top-level case is removing at most one empty word here, which serves as a separator marker at some point during the inner function's work. Your filter (not.null) is essentially fused into the worker function g here, with the conditional opening1 of a new word (i.e. addition1 of an empty list).
Replacing your let with where allowed for the variables (z etc.) to became accessible in both branches of the second clause of the g definition.
In the end, your algorithm was close enough, and the code could be fixed after all.
1 when thinking "right-to-left". In reality the list is constructed left-to-right, in guarded recursion ⁄ tail recursion modulo cons fashion.

Combine Lists with Same Heads in a 2D List (OCaml)

I'm working with a list of lists in OCaml, and I'm trying to write a function that combines all of the lists that share the same head. This is what I have so far, and I make use of the List.hd built-in function, but not surprisingly, I'm getting the failure "hd" error:
let rec combineSameHead list nlist = match list with
| [] -> []#nlist
| h::t -> if List.hd h = List.hd (List.hd t)
then combineSameHead t nlist#uniq(h#(List.hd t))
else combineSameHead t nlist#h;;
So for example, if I have this list:
[[Sentence; Quiet]; [Sentence; Grunt]; [Sentence; Shout]]
I want to combine it into:
[[Sentence; Quiet; Grunt; Shout]]
The function uniq I wrote just removes all duplicates within a list. Please let me know how I would go about completing this. Thanks in advance!
For one thing, I generally avoid functions like List.hd, as pattern maching is usually clearer and less error-prone. In this case, your if can be replaced with guarded patterns (a when clause after the pattern). I think what is happening to cause your error is that your code fails when t is []; guarded patterns help avoid this by making the cases more explicit. So, you can do (x::xs)::(y::ys)::t when x = y as a clause in your match expression to check that the heads of the first two elements of the list are the same. It's not uncommon in OCaml to have several successive patterns which are identical except for guards.
Further things: you don't need []#nlist - it's the same as just writing nlist.
Also, it looks like your nlist#h and similar expressions are trying to concatenate lists before passing them to the recursive call; in OCaml, however, function application binds more tightly than any operator, so it actually appends the result of the recursive call to h.
I don't, off-hand, have a correct version of the function. But I would start by writing it with guarded patterns, and then see how far that gets you in working it out.
Your intended operation has a simple recursive description: recursively process the tail of your list, then perform an "insert" operation with the head which looks for a list that begins with the same head and, if found, inserts all elements but the head, and otherwise appends it at the end. You can then reverse the result to get your intended list of list.
In OCaml, this algorithm would look like this:
let process list =
let rec insert (head,tail) = function
| [] -> head :: tail
| h :: t ->
match h with
| hh :: tt when hh = head -> (hh :: (tail # t)) :: t
| _ -> h :: insert (head,tail) t
in
let rec aux = function
| [] -> []
| [] :: t -> aux t
| (head :: tail) :: t -> insert (head,tail) (aux t)
in
List.rev (aux list)
Consider using a Map or a hash table to keep track of the heads and the elements found for each head. The nlist auxiliary list isn't very helpful if lists with the same heads aren't adjacent, as in this example:
# combineSameHead [["A"; "a0"; "a1"]; ["B"; "b0"]; ["A"; "a2"]]
- : list (list string) = [["A"; "a0"; "a1"; "a2"]; ["B"; "b0"]]
I probably would have done something along the lines of what antonakos suggested. It would totally avoid the O(n) cost of searching in a list. You may also find that using a StringSet.t StringMap.t be easier on further processing. Of course, readability is paramount, and I still find this hold under that criteria.
module OrderedString =
struct
type t = string
let compare = Pervasives.compare
end
module StringMap = Map.Make (OrderedString)
module StringSet = Set.Make (OrderedString)
let merge_same_heads lsts =
let add_single map = function
| hd::tl when StringMap.mem hd map ->
let set = StringMap.find hd map in
let set = List.fold_right StringSet.add tl set in
StringMap.add hd set map
| hd::tl ->
let set = List.fold_right StringSet.add tl StringSet.empty in
StringMap.add hd set map
| [] ->
map
in
let map = List.fold_left add_single StringMap.empty lsts in
StringMap.fold (fun k v acc-> (k::(StringSet.elements v))::acc) map []
You can do a lot just using the standard library:
(* compares the head of a list to a supplied value. Used to partition a lists of lists *)
let partPred x = function h::_ -> h = x
| _ -> false
let rec combineHeads = function [] -> []
| []::t -> combineHeads t (* skip empty lists *)
| (hh::_ as h)::t -> let r, l = List.partition (partPred hh) t in (* split into lists with the same head as the first, and lists with different heads *)
(List.fold_left (fun x y -> x # (List.tl y)) h r)::(combineHeads l) (* combine all the lists with the same head, then recurse on the remaining lists *)
combineHeads [[1;2;3];[1;4;5;];[2;3;4];[1];[1;5;7];[2;5];[3;4;6]];;
- : int list list = [[1; 2; 3; 4; 5; 5; 7]; [2; 3; 4; 5]; [3; 4; 6]]
This won't be fast (partition, fold_left and concat are all O(n)) however.