find primes number starting at 2 Haskell - haskell

Write a function called isPrime that determines if an Integer is a prime number (evenly
divisible only by itself and one). For reference, here’s a list of the primes less than 100:
[2,3,5,7,11,13,17,19,23,29,31,37,41,43,47,53,59,61,67,71,73,79,83,89,97]
What are the 1000th through 1020th prime numbers? (starting at 2)
isPrime :: [Integer]
isPrime = sieve [2..1020]
where
sieve (p:xs)
| p*p <= 1020 = p : sieve [x|x <- xs, x `mod` p > 0]
| otherwise = (p:xs)
I tried this code, but it prints primes 2 through 1020.
I want to show 1000 through 1020 starting at 2

Instead of generating primes up to 1020, to emit the 1000th through 1020th primes, you can generate the first 1020 primes and emit only the last 21 of them.
Using a naive unbounded sieve, we can write the following
minus :: Ord a => [a] -> [a] -> [a]
minus (x:xs) (y:ys) = case (compare x y) of
LT -> x : minus xs (y:ys)
EQ -> minus xs ys
GT -> minus (x:xs) ys
minus xs _ = xs
primes :: [Integer]
primes = eratos [2..]
where
eratos [] = []
eratos (p:xs) = p : eratos (xs `minus` [p, p+p..])
primesFromTo from to = drop (from-1) $ take to primes
Then find primesFromTo 1000 1020:
*Main> primesFromTo 1000 1020
[7919,7927,7933,7937,7949,7951,7963,7993,8009,8011,8017,8039,8053,8059,8069,8081,8087,8089,8093,8101,8111]
As an aside, the naming (isPrimes) is a bit questionable for a list of primes...

Related

Circular prime numbers

I am trying to convert the following function which test the number if it's prime to another one that test if the integer is a circular prime.
eg. 1193 is a circular prime, since 1931, 9311 and 3119 all are also prime.
So i need to rotate the digits of the integer and test if the number is prime or not. any ideas?
note: I am new to Haskell Programming
isPrime :: Integer -> Bool
isPrime 1 = False
isPrime 2 = True
isPrime n
| (length [x | x <- [2 .. n-1], n `mod` x == 0]) > 0 = False
| otherwise = True
isCircPrime :: Integer -> Bool
You can improve the efficiency and elegance of your isPrime function easily by implementing it as:
isPrime :: Integral i => i -> Bool
isPrime 1 = False
isPrime n = all ((/=) 0 . mod n) (takeWhile (\x -> x*x <= n) [2..])
In order to rotate numbers, we can make use of two helper functions here: one to convert a number to a list of digits, and one to convert a list of digits to a number, we do this in reverse, since that is more convenient to implement, but will not matter:
num2dig :: Integral i => i -> [i]
num2dig n | n < 10 = [n]
| otherwise = r : num2dig q
where (q, r) = quotRem n 10
dig2num :: (Foldable t, Num a) => t a -> a
dig2num = foldr ((. (10 *)) . (+)) 0
Now we can make a simple function to generate, for a list of items, all rotations:
import Control.Applicative(liftA2)
import Data.List(inits, tails)
rots :: [a] -> [[a]]
rots = drop 1 . liftA2 (zipWith (++)) tails inits
So we can use this to construct all rotated numbers:
rotnum :: Integral i => i -> [i]
rotnum = map dig2num . rots . num2dig
For example for 1425, the rotated numbers are:
Prelude Control.Applicative Data.List> rotnum 1425
[5142,2514,4251,1425]
I leave using isPrime on these numbers as an exercise.
Referencing your question here, you can achieve what you want by adding a single new function:
check :: Integer -> Bool
check n = and [isPrime (stringToInt cs) | cs <- circle (intToString n)]
This is to add an easier to understand solution from where you already were in your specific code, as I can see you were asking for that specifically. Usage:
*Main> check 1931
True
*Main> check 1019
False
Mind you, I have made some type-changes. I assume you want each function to be type-specific, due to their names. Full code, taken from your example:
circle :: String -> [String]
circle xs = take (length xs) (iterate (\(y:ys) -> ys ++ [y]) xs)
stringToInt :: String -> Integer
stringToInt x = read (x) :: Integer
intToString :: Integer -> String
intToString x = show x
isPrime :: Integer -> Bool
isPrime 1 = False
isPrime 2 = True
isPrime n
| (length [x | x <- [2 .. n-1], n `mod` x == 0]) > 0 = False
| otherwise = True
check :: Integer -> Bool
check n = and [isPrime (stringToInt cs) | cs <- circle (intToString n)]

Haskell optimization program

Have the task
I need to implement the function Change, which will take the value and split it into the possible combinations from list of coins(random list)
Example:
coins = [2,3,7]
GHCi> change 7
[[2,2,3],[2,3,2],[3,2,2],[7]]
That's what I did:
coins :: Num a => [a]
coins = [2, 3, 7]
change :: (Ord a, Num a) => a -> [[a]]
change n = uniqEl (filter (\x -> sum x == n) take ()(subsequences (replic' n coins coins)))
replic' n x y | n == 1 = y
| otherwise = replic' (n-1) x (y ++ x)
uniqEl :: Eq a => [a] -> [a]
uniqEl [] = []
uniqEl (x:xs) = if (x `elem` xs) then uniqEl xs else x : (uniqEl xs)
But this code is very slow. Help to make this program more quickly. As part of the job it is said that this task is easily done with the help of generators lists and recursion. Thank you in advance for your help.
import Data.List
change :: [Int] -> Int -> [[Int]]
change _ 0 = []
change coins n = do
x <- [c | c <- coins, c <= n]
if x == n
then return [x]
else do
xs <- change coins (n - x)
-- if (null xs)
-- then return [x]
-- else if x < (head xs)
-- then []
-- else return (x:xs)
return (x:xs)
change' :: Int -> [[Int]]
change' = change [2,3,7]
test7 = change' 7
test6 = change' 6
test5 = change' 5
test4 = change' 4
You're doing a lot of filtering, eleming and so on, and placing a lot of constraints on the data types.
Think of this more as a dynamic problem, that you constantly need to figure out how many ways there are to return change for a total amount.
Once you have found the amount of possibilities for a specific coin, you can remove it from the list.
Here is my proposed solution wrapped up in one function.
In the list comprehension, note that I assign values to the remaining variable, and that these values range from [0,total], with jumps every x, where x is the denomination.
For example, if you had to calculate how many times $0.25 goes into a $2 total, that list comprehension ends up doing:
[countChange 2, countChange 1.75,countChange 1.5, countChange 1.25,...], but also these next iterations of countChange don't include the 0.25 coin - because we just "tested" that.
-- Amount to return -> List of Coin denominations available
countChange :: Integer -> [Integer] -> Integer
countChange _ [] = 0 -- No coins at all, so no change can be given
countChange 0 _ = 1 -- Only one way to return 0 change
countChange total (x:xs) = sum [countChange (total-remaining) xs | remaining <- [0,x..total]]
Use MemoCombinators. This is fast ! Pls. try change 100
import Data.List
import qualified Data.MemoCombinators as Memo
coins :: [Int]
coins = [2,3,7]
change :: Int -> [[Int]]
change = Memo.integral change'
change' 0 = []
change' n = do
x <- [c | c <- coins, c <= n]
if x == n
then return [x]
else do
xs <- change (n - x)
-- if (null xs)
-- then return [x]
-- else if x < (head xs)
-- then []
-- else return (x:xs)
return (x:xs)

Prime factors in Haskell

I'm new to Haskell.
How to generate a list of lists which contains prime factors of next integers?
Currently, I only know how to generate prime numbers:
primes = map head $ iterate (\(x:xs) -> [y | y<-xs, y `mod` x /= 0 ]) [2..]
A simple approach to determine the prime factors of n is to
search for the first divisor d in [2..n-1]
if D exists: return d : primeFactors(div n d)
otherwise return n (since n is prime)
Code:
prime_factors :: Int -> [Int]
prime_factors 1 = []
prime_factors n
| factors == [] = [n]
| otherwise = factors ++ prime_factors (n `div` (head factors))
where factors = take 1 $ filter (\x -> (n `mod` x) == 0) [2 .. n-1]
This obviously could use a lot of optimization (search only from 2 to sqrt(N), cache the prime numbers found so far and compute the division only for these etc.)
UPDATE
A slightly modified version using case (as suggested by #user5402):
prime_factors n =
case factors of
[] -> [n]
_ -> factors ++ prime_factors (n `div` (head factors))
where factors = take 1 $ filter (\x -> (n `mod` x) == 0) [2 .. n-1]
Until the dividend m < 2,
take the first divisor n from primes.
repeat dividing m by n while divisible.
take the next divisor n from primes, and go to 2.
The list of all divisors actually used are prime factors of original m.
Code:
-- | prime factors
--
-- >>> factors 13
-- [13]
-- >>> factors 16
-- [2,2,2,2]
-- >>> factors 60
-- [2,2,3,5]
--
factors :: Int -> [Int]
factors m = f m (head primes) (tail primes) where
f m n ns
| m < 2 = []
| m `mod` n == 0 = n : f (m `div` n) n ns
| otherwise = f m (head ns) (tail ns)
-- | primes
--
-- >>> take 10 primes
-- [2,3,5,7,11,13,17,19,23,29]
--
primes :: [Int]
primes = f [2..] where f (p : ns) = p : f [n | n <- ns, n `mod` p /= 0]
Update:
This replacement code improves performance by avoiding unnecessary evaluations:
factors m = f m (head primes) (tail primes) where
f m n ns
| m < 2 = []
| m < n ^ 2 = [m] -- stop early
| m `mod` n == 0 = n : f (m `div` n) n ns
| otherwise = f m (head ns) (tail ns)
primes can also be sped up drastically, as mentioned in Will Ness's comment:
primes = 2 : filter (\n-> head (factors n) == n) [3,5..]
This is a good-performanced and easy-to-understand implementation, in which isPrime and primes are defined recursively, and primes will be cached by default. primeFactors definition is just a proper use of primes, the result will contains continuous-duplicated numbers, this feature makes it easy to count the number of each factor via (map (head &&& length) . group) and it's easy to unique it via (map head . group) :
isPrime :: Int -> Bool
primes :: [Int]
isPrime n | n < 2 = False
isPrime n = all (\p -> n `mod` p /= 0) . takeWhile ((<= n) . (^ 2)) $ primes
primes = 2 : filter isPrime [3..]
primeFactors :: Int -> [Int]
primeFactors n = iter n primes where
iter n (p:_) | n < p^2 = [n | n > 1]
iter n ps#(p:ps') =
let (d, r) = n `divMod` p
in if r == 0 then p : iter d ps else iter n ps'
And the usage:
> import Data.List
> import Control.Arrow
> primeFactors 12312
[2,2,2,3,3,3,3,19]
> (map (head &&& length) . group) (primeFactors 12312)
[(2,3),(3,4),(19,1)]
> (map head . group) (primeFactors 12312)
[2,3,19]
Haskell allows you to create infinite lists, that are mutually recursive. Let's take an advantage of this.
First let's create a helper function that divides a number by another as much as possible. We'll need it, once we find a factor, to completely eliminate it from a number.
import Data.Maybe (mapMaybe)
-- Divide the first argument as many times as possible by the second one.
divFully :: Integer -> Integer -> Integer
divFully n q | n `mod` q == 0 = divFully (n `div` q) q
| otherwise = n
Next, assuming we have somewhere the list of all primes, we can easily find factors of a numbers by dividing it by all primes less than the square root of the number, and if the number is divisible, noting the prime number.
-- | A lazy infinite list of non-trivial factors of all numbers.
factors :: [(Integer, [Integer])]
factors = (1, []) : (2, [2]) : map (\n -> (n, divisors primes n)) [3..]
where
divisors :: [Integer] -> Integer -> [Integer]
divisors _ 1 = [] -- no more divisors
divisors (p:ps) n
| p^2 > n = [n] -- no more divisors, `n` must be prime
| n' < n = p : divisors ps n' -- divides
| otherwise = divisors ps n' -- doesn't divide
where
n' = divFully n p
Conversely, when we have the list of all factors of numbers, it's easy to find primes: They are exactly those numbers, whose only prime factor is the number itself.
-- | A lazy infinite list of primes.
primes :: [Integer]
primes = mapMaybe isPrime factors
where
-- | A number is prime if it's only prime factor is the number itself.
isPrime (n, [p]) | n == p = Just p
isPrime _ = Nothing
The trick is that we start the list of factors manually, and that to determine the list of prime factors of a number we only need primes less then its square root. Let's see what happens when we consume the list of factors a bit and we're trying to compute the list of factors of 3. We're consuming the list of primes, taking 2 (which can be computed from what we've given manually). We see that it doesn't divide 3 and that since it's greater than the square root of 3, there are no more possible divisors of 3. Therefore the list of factors for 3 is [3]. From this, we can compute that 3 is another prime. Etc.
I just worked on this problem. Here's my solution.
Two helping functions are
factors n = [x | x <- [1..n], mod n x == 0]
isPrime n = factors n == [1,n]
Then using a list comprehension to get all prime factors and how many are they.
prime_factors num = [(last $ takeWhile (\n -> (x^n) `elem` (factors num)) [1..], x) | x <- filter isPrime $ factors num]
where
x <- filter isPrime $ factors num
tells me what prime factors the given number has, and
last $ takeWhile (\n -> (x^n) `elem` (factors num)) [1..]
tells me how many this factor is.
Examples
> prime_factors 36 -- 36 = 4 * 9
[(2,2),(2,3)]
> prime_factors 1800 -- 1800 = 8 * 9 * 25
[(3,2),(2,3),(2,5)]
More elegant code,use 2 and odd numbers to divide the number.
factors' :: Integral t => t -> [t]
factors' n
| n < 0 = factors' (-n)
| n > 0 = if 1 == n
then []
else let fac = mfac n 2 in fac : factors' (n `div` fac)
where mfac m x
| rem m x == 0 = x
| x * x > m = m
| otherwise = mfac m (if odd x then x + 2 else x + 1)
Here's my version. Not as concise as the others, but I think it's very readable and easy to understand.
import Data.List
factor :: Int -> [Int]
factor n
| n <= 1 = []
| even n = 2 : factor(div n 2)
| otherwise =
let root = floor $ sqrt $ fromIntegral n
in
case find ((==) 0 . mod n) [3, 5.. root] of
Nothing -> [n]
Just fac -> fac : factor(div n fac)
I'm sure this code is ugly enough to drive a real Haskell programmer to tears, but it works in GHCI 9.0.1 to provide prime factors with a count of each prime factor.
import Data.List
factors n = [x | x <- [2..(n`div` 2)], mod n x == 0] ++ [n]
factormap n = fmap factors $ factors n
isPrime n = case factormap n of [a] -> True; _ -> False
primeList (x:xs) = filter (isPrime) (x:xs)
numPrimes n a = length $ (factors n) `intersect` (takeWhile ( <=n) $ iterate (a*) a)
primeFactors n = primeList $ factors n
result1 n = fmap (numPrimes n) (primeFactors n)
answer n = ((primeFactors n),(result1 n))
Example:
ghci> answer 504
([2,3,7],[3,2,1])
The answer is a list of prime factors and a second list showing how many times each
prime factor is in the submitted number.

Double every other element of list from right in Haskell

I have a list and I want to double every other element in this list from the right.
There is another related question that solves this problem but it doubles from the left, not the right: Haskell: Double every 2nd element in list
For example, in my scenario, [1,2,3,4] would become [2,2,6,4], and in that question, [1,2,3,4] would become [1,4,3,8].
How would I implement this?
I think that the top answer misinterpreted the question. The title clearly states that the OP wants to double the second, fourth, etc. elements from the right of the list. Ørjan Johansen's answer is correct, but slow. Here is my more efficient solution:
doubleFromRight :: [Integer] -> [Integer]
doubleFromRight xs = fst $ foldr (\x (acc, bool) ->
((if bool then 2 * x else x) : acc,
not bool)) ([], False) xs
It folds over the list from the right. The initial value is a tuple containing the empty list and a boolean. The boolean starts as false and flips every time. The value is multiplied by 2 only if the boolean is true.
OK, as #TomEllis mentions, everyone else seems to have interpreted your question as about odd-numbered elements from the left, instead of as even-numbered from the right, as your title implies.
Since you start checking positions from the right, there is no way to know what to double until the end of the list has been found. So the solution cannot be lazy, and will need to temporarily store the entire list somewhere (even if just on the execution stack) before returning anything.
Given this, the simplest solution might be to just apply reverse before and after the from-left solution:
doubleFromRight = reverse . doubleFromLeft . reverse
Think about it.
double = zipWith ($) (cycle [(*2),id])
EDIT I should note, this isn't really my solution it is the solution of the linked post with the (*2) and id flipped. That's why I said think about it because it was such a trivial fix.
A direct implementation would be:
doubleOddElements :: [Int] -> [Int]
doubleOddElements [] = []
doubleOddElements [x] = [2 * x]
doubleOddElements (x:y:xs) = (2*x):y:(doubleOddElements xs)
Okay, so not elegant or efficient like the other answers, but I wrote this from a beginners standpoint (I am one) in terms of readability and basic functionality.
This doubles every second number, beginning from the right.
Using this script: doubleEveryOther [1,3,6,9,12,15,18] produces [1,6,6,18,12,30,18] and doubleEveryOther [1,3,6,9,12,15] produces [2,3,12,9,24,15]
doubleEveryOther :: [Integer] -> [Integer]
doubleEveryOther [] = []
doubleEveryOther (x:[]) = [x]
doubleEveryOther (x:y:zs)
| (length (x:y:zs)) `mod` 2 /= 0 = x : y*2 : doubleEveryOther zs
| otherwise = x*2 : y : doubleEveryOther zs
Trying to generalize the problem a bit: Since we want to double every 2nd element from the end, we can't know in advance if it'll be every odd or even from the start. So the easiest way is to construct both, count if the overall size is even or odd, and then decide.
Let's define an Applicative data structure that captures:
Having two variants of values,
keeping the parity of the length (odd/even), and
alternating the two when two such values are combined,
as follows:
import Control.Applicative
import Data.Monoid
import qualified Data.Traversable as T
data Switching m = Switching !Bool m m
deriving (Eq, Ord, Show)
instance Functor Switching where
fmap f (Switching b x y) = Switching b (f x) (f y)
instance Applicative Switching where
pure x = Switching False x x
(Switching False f g) <*> (Switching b2 x y) = Switching b2 (f x) (g y)
(Switching True f g) <*> (Switching b2 x y) = Switching (not b2) (f y) (g x)
So traversing a list will yield two lists looking like this:
x1 y2 x3 y4 ...
y1 x2 y3 x4 ...
two zig-zag-ing copies. Now we can compute
double2 :: (Num m) => m -> Switching m
double2 x = Switching True (2 * x) x
double2ndRight :: (Num m, T.Traversable f) => f m -> f m
double2ndRight k = case T.traverse double2 k of
Switching True _ y -> y
Switching False x _ -> x
Here are mine two solutions, note that I'm complete beginner in Haskell.
First one uses list functions, head, tail and lenght:
doubleSecondFromEnd :: [Integer] -> [Integer]
doubleSecondFromEnd [] = [] -- Do nothing on empty list
doubleSecondFromEnd n
| length n `mod` 2 == 0 = head n * 2 : doubleSecondFromEnd (tail n)
| otherwise = head n : doubleSecondFromEnd (tail n)
Second one, similar but with a different approach only uses length function:
doubleSecondFromEnd2 :: [Integer] -> [Integer]
doubleSecondFromEnd2 [] = [] -- Do nothing on empty list
doubleSecondFromEnd2 (x:y)
| length y `mod` 2 /= 0 = x * 2 : doubleSecondFromEnd2 y
| otherwise = x : doubleSecondFromEnd2 y
I am just learning Haskell so please find the following beginner solution. I try to use limited cool functions like zipWith , cycle, or reverse
doubleEveryOther :: [Integer] -> [Integer]
doubleEveryOther [] = []
doubleEveryOther s#(x:xs)
| (length s) `mod` 2 == 0 = (x * 2) : (doubleEveryOther xs)
| otherwise = x : (doubleEveryOther xs)
The key thing to note that when doubling every element from the right you can put the doubling into two cases:
If the list is even length, you will ultimately end up doubling the first element of the list.
If the list is odd length, you will not be doubling the first element of the list.
I answered this as part of the homework assignment from CS194
My first thought was:
doubleOdd (x:xs) = (2*x):(doubleEven xs)
doubleOdd [] = []
doubleEven (x:xs) = x:(doubleOdd xs)
doubleEven [] = []
DiegoNolan's solution is more elegant, in that the function and sequence length are more easily altered, but it took me a moment to grok.
Adding the requirement to operate from the right makes it a little more complex. foldr is a neat starting point for doing something from the right, so let me try:
doubleOddFromRight = third . foldr builder (id,double,[])
where third (_,_,x) = x
builder x (fx,fy,xs) = (fy, fx, fx x : xs)
double x = 2 * x
This swaps the two functions fx and fy for each entry. To find the value of any entry will require a traversal to the end of the list, finding whether the length was odd or even.
This is my answer to this CIS 194 homework assignment. It's implemented using just the stuff that was introduced in lecture 1 + reverse.
doubleEveryOtherLeftToRight :: [Integer] -> [Integer]
doubleEveryOtherLeftToRight [] = []
doubleEveryOtherLeftToRight (x:[]) = [x]
doubleEveryOtherLeftToRight (x:y:zs) = x:y*2:(doubleEveryOtherLeftToRight zs)
doubleEveryOther :: [Integer] -> [Integer]
doubleEveryOther xs = reverse (doubleEveryOtherLeftToRight (reverse xs))
How about this for simplicity?
doubleEveryOtherRev :: [Integer] -> [Integer]
doubleEveryOtherRev l = doubleRev (reverse l) []
where
doubleRev [] a = a
doubleRev (x:[]) a = (x:a)
doubleRev (x:y:zs) a = doubleRev zs (2*y:x:a)
You would have to feed a reversed list of digits, in case you followed that course's recommendation, because it will double every other element as it reverses again. I think that this is different than using twice the reverse function, with another to double every other digit in between, because you won't need to know the full extent of their list by the second time. In other words, it solves that course's problem, but someone correct me if I'm wrong.
We can also do it like this:
doubleEveryOther = reverse . zipWith (*) value . reverse
where
value = 1 : 2 : value
Some answers seems not deal with odd/even length of list.
doubleEveryOtherEvenList = zipWith ($) (cycle [(*2),id])
doubleEveryOther :: [Int] -> [Int]
doubleEveryOther n
| length n `mod` 2 == 0 = doubleEveryOtherEvenList n
| otherwise = (head n) : doubleEveryOtherEvenList (tail n)
Taking an edx course in haskell, this is my noob solution.
doubleSecondR :: [Integer] -> [Integer]
doubleSecondR xs = reverse(zipWith (*) (reverse xs) ys)
where ys = repeat' [1,2]
repeat' :: [a] -> [a]
repeat' xs = xs ++ repeat' xs
I'm too coming to this question from the CIS 194 course.
I did this two ways. First I figured that the point of the question should only rely on functions or ways of programming mentioned in either of the 3 possible sources listed. The course lecture 1, Real World Haskell ch. 1,2 and Learn You a Haskell ch. 2.
So OK:
Recursion, conditionals
reverse, basic functions like max, min, odd, even
list functions e.g. head, tail, ...
Not OK:
foldr, foldl, map
Higher Order functions
Anything beyond these
First solution, just using recursion with a counter:
doubleEveryOther :: [Integer] -> [Integer]
doubleEveryOther xs = loopDoubles xs 1
loopDoubles :: [Integer] -> Integer -> [Integer]
loopDoubles [] _ = []
loopDoubles xs n = loopDoubles (init xs) (n + 1) ++ [doubleEven (last xs) n]
doubleEven :: Integer -> Integer -> Integer
doubleEven x n = if even n then x * 2 else x
This method uses recursion, but avoids calculating the length at each level of the recursion.
Second method breaking the aforemention rules of mine:
doubleEveryOther' :: [Integer] -> [Integer]
doubleEveryOther' xs = map (\x -> if even (fst x) then (snd x) * 2 else snd x) $ zip (reverse [1..n]) xs
where n = length(xs)
This second one works by building up a reversed set of indexes and then mapping over these. This does calculate the length but only once.
e.g. [1,1,1,1] -> [(4,1),(3,1),(2,1),(1,1)]
Both of these are following the requirement of doubling every other element from the right.
> doubleEveryOther [1,2,3,4]
[2,2,6,4]
> doubleEveryOther [1,2,3]
[1,4,3]
> doubleEveryOther' [1,2,3,4]
[2,2,6,4]
> doubleEveryOther' [1,2,3]
[1,4,3]
I'm guessing the OP posed this question while researching an answer to the Homework 1 assignment from Haskell CIS194 Course. Very little Haskell has been imparted to the student at that stage of the course, so while the above answers are correct, they're beyond the comprehension of the learning student because elements such as lambdas, function composition (.), and even library routines like length and reverse haven't been introduced yet. Here is an answer that matches the stage of teaching in the course:
doubleEveryOtherEven :: [Integer] -> [Integer]
doubleEveryOtherEven [] = []
doubleEveryOtherEven (x:y:xs) = x*2 : y : doubleEveryOtherEven xs
doubleEveryOtherOdd :: [Integer] -> [Integer]
doubleEveryOtherOdd (x:[]) = [x]
doubleEveryOtherOdd (x:y:xs) = x : y*2 : doubleEveryOtherOdd xs
integerListLen :: [Integer] -> Integer
integerListLen [] = 0
integerListLen (x:xs) = 1 + integerListLen xs
doubleEveryOther :: [Integer] -> [Integer]
doubleEveryOther xs
| integerListLen xs `mod` 2 == 0 = doubleEveryOtherEven xs -- also handles empty list case
| otherwise = doubleEveryOtherOdd xs
The calculation requires foreknowledge on whether the list has an even or odd number of elements, to determine which digit in each pair of digits should be doubled. However, basic Haskell pattern-matching only permits matching list elements from left-to-right (example: x:xs), which means you can't determine if there are an odd or even number of elements until you've reached the end of the list, but by then it's too late since you need to do calculations on each left-hand pair of elements while working through the list to reach the end.
The solution is to split the doubling logic into two functions - one which handles even-length lists and another which handles odd-length lists. A third function is needed to determine which of those two functions to call for a given list, which in turn needs an additional function that can calculate the length of the list so we can establish whether the list has an odd or even number of elements (again, since the length library function hasn't been introduced at this stage of the course).
This solution is also in keeping with the advisory in the Week 1 lesson, which states: "It’s good Haskell style to build up more complex functions by combining many simple ones."
Here is my answer for CIS 194 homework1.
I took idea from toDigits and toDigitsRev. It's not fancy, but works.
takeLastTwo :: [Int] -> [Int]
takeLastTwo [] = []
takeLastTwo (x : y : []) = [x, y]
takeLastTwo (x : xs) = takeLastTwo xs
removeLastTwo :: [Int] -> [Int]
removeLastTwo [] = []
removeLastTwo (x : y : []) = []
removeLastTwo (x : xs) = x : removeLastTwo xs
doubleEveryOther :: [Int] -> [Int]
doubleEveryOther [] = []
doubleEveryOther (x : []) = [x]
doubleEveryOther (x : y : []) = (2 * x) : y : []
doubleEveryOther xs = doubleEveryOther (removeLastTwo xs) ++ doubleEveryOther (takeLastTwo xs)

Sieve of Eratosthenes in Haskell

I'm solving some classic problems in Haskell to develop my functional
skills and I have a problem to implement an optimization suggested at this "Programming Praxis" site:
I have three solutions to this problem and the third one is too slow
compared to the second solution. Can someone suggest some improvements to
my code?
My implementations are:
-- primeira implementação
primes n
| n < 2 = []
| n == 2 = [2]
| n `mod` 2 == 0 = primes'
| otherwise = if (find (\x -> n `mod` x == 0) primes') == Nothing then
n:primes'
else
primes'
where primes' = primes (n - 1)
-- segunda implementação
primes' :: Integer -> [Integer]
primes' n = sieve $ 2 : [3,5..n]
where sieve :: [Integer] -> [Integer]
sieve [] = []
sieve l#(x:xs)
| x*x >= n = l
| otherwise = x : sieve list'
where list' = filter (\y -> y `mod` x /= 0) xs
-- terceira implementação
primes'' :: Integer -> [Integer]
primes'' n = 2 : sieve 3 [3,5..n]
where sieve :: Integer -> [Integer] -> [Integer]
sieve _ [] = []
sieve m l#(x:xs)
| m*m >= n = l
| x < m*m = x : sieve m xs
| otherwise = sieve (m + 2) list'
where list'= filter (\y -> y `mod` m /= 0) l
Looks to me like the problem with your third revision is how you choose the next element to sift on.
You indiscriminately increment by 2. The problem is that you then sift on unnecessary numbers.
for example, in this version your eventually going to pass 9 as m, and you're going to do an extra recursion to filter on 9, even though it isn't even in the list, and thus you should have never picked it in the first place (since it would have been removed in the very first filter on 3)
Even though the second version doesn't start the filtering past the square of the number it sifts on, it never chooses an unnecessary sifting value.
In other words, I think you end up sifting on every odd number between 3 and n. Instead you should be sifting on every odd number that hasn't already been removed by a previous pass.
I think to correctly implement the optimization of starting the sieve at the square of the current sift value, you have to retain the front of the list while sifting on the back where back contains the elements >= the square of the sift value. I think this would force you to use concatenations, and I'm not so sure that the optimization is good enough to cancel out the overhead induced by using ++.
First of all, mod is slow so use rem in situations where it doesn't matter (when you aren't dealing with negatives, basically). Secondly, use Criterion to show (to yourself) what is faster and what changes are actually optimizations. I know I'm not giving a full answer to you question with this, but its a good place for you (and other potential answerers) to start, so here's some code:
import List
import Criterion.Main
main = do
str <- getLine
let run f = length . f
input = read str :: Integer
defaultMain [ bench "primes" (nf (run primes) input)
, bench "primes'" (nf (run primes') input)
, bench "primes''" (nf (run primes'') input)
, bench "primesTMD" (nf (run primesTMD) input)
, bench "primes'TMD" (nf (run primes'TMD) input)
, bench "primes''TMD" (nf (run primes''TMD) input)
]
putStrLn . show . length . primes'' $ (read str :: Integer)
-- primeira implementação
primes n
| n < 2 = []
| n == 2 = [2]
| n `mod` 2 == 0 = primes'
| otherwise = if (find (\x -> n `mod` x == 0) primes') == Nothing then
n:primes'
else
primes'
where primes' = primes (n - 1)
primesTMD n
| n < 2 = []
| n == 2 = [2]
| n `mod` 2 == 0 = primes'
| otherwise = if (find (\x -> n `rem` x == 0) primes') == Nothing then
n:primes'
else
primes'
where primes' = primesTMD (n - 1)
-- segunda implementação
primes' :: Integer -> [Integer]
primes' n = sieve $ 2 : [3,5..n]
where sieve :: [Integer] -> [Integer]
sieve [] = []
sieve l#(x:xs)
| x*x >= n = l
| otherwise = x : sieve list'
where list' = filter (\y -> y `mod` x /= 0) xs
primes'TMD :: Integer -> [Integer]
primes'TMD n = sieve $ 2 : [3,5..n]
where sieve :: [Integer] -> [Integer]
sieve [] = []
sieve l#(x:xs)
| x*x >= n = l
| otherwise = x : sieve list'
where list' = filter (\y -> y `rem` x /= 0) xs
-- terceira implementação
primes'' :: Integer -> [Integer]
primes'' n = 2 : sieve 3 [3,5..n]
where sieve :: Integer -> [Integer] -> [Integer]
sieve _ [] = []
sieve m l#(x:xs)
| m*m >= n = l
| x < m*m = x : sieve m xs
| otherwise = sieve (m + 2) list'
where list'= filter (\y -> y `mod` m /= 0) l
primes''TMD :: Integer -> [Integer]
primes''TMD n = 2 : sieve 3 [3,5..n]
where sieve :: Integer -> [Integer] -> [Integer]
sieve _ [] = []
sieve m l#(x:xs)
| m*m >= n = l
| x < m*m = x : sieve m xs
| otherwise = sieve (m + 2) list'
where list'= filter (\y -> y `rem` m /= 0) l
Notice the improved runtime of the variants using rem:
$ ghc --make -O2 sieve.hs
$./sieve
5000
...
benchmarking primes
mean: 23.88546 ms, lb 23.84035 ms, ub 23.95000 ms
benchmarking primes'
mean: 775.9981 us, lb 775.4639 us, ub 776.7081 us
benchmarking primes''
mean: 837.7901 us, lb 836.7824 us, ub 839.0260 us
benchmarking primesTMD
mean: 16.15421 ms, lb 16.11955 ms, ub 16.19202 ms
benchmarking primes'TMD
mean: 568.9857 us, lb 568.5819 us, ub 569.4641 us
benchmarking primes''TMD
mean: 642.5665 us, lb 642.0495 us, ub 643.4105 us
While I see you are doing this for your own education, its worth noting the related links of Primes on Haskell.org and the fast Primes package on hackage.
This is not optimized but expressive implementation: check video Sieve of Eratosthenes in haskell
import qualified Data.Set as Set(fromList,difference)
kr n l = (*n) <$> [2..l `div` n]
g n = difference (fromList [2..n]) (fromList $ concat $ ((flip kr) n) <$> [2..n])

Resources