Implement the take function with list comprehension - haskell

How would you implement take with a list comprehension?
My approach so far:
take2 :: (Num i, Ord i) => i -> [a] -> [a]
take2 n xs = [x | x <- xs, [x..n]]

The fundamental reason why list comprehensions are not a good fit for the take function is this:
The take function stops the evaluation of the argument list after n elements.
But lists comprehensions always evaluate all elements of the list in the generator. There is no break-statement in Haskell.
You can use some trick to truncate the list before or after using it in the list comprehension, but there is no real point of doing so. That would be similar to first using normal take to truncate the list, then using a list comprehension just to return the result.

We can use a zip approach here, and enumerate over both the elements, and indices, like:
take2 :: (Num i, Enum i) => i -> [a] -> [a]
take2 n xs = [x | (x, _) <- zip xs [1..n]]
Or with the ParallelListComp extension:
{-# LANGUAGE ParallelListComp #-}
take2 :: (Num i, Enum i) => i -> [a] -> [a]
take2 n xs = [x | x <- xs | _ <- [1..n]]
But actually take is probably not a function that is a good fit for list comprehension in the first place.

Without List Comprehension
take' :: Int -> [Int] -> [Int]
take' _ [] = []
take' _ [x] = [x]
take' n all#(x : xs)
| (n > length all) = error "Index too large"
| (n == length all) = all
| (n == 0) = []
| (n < length all) = x : [] ++ (take' (n-1) xs)

take' :: Int -> [a] -> [a]
take' n xs = [xs !! i | i <- [0..n-1]]

Related

create a function ved that will only remove the last occurrence of the largest item in the list using recursion

You must use recursion to define rmax2 and you must do so from “scratch”. That is, other than the cons operator, head, tail, and comparisons, you should not use any functions from the Haskell library.
I created a function that removes all instances of the largest item, using list comprehension. How do I remove the last instance of the largest number using recursion?
ved :: Ord a => [a] -> [a]
ved [] =[]
ved as = [ a | a <- as, m /= a ]
where m= maximum as
An easy way to split the problem into two easier subproblems consists in:
get the position index of the rightmost maximum value
write a general purpose function del that eliminates the element of a list at a given position. This does not require an Ord constraint.
If we were permitted to use regular library functions, ved could be written like this:
ved0 :: Ord a => [a] -> [a]
ved0 [] = []
ved0 (x:xs) =
let
(maxVal,maxPos) = maximum (zip (x:xs) [0..])
del k ys = let (ys0,ys1) = splitAt k ys in (ys0 ++ tail ys1)
in
del maxPos (x:xs)
where the pairs produced by zip are lexicographically ordered, thus ensuring the rightmost maximum gets picked.
We need to replace the library functions by manual recursion.
Regarding step 1, that is finding the position of the rightmost maximum, as is commonly done, we can use a recursive stepping function and a wrapper above it.
The recursive step function takes as arguments the whole context of the computation, that is:
current candidate for maximum value, mxv
current rightmost position of maximum value, mxp
current depth into the original list, d
rest of original list, xs
and it returns a pair: (currentMaxValue, currentMaxPos)
-- recursive stepping function:
findMax :: Ord a => a -> Int -> Int -> [a] -> (a, Int)
findMax mxv mxp d [] = (mxv,mxp)
findMax mxv mxp d (x:xs) = if (x >= mxv) then (findMax x d (d+1) xs)
else (findMax mxv mxp (d+1) xs)
-- top wrapper:
lastMaxPos :: Ord a => [a] -> Int
lastMaxPos [] = (-1)
lastMaxPos (x:xs) = snd (findMax x 0 1 xs)
Step 2, eliminating the list element at position k, can be handled in very similar fashion:
-- recursive stepping function:
del1 :: Int -> Int -> [a] -> [a]
del1 k d [] = []
del1 k d (x:xs) = if (d==k) then xs else x : del1 k (d+1) xs
-- top wrapper:
del :: Int -> [a] -> [a]
del k xs = del1 k 0 xs
Putting it all together:
We are now able to write our final recursion-based version of ved. For simplicity, we inline the content of wrapper functions instead of calling them.
-- ensure we're only using authorized functionality:
{-# LANGUAGE NoImplicitPrelude #-}
import Prelude (Ord, Eq, (==), (>=), (+), ($), head, tail,
IO, putStrLn, show, (++)) -- for testing only
ved :: Ord a => [a] -> [a]
ved [] = []
ved (x:xs) =
let
findMax mxv mxp d [] = (mxv,mxp)
findMax mxv mxp d (y:ys) = if (y >= mxv) then (findMax y d (d+1) ys)
else (findMax mxv mxp (d+1) ys)
(maxVal,maxPos) = findMax x 0 1 xs
del1 k d (y:ys) = if (d==k) then ys else y : del1 k (d+1) ys
del1 k d [] = []
in
del1 maxPos 0 (x:xs)
main :: IO ()
main = do
let xs = [1,2,3,7,3,2,1,7,3,5,7,5,4,3]
res = ved xs
putStrLn $ "input=" ++ (show xs) ++ "\n" ++ " res=" ++ (show res)
If you are strictly required to use recursion, you can use 2 helper functions: One to reverse the list and the second to remove the first largest while reversing the reversed list.
This result in a list where the last occurrence of the largest element is removed.
We also use a boolean flag to make sure we don't remove more than one element.
This is ugly code and I really don't like it. A way to make things cleaner would be to move the reversal of the list to a helper function outside of the current function so that there is only one helper function to the main function. Another way is to use the built-in reverse function and use recursion only for the removal.
removeLastLargest :: Ord a => [a] -> [a]
removeLastLargest xs = go (maximum xs) [] xs where
go n xs [] = go' n True [] xs
go n xs (y:ys) = go n (y:xs) ys
go' n f xs [] = xs
go' n f xs (y:ys)
| f && y == n = go' n False xs ys
| otherwise = go' n f (y:xs) ys
Borrowing the implementation of dropWhileEnd from Hackage, we can implement a helper function splitWhileEnd:
splitWhileEnd :: (a -> Bool) -> [a] -> ([a], [a])
splitWhileEnd p = foldr (\x (xs, ys) -> if p x && null xs then ([], x:ys) else (x:xs, ys)) ([],[])
splitWhileEnd splits a list according to a predictor from the end. For example:
ghci> xs = [1,2,3,4,3,2,4,3,2]
ghci> splitWhileEnd (< maximum xs) xs
([1,2,3,4,3,2,4],[3,2])
With this helper function, you can write ven as:
ven :: Ord a => [a] -> [a]
ven xs =
let (x, y) = splitWhileEnd (< maximum xs) xs
in init x ++ y
ghci> ven xs
[1,2,3,4,3,2,3,2]
For your case, you can refactor splitWhileEnd as:
fun p = \x (xs, ys) -> if p x && null xs then ([], x:ys) else (x:xs, ys)
splitWhileEnd' p [] = ([], [])
splitWhileEnd' p (x : xs) = fun p x (splitWhileEnd' p xs)
ven' xs = let (x, y) = splitWhileEnd' (< maximum xs) xs in init x ++ y
If init and ++ are not allowed, you can implement them manually. It's easy!
BTW, I guess this may be your homework for Haskell course. I think it's ridiculous if your teacher gives the limitations. Who is programming from scratch nowadays?
Anyway, you can always work around this kind of limitations by reimplementing the built-in function manually. Good luck!

I am wanting to create my own version of findIndices in Haskell

I am new to Haskell and I'm not too comfortable with the syntax. I am basically trying to write my own version of findIndices from Haskell. This is what I have so far:
findIndices :: (a -> Bool) -> [a] -> [Int]
findIndices pred [] = []
findIndices pred (x:xs) = [n | n <- [0..length xs], pred x == True]
I am stuck on the list comprehension part. I want to be able to ask if the pred x == True on all of the elements of the list, but this will only ask it on the head of the list. Is there any way to recurse through the entire list to ask if pred x == True?
x is the first element of the list, xs are the remaining elements, so pred x will always be True or always be False, regardless of the value for n.
You can work with zip :: [a] -> [b] -> [(a, b)] to enumerate over two lists concurrently and construct 2-tuples, so:
findIndices :: (a -> Bool) -> [a] -> [Int]
findIndices pred xs = [i | (i, x) <- zip [0..] xs, pred x]
Here (i, x) are a 2-tuple where i is a (zero-based) index, and x an element from xs. We thus filter on pred x, and in that case yield the index i.
Use zip [0..] xs to get a list of (index, element) tuples, then apply your predicate :)
findIndices :: (a -> Bool) -> [a] -> [Int]
findIndices pred xs = [i | (i, x) <- zip [0..] xs, pred x]

How to remove second largest element in a list in haskell?

I have created a program to remove first smallest element but I dont how to do for second largest:
withoutBiggest (x:xs) =
withoutBiggestImpl (biggest x xs) [] (x:xs)
where
biggest :: (Ord a) => a -> [a] -> a
biggest big [] = big
biggest big (x:xs) =
if x < big then
biggest x xs
else
biggest big xs
withoutBiggestImpl :: (Eq a) => a -> [a] -> [a] -> [a]
withoutBiggestImpl big before (x:xs) =
if big == x then
before ++ xs
else
withoutBiggestImpl big (before ++ [x]) xs
Here is a simple solution.
Prelude> let list = [10,20,100,50,40,80]
Prelude> let secondLargest = maximum $ filter (/= (maximum list)) list
Prelude> let result = filter (/= secondLargest) list
Prelude> result
[10,20,100,50,40]
Prelude>
A possibility, surely not the best one.
import Data.Permute (rank)
x = [4,2,3]
ranks = rank (length x) x -- this gives [2,0,1]; that means 3 (index 1) is the second smallest
Then:
[x !! i | i <- [0 .. length x -1], i /= 1]
Hmm.. not very cool, let me some time to think to something better please and I'll edit my post.
EDIT
Moreover my previous solution was wrong. This one should be correct, but again not the best one:
import Data.Permute (rank, elems, inverse)
ranks = elems $ rank (length x) x
iranks = elems $ inverse $ rank (length x) x
>>> [x !! (iranks !! i) | i <- filter (/=1) ranks]
[4,2]
An advantage is that this preserves the order of the list, I think.
Here is a solution that removes the n smallest elements from your list:
import Data.List
deleteN :: Int -> [a] -> [a]
deleteN _ [] = []
deleteN i (a:as)
| i == 0 = as
| otherwise = a : deleteN (i-1) as
ntails :: Int -> [a] -> [(a, Int)] -> [a]
ntails 0 l _ = l
ntails n l s = ntails (n-1) (deleteN (snd $ head s) l) (tail s)
removeNSmallest :: Ord a => Int -> [a] -> [a]
removeNSmallest n l = ntails n l $ sort $ zip l [0..]
EDIT:
If you just want to remove the 2nd smallest element:
deleteN :: Int -> [a] -> [a]
deleteN _ [] = []
deleteN i (a:as)
| i == 0 = as
| otherwise = a : deleteN (i-1) as
remove2 :: [a] -> [(a, Int)] -> [a]
remove2 [] _ = []
remove2 [a] _ = []
remove2 l s = deleteN (snd $ head $ tail s) l
remove2Smallest :: Ord a => [a] -> [a]
remove2Smallest l = remove2 l $ sort $ zip l [0..]
It was not clear if the OP is looking for the biggest (as the name withoutBiggest implies) or what. In this case, one solution is to combine the filter :: (a->Bool) -> [a] -> [a] and maximum :: Ord a => [a] -> a functions from the Prelude.
withoutBiggest l = filter (/= maximum l) l
You can remove the biggest elements by first finding it and then filtering it:
withoutBiggest :: Ord a => [a] -> [a]
withoutBiggest [] = []
withoutBiggest xs = filter (/= maximum xs) xs
You can then remove the second-biggest element in much the same way:
withoutSecondBiggest :: Ord a => [a] -> [a]
withoutSecondBiggest xs =
case withoutBiggest xs of
[] -> xs
rest -> filter (/= maximum rest) xs
Assumptions made:
You want each occurrence of the second-biggest element removed.
When there is zero/one element in the list, there isn't a second element, so there isn't a second-biggest element. Having the list without an element that isn't there is equivalent to having the list.
When the list contains only values equivalent to maximum xs, there also isn't a second-biggest element even though there may be two or more elements in total.
The Ord type-class instance implies a total ordering. Otherwise you may have multiple maxima that are not equivalent; otherwise which one is picked as the biggest and second-biggest is not well-defined.

How to extract the same elements from two lists in Haskell?

here's my question:
How to extract the same elements from two equal length lists to another list?
For example: given two lists [2,4,6,3,2,1,3,5] and [7,3,3,2,8,8,9,1] the answer should be [1,2,3,3]. Note that the order is immaterial. I'm actually using the length of the return list.
I tried this:
sameElem as bs = length (nub (intersect as bs))
but the problem is nub removes all the duplications. The result of using my function to the former example is 3 the length of [1,3,2] instead of 4 the length of [1,3,3,2]. Is there a solution? Thank you.
Since the position seems to be irrelevant, you can simply sort the lists beforehand and then traverse both lists:
import Data.List (sort)
intersectSorted :: Ord a => [a] -> [a] -> [a]
intersectSorted (x:xs) (y:ys)
| x == y = x : intersectSorted xs ys
| x < y = intersectSorted xs (y:ys)
| x > y = intersectSorted (x:xs) ys
intersectSorted _ _ = []
intersect :: Ord a => [a] -> [a] -> [a]
intersect xs ys = intersectSorted (sort xs) (sort ys)
Note that it's also possible to achieve this with a Map:
import Data.Map.Strict (fromListWith, assocs, intersectionWith, Map)
type Counter a = Map a Int
toCounter :: Ord a => [a] -> Counter a
toCounter = fromListWith (+) . flip zip (repeat 1)
intersectCounter :: Ord a => Counter a -> Counter a -> Counter a
intersectCounter = intersectionWith min
toList :: Counter a -> [a]
toList = concatMap (\(k,c) -> replicate c k) . assocs
intersect :: Ord a => [a] -> [a] -> [a]
intersect xs ys = toList $ intersectCounter (toCounter xs) (toCounter ys)
You could write a function for this. There is probably a more elegant version of this involving lambda's or folds, but this does work for your example:
import Data.List
same (x:xs) ys = if x `elem` ys
then x:same xs (delete x ys)
else same xs ys
same [] _ = []
same _ [] = []
The delete x ys in the then-clause is important, without that delete command items from the first list that occur at least once will be counted every time they're encountered.
Note that the output is not sorted, since you were only interested in the length of the resulting list.
import Data.List (delete)
mutuals :: Eq a => [a] -> [a] -> [a]
mutuals [] _ = []
mutuals (x : xs) ys | x `elem` ys = x : mutuals xs (delete x ys)
| otherwise = mutuals xs ys
gives
mutuals [2,4,6,3,2,1,3,5] [7,3,3,2,8,8,9,1] == [2,3,1,3]

can you get a count on matches in a list comprehension (trying to insertionSort on a qsort after threshold)

I come from a C++ background so I'm not sure if I'm even going about this properly. But what I'm trying to do is write up quick sort but fallback to insertion sort if the length of a list is less than a certain threshold. So far I have this code:
insertionSort :: (Ord a) => [a] -> [a]
insertionSort [] = []
insertionSort (x:xs) = insert x (insertionSort xs)
quickSort :: (Ord a) => [a] -> [a]
quickSort x = qsHelper x (length x)
qsHelper :: (Ord a) => [a] -> Int -> [a]
qsHelper [] _ = []
qsHelper (x:xs) n
| n <= 10 = insertionSort xs
| otherwise = qsHelper before (length before) ++ [x] ++ qsHelper after (length after)
where
before = [a | a <- xs, a < x]
after = [a | a <- xs, a >= x]
Now what I'm concerned about is calculating the length of each list every time. I don't fully understand how Haskell optimizes things or the complete effects of lazy evaluation on code like the above. But it seems like calculating the length of the list for each before and after list comprehension is not a good thing? Is there a way for you to extract the number of matches that occurred in a list comprehension while performing the list comprehension?
I.e. if we had [x | x <- [1,2,3,4,5], x > 3] (which results in [4,5]) could I get the count of [4,5] without using a call to length?
Thanks for any help/explanations!
Short answer: no.
Less short answer: yes, you can fake it. import Data.Monoid, then
| otherwise = qsHelper before lenBefore ++ [x] ++ qsHelper after lenAfter
where
(before, Sum lenBefore) = mconcat [([a], Sum 1) | a <- xs, a < x]
(after, Sum lenAfter) = mconcat [([a], Sum 1) | a <- xs, a >= x]
Better answer: you don't want to.
Common reasons to avoid length include:
its running time is O(N)
but it costs us O(N) to build the list anyway
it forces the list spine to be strict
but we're sorting the list: we have to (at least partially) evaluate each element in order to know which is the minimum; the list spine is already forced to be strict
if you don't care how long the list is, just whether it's shorter/longer than another list or a threshold, length is wasteful: it will walk all the way to the end of the list regardless
BINGO
isLongerThan :: Int -> [a] -> Bool
isLongerThan _ [] = False
isLongerThan 0 _ = True
isLongerThan n (_:xs) = isLongerThan (n-1) xs
quickSort :: (Ord a) => [a] -> [a]
quickSort [] = []
quickSort (x:xs)
| not (isLongerThan 10 (x:xs)) = insertionSort xs
| otherwise = quickSort before ++ [x] ++ quickSort after
where
before = [a | a <- xs, a < x]
after = [a | a <- xs, a >= x]
The real inefficiency here though is in before and after. They both step through the entire list, comparing each element against x. So we are stepping through xs twice, and comparing each element against x twice. We only have to do it once.
(before, after) = partition (< x) xs
partition is in Data.List.
No, there is no way to use list comprehensions to simultaneously do a filter and count the number of found elements. But if you are worried about this performance hit, you should not be using the list comprehensions the way you are in the first place: You are filtering the list twice, hence applying the predicate <x and its negation to each element. A better variant would be
(before, after) = partition (< x) xs
Starting from that it is not hard to write a function
partitionAndCount :: (a -> Bool) -> [a] -> (([a],Int), ([a],Int))
that simultaneously partitions and counts the list and counts the elements in each of the returned list:
((before, lengthBefore), (after, lengthAfter)) = partitionAndCount (< x) xs
Here is a possible implementation (with a slightly reordered type):
{-# LANGUAGE BangPatterns #-}
import Control.Arrow
partitionAndCount :: (a -> Bool) -> [a] -> (([a], [a]), (Int, Int))
partitionAndCount p = go 0 0
where go !c1 !c2 [] = (([],[]),(c1,c2))
go !c1 !c2 (x:xs) = if p x
then first (first (x:)) (go (c1 + 1) c2 xs)
else first (second (x:)) (go c1 (c2 + 1) xs)
And here you can see it in action:
*Main> partitionAndCount (>=4) [1,2,3,4,5,3,4,5]
(([4,5,4,5],[1,2,3,3]),(4,4))

Resources