Multiplying Lists through Folding - ocaml

So I am currently trying to figure out how to write a function where it takes 2 lists of equal lengths and multiplies the same position of both lists through folding, and returns the result as a new List.
eg) let prodList [1; 2; 3] [4; 5; 6] ;;
==> (through folding) ==> [1*4; 2*5; 3*6]
==> result = [4; 10; 18]
I feel like I need to use List.combine, since it will put the values that need to be multiplied into tuples. After that, I can't figure out how to break apart the tuple in a way that allows me to multiply the values. Here is what I have so far:
let prodLists l1 l2 =
let f a x = (List.hd(x)) :: a in
let base = [] in
let args = List.rev (List.combine l1 l2) in
List.fold_left f base args
Am I on the right track?

You can use fold_left2 which folds two lists of the same length. The documentation can give you more details (https://caml.inria.fr/pub/docs/manual-ocaml/libref/List.html):
val fold_left2 : ('a -> 'b -> 'c -> 'a) -> 'a -> 'b list -> 'c list -> 'a
List.fold_left2 f a [b1; ...; bn] [c1; ...; cn] is f (... (f (f a b1 c1) b2 c2) ...) bn cn. Raise Invalid_argument if the two lists are determined to have different lengths.
Another way is to fold the output of combine as you have suggested, I would recommend you to try it by yourself before looking at the solution bellow.
Solution:
let prod_lists l s =
List.rev (List.fold_left2 (fun acc a b -> (a * b) :: acc) [] l s);;
let prod_lists' l s =
List.fold_left (fun acc (a, b) -> (a * b) :: acc) [] (List.rev (List.combine l s));;

First let me note using fold to implement this operation seems a bit forced, since you have to traverse both lists at the same time. Fold however combines the elements of a single list. Nonetheless here is an implementation.
let e [] = []
let f x hxs (y::ys) = (x*y) :: hxs ys
let prodList xs ys = List.fold_right f xs e ys
Looks a bit complicated, so let me explain.
Universal Property of fold right
First you should be aware of the following property of fold_right.
h xs = fold_right f xs e
if and only if
h [] = e
h (x::xs) = f x (h xs)
This means that if we write the multiplication of lists in the recursive form below, then we can use the e and f to write it using fold as above. Note though we are operating two lists so h takes two arguments.
Base case - empty lists
Multiplying two empty lists returns an empty list.
h [] [] = []
How to write this in the form above? Just abstract over the second argument.
h [] = fun [] -> []
So,
e = fun [] -> []`
Or equivalently,
e [] = []
Recursive case - non-empty lists
h (x::xs) (y::ys) = x*y :: h xs ys
Or, using just one argument,
h (x::xs) = fun -> (y::ys) -> x*y :: h xs ys
Now we need to rewrite this expression in the form h (x::xs) = f x (h xs). It may seem complicated but we just need to abstract over x and h xs.
h (x::xs) = (fun x hxs -> fun (y::ys) -> x*y :: hxs ys) x (h xs)
so we have that f is defined by,
f = fun x hxs -> fun (y::ys) -> x*y :: hxs ys
or equivalently,
f x hxs (y::ys) = x*y :: hxs ys
Solution as a fold right
Having determined both e and f we just plug then into fold according to the first equation of the property above. And we get,
h xs = List.fold_right f xs e
or equivalently,
h xs ys = List.fold_right f xs e ys
Understanding the implementation
Note that the type of List.fold_right f xs e is int list -> int list, so the fold is building a function on lists, that given some ys will multiply it with the given parameter xs.
For an empty xs you will expect an empty ys and return an empty result so,
e [] = fun [] -> []
As for the recursive case, the function f in a fold_right must implement a solution for x::xs from a solution for xs. So f takes an x of type int and a function hxs of type int list -> int list which implements the multiplication for the tail, and it must implement multiplication for x::xs.
f x hxs = fun (y::ys) -> x*y :: hxs ys
So f constructs a function that multiplies x with y, and then applies to ys the already constructed hxs which multiplies xs to a list.

You mostly have the right idea; you'll want to combine (zip in other languages) the two lists and then map over each tuple:
let prod_lists l1 l2 =
List.combine l1 l2
|> List.map (fun (a, b) -> a * b)
The key is that you can pattern match on that tuple using (a, b).
You can also fold over the combined list, then rev the result, if you don't want to use map.

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).

Haskell List function (map, zip, etc..) with fix

I try to learn haskell and have exercise -try to rewrite standart list operation(map, foldr, zip, iterate, etc.) with function fix.
I have example with repeat:
repeat a = fix $ \xs -> a : xs
and it's further simplify
repeat a = fix (a:)
repeat = fix . (:)
Can anyone help me with map?
Sorry for my bad engl and thank u in advance.
To use fix, one needs to write the recursive definition in the form
map = .... something involving map ....
Then, we let
map = fix (\m -> .... something involving m ....)
For instance,
map = \f xs -> case xs of
[] -> []
y:ys -> f y : map f ys
so,
map = fix (\m f xs -> case xs of
[] -> []
y:ys -> f y : m f ys)
Alternatively, since the argument f is the same for each recursive call, we can let
map f = \xs -> case xs of
[] -> []
y:ys -> f y : map f ys
and obtain
map f = fix (\m xs -> case xs of
[] -> []
y:ys -> f y : m ys)

OCaml: Combination of elements in Lists, functional reasoning

I am back to coding in OCaml and I missed it so much. I missed it so much I completely lost my reasoning in this language and I hit a wall today.
What I want to do is the combination of elements between a set of n lists.
I decomposed the problem by first attempting the combination of elements between two list of arbitrary sizes.
Assume we have to lists: l1 = [1;2;3] and l2 = [10,20].
What I want to do is obtain the following list:
l_res = [10;20;20;40;30;60]
I know how to do this using loop structures, but I really want to solve this without them.
I tried the following:
let f l1 l2 =
List.map (fun y -> (List.map (fun x -> x * y) l1) l2
But this does not seem to work. The type I get is f : int list -> int list -> int list list but I want f : int list -> int list -> int list
I tried already many different approaches I feel I am over complicating.
What did I miss?
What you are missing is that List.map f [a; b; c] gives [f a; f b; f c] so what you'll get from your function will be
f [a; b; c] [d; e] = [[ad; ae]; [bd; be]; [cd; ce]]
but you want
f [a; b; c] [d; e] = [ad; ae; bd; be; cd; ce]
so you need to use an other iterator, i.e. :
let f l1 l2 =
let res = List.fold_left (fun acc x ->
List.fold_left (fun acc y -> (x * y) :: acc) acc l2
) [] l1 in
List.rev res
or to flatten your result :
val concat : 'a list list -> 'a list
Concatenate a list of lists. The elements of the argument are all
concatenated together (in the same order) to give the result. Not
tail-recursive (length of the argument + length of the longest
sub-list).
val flatten : 'a list list -> 'a list
Same as concat. Not tail-recursive (length of the argument + length of
the longest sub-list).
Some Core-flavoured answers:
open Core.Std
let f1 l1 l2 =
List.map (List.cartesian_product l1 l2) ~f:(fun (x, y) -> x * y)
let f2 l1 l2 =
List.concat_map l1 ~f:(fun x -> List.map l2 ~f:(fun y -> x * y))
let f4 l1 l2 =
let open List.Monad_infix in
l1 >>= fun x ->
l2 >>| fun y ->
x * y
The last answer explicitly (and arguably the two other answers implicitly) makes use of the list monad, which this is a textbook use case of. I couldn't find the list monad in Batteries, which is possibly not so surprising as it's much less widely used than (say) the option or result monads.
let f l1 l2 =
let multiply x = List.map (( * )x) l2 in
l1 |> List.map multiply
|> List.concat

Library function to find difference between two lists - OCaml

Is there a library function to find List1 minus elements that appear in List2? I've been googling around and haven't found much.
It doesn't seem too trivial to write it myself. I've written a function to remove a specific element from a list but that's much more simple:
let rec difference l arg = match l with
| [] -> []
| x :: xs ->
if (x = arg) then difference xs arg
else x :: difference xs arg;;
Will this do?
let diff l1 l2 = List.filter (fun x -> not (List.mem x l2)) l1
What I ended up actually doing was just writing another function which would call the first one I posted
let rec difference l arg = match l with
| [] -> []
| x :: xs ->
if (x = arg) then difference xs arg
else x :: difference xs arg;;
let rec list_diff l1 l2 = match l2 with
| [] -> l1
| x :: xs -> list_diff (difference l1 x) xs;;
Although the solution I accepted is much more elegant

Zip with default value instead of dropping values?

I'm looking for a function in haskell to zip two lists that may vary in length.
All zip functions I could find just drop all values of a lists that is longer than the other.
For example:
In my exercise I have two example lists.
If the first one is shorter than the second one I have to fill up using 0's. Otherwise I have to use 1's.
I'm not allowed to use any recursion. I just have to use higher order functions.
Is there any function I can use?
I really could not find any solution so far.
There is some structure to this problem, and here it comes. I'll be using this stuff:
import Control.Applicative
import Data.Traversable
import Data.List
First up, lists-with-padding are a useful concept, so let's have a type for them.
data Padme m = (:-) {padded :: [m], padder :: m} deriving (Show, Eq)
Next, I remember that the truncating-zip operation gives rise to an Applicative instance, in the library as newtype ZipList (a popular example of a non-Monad). The Applicative ZipList amounts to a decoration of the monoid given by infinity and minimum. Padme has a similar structure, except that its underlying monoid is positive numbers (with infinity), using one and maximum.
instance Applicative Padme where
pure = ([] :-)
(fs :- f) <*> (ss :- s) = zapp fs ss :- f s where
zapp [] ss = map f ss
zapp fs [] = map ($ s) fs
zapp (f : fs) (s : ss) = f s : zapp fs ss
I am obliged to utter the usual incantation to generate a default Functor instance.
instance Functor Padme where fmap = (<*>) . pure
Thus equipped, we can pad away! For example, the function which takes a ragged list of strings and pads them with spaces becomes a one liner.
deggar :: [String] -> [String]
deggar = transpose . padded . traverse (:- ' ')
See?
*Padme> deggar ["om", "mane", "padme", "hum"]
["om ","mane ","padme","hum "]
This can be expressed using These ("represents values with two non-exclusive possibilities") and Align ("functors supporting a zip operation that takes the union of non-uniform shapes") from the these library:
import Data.Align
import Data.These
zipWithDefault :: Align f => a -> b -> f a -> f b -> f (a, b)
zipWithDefault da db = alignWith (fromThese da db)
salign and the other specialised aligns in Data.Align are also worth having a look at.
Thanks to u/WarDaft, u/gallais and u/sjakobi over at r/haskell for pointing out this answer should exist here.
You can append an inifinte list of 0 or 1 to each list and then take the number you need from the result zipped list:
zipWithDefault :: a -> b -> [a] -> [b] -> [(a,b)]
zipWithDefault da db la lb = let len = max (length la) (length lb)
la' = la ++ (repeat da)
lb' = lb ++ (repeat db)
in take len $ zip la' lb'
This should do the trick:
import Data.Maybe (fromMaybe)
myZip dx dy xl yl =
map (\(x,y) -> (fromMaybe dx x, fromMaybe dy y)) $
takeWhile (/= (Nothing, Nothing)) $
zip ((map Just xl) ++ (repeat Nothing)) ((map Just yl) ++ (repeat Nothing))
main = print $ myZip 0 1 [1..10] [42,43,44]
Basically, append an infinite list of Nothing to the end of both lists, then zip them, and drop the results when both are Nothing. Then replace the Nothings with the appropriate default value, dropping the no longer needed Justs while you're at it.
No length, no counting, no hand-crafted recursions, no cooperating folds. transpose does the trick:
zipLongest :: a -> b -> [a] -> [b] -> [(a,b)]
zipLongest x y xs ys = map head . transpose $ -- longest length;
[ -- view from above:
zip xs
(ys ++ repeat y) -- with length of xs
, zip (xs ++ repeat x)
ys -- with length of ys
]
The result of transpose is as long a list as the longest one in its input list of lists. map head takes the first element in each "column", which is the pair we need, whichever the longest list was.
(update:) For an arbitrary number of lists, efficient padding to the maximal length -- aiming to avoid the potentially quadratic behaviour of other sequentially-combining approaches -- can follow the same idea:
padAll :: a -> [[a]] -> [[a]]
padAll x xss = transpose $
zipWith const
(transpose [xs ++ repeat x | xs <- xss]) -- pad all, and cut
(takeWhile id . map or . transpose $ -- to the longest list
[ (True <$ xs) ++ repeat False | xs <- xss])
> mapM_ print $ padAll '-' ["ommmmmmm", "ommmmmm", "ommmmm", "ommmm", "ommm",
"omm", "om", "o"]
"ommmmmmm"
"ommmmmm-"
"ommmmm--"
"ommmm---"
"ommm----"
"omm-----"
"om------"
"o-------"
You don't have to compare list lengths. Try to think about your zip function as a function taking only one argument xs and returning a function which will take ys and perform the required zip. Then, try to write a recursive function which recurses on xs only, as follows.
type Result = [Int] -> [(Int,Int)]
myZip :: [Int] -> Result
myZip [] = map (\y -> (0,y)) -- :: Result
myZip (x:xs) = f x (myZip xs) -- :: Result
where f x k = ??? -- :: Result
Once you have found f, notice that you can turn the recursion above into a fold!
As you said yourself, the standard zip :: [a] -> [b] -> [(a, b)] drops elements from the longer list. To amend for this fact you can modify your input before giving it to zip. First you will have to find out which list is the shorter one (most likely, using length). E.g.,
zip' x xs y ys | length xs <= length ys = ...
| otherwise = ...
where x is the default value for shorter xs and y the default value for shorter ys.
Then you extend the shorter list with the desired default elements (enough to account for the additional elements of the other list). A neat trick for doing so without having to know the length of the longer list is to use the function repeat :: a -> [a] that repeats its argument infinitely often.
zip' x xs y ys | length xs <= length ys = zip {-do something with xs-} ys
| otherwise = zip xs {-do something with ys-}
Here is another solution, that does work on infinite lists and is a straightforward upgrade of Prelude's zip functions:
zipDefault :: a -> b -> [a] -> [b] -> [(a,b)]
zipDefault _da _db [] [] = []
zipDefault da db (a:as) [] = (a,db) : zipDefault da db as []
zipDefault da db [] (b:bs) = (da,b) : zipDefault da db [] bs
zipDefault da db (a:as) (b:bs) = (a,b) : zipDefault da db as bs
and
zipDefaultWith :: a -> b -> (a->b->c) -> [a] -> [b] -> [c]
zipDefaultWith _da _db _f [] [] = []
zipDefaultWith da db f (a:as) [] = f a db : zipDefaultWith da db f as []
zipDefaultWith da db f [] (b:bs) = f da b : zipDefaultWith da db f [] bs
zipDefaultWith da db f (a:as) (b:bs) = f a b : zipDefaultWith da db f as bs
#pigworker, thank you for your enlightening solution!
Yet another implementation:
zipWithDefault :: a -> b -> (a -> b -> c) -> [a] -> [b] -> [c]
zipWithDefault dx _ f [] ys = zipWith f (repeat dx) ys
zipWithDefault _ dy f xs [] = zipWith f xs (repeat dy)
zipWithDefault dx dy f (x:xs) (y:ys) = f x y : zipWithDefault dx dy f xs ys
And also:
zipDefault :: a -> b -> [a] -> [b] -> [c]
zipDefault dx dy = zipWithDefault dx dy (,)
I would like to address the second part of Will Ness's solution, with its excellent use of known functions, by providing another to the original question.
zipPadWith :: a -> b -> (a -> b -> c) -> [a] -> [b] -> [c]
zipPadWith n _ f [] l = [f n x | x <- l]
zipPadWith _ m f l [] = [f x m | x <- l]
zipPadWith n m f (x:xs) (y:ys) = f x y : zipPadWith n m f xs ys
This function will pad a list with an element of choice. You can use a list of the same element repeated as many times as the number of lists in another like this:
rectangularWith :: a -> [[a]] -> [[a]]
rectangularWith _ [] = []
rectangularWith _ [ms] = [[m] | m <- ms]
rectangularWith n (ms:mss) = zipPadWith n [n | _ <- mss] (:) ms (rectangularWith n mss)
The end result will have been a transposed rectangular list of lists padded by the element that we provided so we only need to import transpose from Data.List and recover the order of the elements.
mapM_ print $ transpose $ rectangularWith 0 [[1,2,3,4],[5,6],[7,8],[9]]
[1,2,3,4]
[5,6,0,0]
[7,8,0,0]
[9,0,0,0]