Currently I am doing something like this in my code:
--Generate a list of n 'Foo's
generateFoos n = [createFoo (show i) | i <- [1..n]]
-- Create a Foo with a given name
createFoo :: String -> Foo
I was wandering if there is a another way of doing this than creating a range [1..n] all the time...
I would say don't worry about it. "Creating the range [1..n]" isn't really going on here as a distinct step; that [1..n] desugars to enumFromTo 1 n and it's constructed lazily like everything else anyway. There's no hidden cost here one would need to eliminate.
Expanding on my comment above - the reason the map function arises naturally here is as follows.
In Haskell, list comprehensions are just syntactic sugar for do notation:
[ 2 * x | x <- [1..10] ]
is equivalent to
do { x <- [1..10]; return (2 * x) }
In turn, do notation is syntactic sugar for monadic binds - the above is equivalent to
[1..10] >>= \x -> return (2 * x)
This works because List is a monad. The code that makes List into a monad is (ignoring some irrelevant stuff)
instance Monad [] where
return x = [x]
xs >>= f = concat (map f xs)
so the call to >>= above is equivalent to
concat (map (\x -> return (2 * x)) [1..10])
which, if we replace the call to bind, is equivalent to
concat (map (\x -> [2 * x]) [1..10])
So we map the function \x -> [2 * x] over the list [1..10] and then call concat on the result. But since our function only every builds one element lists, we can skip out the call to concat and replace the code with
map (\x -> 2 * x) [1..10]
So it's natural that relatively simple list comprehensions can be turned into expressions that involve mapping a function over a range.
I prefer it that way:
generateFoos n = map (createFoo . show) [1..n]
Or are the ranges itself the problem? Then I'd recommend:
generateFoos n = map (createFoo . show) (enumFromTo 1 n)
No map, no range.
generateFoos n = unfoldr (doit (createFoo . show)) 1 where
doit f acc = if acc > n then Nothing else Just (f acc, acc + 1)
I do not guarantee any particular quality or property of this code though ;)
Related
I am learning Haskell for a university course and i have a question about reducible expressions (redexes). I understand the concept yet I still have some questions that I can't seem to figure out on my own.
Lets say you would want to find all the reducible expressions in an expression, like this:
head (map (+1) (3:repeat 3))
In this expression an obvious redex would be map (+1) (3:repeat 3)) because it matches to the definition of map, so Haskell would "reduce" the expression and map would increment the 3 and 4:map (+1) (repeat 3). would be reduced next.
The question I have is:
Is head (map (+1) (3:repeat 3)) already a redex, before map is evaluated?
Because the "input" of head does not match the constructor of a list (which is what head is looking for), I am confused about whether it still is a redex because logically it can't get reduced yet, but the definitions online seem to be saying that it would be.
Haskell's evaluation is lazy: it proceeds by topmost leftmost redex strategy (at least conceptually): it reduces the leftmost among the topmost redexes.
Presumably head is defined as
head xs = case xs of (x:_) -> x
so then its application to whatever expression is indeed a redex -- an expression in need of reducing. Which proceeds according to the definition of head,
head (map (+1) (3:repeat 3))
=
case (map (+1) (3:repeat 3)) of (x:_) -> x
=
(or we could say that head itself is the topmost leftmost redex, which reduces to its definition, first; and if we'd written the above as ((\xs -> case xs of (x:_) -> x) (map (+1) (3:repeat 3))) we'd get to the same outcome, just a bit more tediously).
A primary forcing primitive is case. Now it needs to perform the pattern match, so it must find out the value of its scrutinee expression (only to the extent that the pattern match becomes possible). To do that it must now work according to the definition of map which is presumably
map f xs = case xs of { (x:ys) -> f x : map f ys
; [] -> [] }
so it becomes
case (map (+1) (3:repeat 3)) of (x:_) -> x
=
case (case (3:repeat 3) of
{ (x:ys ) -> (+1) x : map (+1) ys
; [] -> [] } )
of (x:_) -> x
=
At this point the inner case expression can be reduced,
case (let { x=3 ; ys=repeat 3} in
(+1) x : map (+1) ys )
of (x : _ ) -> x
=
and now the outer case's pattern matching becomes possible,
case (let { x=3 } in
(+1) x )
of (x ) -> x
=
let { x=3 } in
(+1) x
=
(+1) 3
=
4
I have already seen this solution:
doubleAndSum :: [Int] -> Int
doubleAndSum = fst . foldr (\i (acc, even) -> (acc + nextStep even i, not even)) (0,False)
where
nextStep even i
| even = (uncurry (+) . (`divMod` 10) . (*2)) i
| otherwise = i
myLuhn :: Int -> Bool
myLuhn = (0 ==) . (`mod` 10) . doubleAndSum . (map (read . (: ""))) . show
testCC :: [Bool]
testCC = map myLuhn [49927398716, 49927398717, 1234567812345678, 1234567812345670]
-- => [True,False,False,True]
However, I don't understand it because I am new to Haskell.
luhn :: [Int] -> Bool
luhn w x y z = (luhnDouble w + x + luhnDouble y + z) `mod` 10 == 0
luhnDouble :: Int -> Int
luhnDouble x | 2* x <= 9 = 2*x
| otherwise = (2*x)-9
I understand this simplified version of the algorithm for only four digits.
However, I don't know how to write a version of the algorithm for a list of digits of any length.
Honestly, the example is pretty arcane. It makes excessive use of point-free style, i.e. omitting explicit function arguments. That can sometimes make code nice and concise, but it can also make code rather cryptic.
Let's start with this here:
(uncurry (+) . (`divMod` 10) . (*2)) i
First, since you're just applying everything to the argument i, there's no real need for having a composition pipeline – you might as well write it
uncurry (+) $ (`divMod` 10) $ (*2) i
≡ uncurry (+) $ (`divMod` 10) $ i*2
≡ uncurry (+) $ (i*2)`divMod`10
≡ let (d,r) = (i*2)`divMod`10
in d+r
So, nextStep could be written
nextStep isEven i
| isEven = d+r
| otherwise = i
where (d,r) = (i*2)`divMod`10
(I avoid the variable name even, which is also the name of the standard function that checks whether a number is even!)
Alternatively, you could just invoke your luhnDouble function here, which actually computes the same thing, just in a more verbose way:
nextStep isEven i
| isEven = luhnDouble i
| otherwise = i
Then you have this fold. It basically does three things interlocked: 1. toggle between even and odd 2. apply nextStep to each list element, together with the even-ness 3. sum up the results.
I don't agree that it's a good idea to do all of that with a single fold†; much clearer to write it out:
doubleAndSum = sum
. map (\(isEven, i) -> nextStep isEven i) -- or `map (uncurry nextStep)`
. zip (cycle [False, True]) -- or `iterate not False`
. reverse
The reverse is needed just to align the False with the last element of the input list, instead of its head; this is a bit ugly but uncritical.
The combination of map and zip has a standard shortcut that does both in one step:
doubleAndSum = sum
. zipWith nextStep (cycle [False, True])
. reverse
As for myLuhn: this is IMO actually ok to write in the point-free style, but I'd break it out a bit. Specifically,
decimalDigits :: Int -> [Int]
decimalDigits = map (read . (: "")) . show
What (:"") does is, it puts single characters into singleton-strings. Could also be written read . pure.
Then,
myLuhn = (0 ==) . (`mod` 10) . doubleAndSum . decimalDigits
or
myLuhn x = doubleAndSum (decimalDigits x)`mod`10 == 0
†There could be a case made that a single traversal is good for performance, however if you think on that level then it should almost certainly not be a lazy right fold over a list, but rather a strict left fold over an unboxed vector. Anyway, GHC can often fuse separate fold-y operations into a single traversal.
So I m watching a very basic Tutorial, and I m at list comprehension where this comes up:
listx2 = [x * 2 | x<- numberList]
with numberList being a list of numbers
So this takes every number in the list and duplicates it, so numberList = [1,2] results in [2,4].
But HOW does the whole Syntax come together?
I know that x * 2 is the doubleing, but the rest just doesn't make sense to me.
| is the "or" Symbol as far as I know,and what does it do there?
x <- numberList gives x a number from the list, but why does it take just a number? and why so nicely one after the other? There is no recursion or anything that tells it to do one element at a time...
I learn stuff by understanding it, so is that even possible here or do I just have to accept this as "thats how it goes" and memorize the pattern?
List comprehensions use their own special syntax, which is
[ e | q1, q2, ..., qn ]
The | is not an "or", it's part of the syntax, just as [ and ].
Each qi can be of the following forms.
x <- list chooses x from the list
condition is a boolean expression, which discards the xs chosen before if the condition is false
let y = expression defines variable y accordingly
Finally, e is an expression which can involve all the variables defined in the qi, and which forms the elements in the resulting list.
What you see is syntactical sugar. So Haskell does not interpret the pipe (|) as a guard, etc. It sees the list comprehension as a whole.
This however does not mean that the <- are picked at random. Actually list comprehension maps nicely on the list monad. What you see is syntactical sugar for:
listx2 = do
x <- numberList
return x*2
Now a list type [] is actually a monad. It means that we have written:
listx2 = numberList >>= \x -> return (x*2)
Or even shorter:
listx2 = numberList >>= return . (*2)
Now the list monad is defined as:
instance Monad [] where
return x = [x]
xs >>= k = concat $ fmap k xs
So this means that it is equivalent to:
listx2 = numberList >>= return . (*2)
listx2 = concat (fmap (return . (*2)) numberList)
listx2 = concat (fmap (\x -> [2*x]) numberList)
Now for a list fmap is equal to map, so:
listx2 = concat $ map (\x -> [2*x]) numberList
listx2 = concatMap (\x -> [2*x]) numberList
so that means that for every element x in the numberList we will generate a singleton list [2*x] and concatenate all these singleton lists into the result.
I went through a post for this problem but I do not understand it. Could someone please explain it?
Q: Find every n-th element of the list in the form of a list start from the n-th element itself.
everyNth :: Int -> [t] -> [t]
everyNth elt = map snd . filter (\(lst,y) -> (mod lst elt) == 0) . zip [1..]
Also, please explain how pattern matching can be used for this problem. That is using
[]->[]
It's easy to use pattern matching to 'select every nth element' for particular cases of n:
every2nd (first:second:rest) = second : every2nd rest
every2nd _ = []
-- >>> every2nd [1..12]
-- [2,4,6,8,10,12]
every3rd (first:second:third:rest) = third : every3rd rest
every3rd _ = []
-- >>> every3rd [1..13]
-- [3,6,9,12]
every4th (first:second:third:fourth:rest) = fourth : every4th rest
every4th _ = []
-- >>> every4th [1..12]
-- [4,8,12]
For the general case, though, we're out of luck, at least with that particular approach. Patterns like those above will need some definite length to be definite patterns. The composed function you mention starts from the thought that we do know how to find every nth member of [1..], namely if it's a multiple of n
multiple n m = m `mod` n == 0
-- >>> filter (multiple 3) [1..12]
-- [3,6,9,12]
So the solution you are trying to understand zips [1..] with the list
index xs = zip [1..] xs
-- >>> index [1..5]
-- [(1,1),(2,2),(3,3),(4,4),(5,5)]
-- >>> index "hello"
-- [(1,'h'),(2,'e'),(3,'l'),(4,'l'),(5,'o')]
Then it filters out just those pairs whose first element is a multiple of n
every_nth_with_index n xs = filter (\(m,a) -> multiple n m) (index xs)
-- >>> every_nth_with_index 3 [1..12]
-- [(3,3),(6,6),(9,9),(12,12)]
-- >>> every_nth_with_index 3 "stackoverflow.com"
-- [(3,'a'),(6,'o'),(9,'r'),(12,'o'),(15,'c')]
Then it gets rid of the ancillary construction, leaving us with just the second element of each pair:
every_nth n xs = map snd (every_nth_with_index n xs)
-- >>> every_nth 3 [1..12]
-- [3,6,9,12]
-- >>> every_nth 3 "stackoverflow.com"
-- "aoroc"
Retracinging our steps we see that this is the same as
everyNth elt = map snd . filter (\(lst,y) -> (mod lst elt) == 0) . zip [1..]
The notorious fold fan strikes again.
everyNth n xs = foldr go (`seq` []) xs n where
go x r 0 = x : r (n - 1)
go _ r k = r (k - 1)
This is very similar to chepner's approach but it integrates the dropping into the recursion. Rewritten without the fold, it's pure pattern matching:
everyNth n = go n where
go k [] = k `seq` []
go 0 (x : xs) = x : go (n - 1) xs
go k (_ : xs) = go (k - 1) xs
With a little cheating, you can define everyNth using pattern matching. Really, we're abstracting out the part that makes pattern matching difficult, as pointed out in Michael's answer.
everyNth n lst = e (shorten lst)
where shorten = drop (n-1) -- here's the cheat
e [] = []
e (first:rest) = first : e (shorten rest)
If you have never seen Haskell before then this takes a bit of explaining.
everyNth :: Int -> [t] -> [t]
everyNth elt = map snd . filter (\(lst,y) -> (mod lst elt) == 0) . zip [1..]
First, note that the type has two arguments, but the definition has only one. This is because the value returned by everyNth is in fact another function. elt is the Int, and the expression in the second line creates a new function that does the job.
Second, note the "." operators. This is an operator that joins two functions together. It is defined like this:
(f . g) x = f (g x)
Here is an equivalent version of the definition with the second argument made explicit:
everyNth elt xs = map snd (filter (\(lst y) -> (mod lst elt) == 0) (zip xs))
When you see a bunch of functions in a chain linked by "." operators you need to read it from right to left. In my second version pay attention to the bracket nesting. zip [1..] xs is the inner-most expression, so it gets evaluated first. It turns a list like ["foo", "bar"] into [(1, "foo"),(2, "bar")]. Then this is filtered to find entries where the number is a multiple of elt. Finally the map snd strips the numbers back out to return just the required entries.
how can i get the most frequent value in a list example:
[1,3,4,5,6,6] -> output 6
[1,3,1,5] -> output 1
Im trying to get it by my own functions but i cant achieve it can you guys help me?
my code:
del x [] = []
del x (y:ys) = if x /= y
then y:del x y
else del x ys
obj x []= []
obj x (y:ys) = if x== y then y:obj x y else(obj x ys)
tam [] = 0
tam (x:y) = 1+tam y
fun (n1:[]) (n:[]) [] =n1
fun (n1:[]) (n:[]) (x:s) =if (tam(obj x (x:s)))>n then fun (x:[]) ((tam(obj x (x:s))):[]) (del x (x:s)) else(fun (n1:[]) (n:[]) (del x (x:s)))
rep (x:s) = fun (x:[]) ((tam(obj x (x:s))):[]) (del x (x:s))
Expanding on Satvik's last suggestion, you can use (&&&) :: (b -> c) -> (b -> c') -> (b -> (c, c')) from Control.Arrow (Note that I substituted a = (->) in that type signature for simplicity) to cleanly perform a decorate-sort-undecorate transform.
mostCommon list = fst . maximumBy (compare `on` snd) $ elemCount
where elemCount = map (head &&& length) . group . sort $ list
The head &&& length function has type [b] -> (b, Int). It converts a list into a tuple of its first element and its length, so when it is combined with group . sort you get a list of each distinct value in the list along with the number of times it occurred.
Also, you should think about what happens when you call mostCommon []. Clearly there is no sensible value, since there is no element at all. As it stands, all the solutions proposed (including mine) just fail on an empty list, which is not good Haskell. The normal thing to do would be to return a Maybe a, where Nothing indicates an error (in this case, an empty list) and Just a represents a "real" return value. e.g.
mostCommon :: Ord a => [a] -> Maybe a
mostCommon [] = Nothing
mostCommon list = Just ... -- your implementation here
This is much nicer, as partial functions (functions that are undefined for some input values) are horrible from a code-safety point of view. You can manipulate Maybe values using pattern matching (matching on Nothing and Just x) and the functions in Data.Maybe (preferable fromMaybe and maybe rather than fromJust).
In case you would like to get some ideas from code that does what you wish to achieve, here is an example:
import Data.List (nub, maximumBy)
import Data.Function (on)
mostCommonElem list = fst $ maximumBy (compare `on` snd) elemCounts where
elemCounts = nub [(element, count) | element <- list, let count = length (filter (==element) list)]
Here are few suggestions
del can be implemented using filter rather than writing your own recursion. In your definition there was a mistake, you needed to give ys and not y while deleting.
del x = filter (/=x)
obj is similar to del with different filter function. Similarly here in your definition you need to give ys and not y in obj.
obj x = filter (==x)
tam is just length function
-- tam = length
You don't need to keep a list for n1 and n. I have also made your code more readable, although I have not made any changes to your algorithm.
fun n1 n [] =n1
fun n1 n xs#(x:s) | length (obj x xs) > n = fun x (length $ obj x xs) (del x xs)
| otherwise = fun n1 n $ del x xs
rep xs#(x:s) = fun x (length $ obj x xs) (del x xs)
Another way, not very optimal but much more readable is
import Data.List
import Data.Ord
rep :: Ord a => [a] -> a
rep = head . head . sortBy (flip $ comparing length) . group . sort
I will try to explain in short what this code is doing. You need to find the most frequent element of the list so the first idea that should come to mind is to find frequency of all the elements. Now group is a function which combines adjacent similar elements.
> group [1,2,2,3,3,3,1,2,4]
[[1],[2,2],[3,3,3],[1],[2],[4]]
So I have used sort to bring elements which are same adjacent to each other
> sort [1,2,2,3,3,3,1,2,4]
[1,1,2,2,2,3,3,3,4]
> group . sort $ [1,2,2,3,3,3,1,2,4]
[[1,1],[2,2,2],[3,3,3],[4]]
Finding element with the maximum frequency just reduces to finding the sublist with largest number of elements. Here comes the function sortBy with which you can sort based on given comparing function. So basically I have sorted on length of the sublists (The flip is just to make the sorting descending rather than ascending).
> sortBy (flip $ comparing length) . group . sort $ [1,2,2,3,3,3,1,2,4]
[[2,2,2],[3,3,3],[1,1],[4]]
Now you can just take head two times to get the element with the largest frequency.
Let's assume you already have argmax function. You can write
your own or even better, you can reuse list-extras package. I strongly suggest you
to take a look at the package anyway.
Then, it's quite easy:
import Data.List.Extras.Argmax ( argmax )
-- >> mostFrequent [3,1,2,3,2,3]
-- 3
mostFrequent xs = argmax f xs
where f x = length $ filter (==x) xs