Fix ghc warnings
This commit is contained in:
parent
71783f4043
commit
3e09b8147e
@ -3,13 +3,15 @@
|
||||
|
||||
module P003 (p003) where
|
||||
|
||||
import Data.List (uncons)
|
||||
import Data.Maybe (fromJust)
|
||||
import ProjectEuler (isPrime)
|
||||
|
||||
maxPrimeFactor :: Int -> Int
|
||||
maxPrimeFactor n
|
||||
| isPrime n = n
|
||||
| even n = maxPrimeFactor $ n `div` 2
|
||||
| otherwise = maxPrimeFactor $ n `div` head [i | i <- [3, 5 ..], n `mod` i == 0 && isPrime i]
|
||||
| otherwise = maxPrimeFactor $ n `div` (fst . fromJust $ uncons [i | i <- [3, 5 ..], n `mod` i == 0 && isPrime i])
|
||||
|
||||
p003 :: IO ()
|
||||
p003 = do
|
||||
|
@ -13,7 +13,7 @@
|
||||
module P006 (p006) where
|
||||
|
||||
sumSquareDiff :: Int -> Int
|
||||
sumSquareDiff n = (sum [1 .. n] ^ 2) - sum (map (^ 2) [1 .. n])
|
||||
sumSquareDiff n = (sum [1 .. n] ^ (2 :: Int)) - sum (map (^ (2 :: Int)) [1 .. n])
|
||||
|
||||
p006 :: IO ()
|
||||
p006 = do
|
||||
|
@ -30,7 +30,7 @@ import Data.Char (digitToInt)
|
||||
nDigitProduct :: Int -> String -> Int
|
||||
nDigitProduct n s
|
||||
| length s < n = -1
|
||||
| otherwise = max (product (map digitToInt (take n s))) (nDigitProduct n (tail s))
|
||||
| otherwise = max (product (map digitToInt (take n s))) (nDigitProduct n (drop 1 s))
|
||||
|
||||
p008 :: IO ()
|
||||
p008 = do
|
||||
|
@ -10,8 +10,11 @@
|
||||
|
||||
module P009 (p009) where
|
||||
|
||||
import Data.List (uncons)
|
||||
import Data.Maybe (fromJust)
|
||||
|
||||
pythagoreanTriplet :: Int -> (Int, Int, Int)
|
||||
pythagoreanTriplet n = head [(x, y, z) | x <- [1 .. n], y <- [x .. n], z <- [y .. n], x + y + z == n, x ^ 2 + y ^ 2 == z ^ 2]
|
||||
pythagoreanTriplet n = fst . fromJust $ uncons [(x, y, z) | x <- [1 .. n], y <- [x .. n], z <- [y .. n], x + y + z == n, x ^ (2 :: Int) + y ^ (2 :: Int) == z ^ (2 :: Int)]
|
||||
|
||||
prodTriplet :: (Int, Int, Int) -> Int
|
||||
prodTriplet (x, y, z) = x * y * z
|
||||
|
@ -8,7 +8,7 @@ import ProjectEuler (primeSieve)
|
||||
|
||||
p010 :: IO ()
|
||||
p010 = do
|
||||
let result = sum $ takeWhile (< 2000000) primeSieve
|
||||
let result = sum $ takeWhile (< 2000000) primeSieve :: Int
|
||||
putStrLn $
|
||||
"Project Euler, Problem 10\n"
|
||||
++ "Answer: "
|
||||
|
@ -24,6 +24,7 @@
|
||||
-- The product of these numbers is 26 × 63 × 78 × 14 = 1788696.
|
||||
--
|
||||
-- What is the greatest product of four adjacent numbers in the same direction (up, down, left, right, or diagonally) in the 20×20 grid?
|
||||
{-# OPTIONS_GHC -Wno-incomplete-patterns #-}
|
||||
|
||||
module P011 (p011) where
|
||||
|
||||
@ -32,12 +33,12 @@ import Data.List (transpose)
|
||||
diagonals :: [[Int]] -> [[Int]]
|
||||
diagonals xs = diagonals' xs ++ diagonals' ((transpose . reverse) xs)
|
||||
where
|
||||
diagonals' xs =
|
||||
transpose (zipWith drop [0 ..] xs)
|
||||
++ transpose (zipWith drop [1 ..] (transpose xs))
|
||||
diagonals' x =
|
||||
transpose (zipWith drop [0 ..] x)
|
||||
++ transpose (zipWith drop [1 ..] (transpose x))
|
||||
|
||||
maxProd4 :: [Int] -> Int
|
||||
maxProd4 [x, y, z] = 0
|
||||
maxProd4 [_, _, _] = 0
|
||||
maxProd4 (w : x : y : z : xs) = max (w * x * y * z) (maxProd4 (x : y : z : xs))
|
||||
|
||||
p011 :: IO ()
|
||||
|
@ -19,14 +19,15 @@
|
||||
|
||||
module P012 (p012) where
|
||||
|
||||
import Data.List (nub)
|
||||
import Data.List (uncons)
|
||||
import Data.Maybe (fromJust)
|
||||
import ProjectEuler (countDivisors)
|
||||
|
||||
triangNumbers :: [Int]
|
||||
triangNumbers = scanl1 (+) [1 ..]
|
||||
|
||||
triang500 :: Int
|
||||
triang500 = head [x | x <- triangNumbers, countDivisors x > 500]
|
||||
triang500 = fst . fromJust $ uncons [x | x <- triangNumbers, countDivisors x > 500]
|
||||
|
||||
p012 :: IO ()
|
||||
p012 = do
|
||||
|
@ -13,6 +13,7 @@
|
||||
-- Which starting number, under one million, produces the longest chain?
|
||||
--
|
||||
-- NOTE: Once the chain starts the terms are allowed to go above one million.
|
||||
{-# OPTIONS_GHC -Wno-incomplete-patterns #-}
|
||||
|
||||
module P014 (p014) where
|
||||
|
||||
|
@ -3,13 +3,13 @@
|
||||
|
||||
module P015 (p015) where
|
||||
|
||||
factorial :: (Integral a) => a -> a
|
||||
factorial :: Integer -> Integer
|
||||
factorial 0 = 1
|
||||
factorial n = n * factorial (n - 1)
|
||||
|
||||
p015 :: IO ()
|
||||
p015 = do
|
||||
let result = factorial 40 `div` factorial 20 ^ 2
|
||||
let result = factorial 40 `div` factorial 20 ^ (2 :: Int)
|
||||
putStrLn $
|
||||
"Project Euler, Problem 15\n"
|
||||
++ "Answer: "
|
||||
|
@ -1,6 +1,7 @@
|
||||
-- 2^15 = 32768 and the sum of its digits is 3 + 2 + 7 + 6 + 8 = 26.
|
||||
--
|
||||
-- What is the sum of the digits of the number 2^1000?
|
||||
{-# OPTIONS_GHC -Wno-type-defaults #-}
|
||||
|
||||
module P016 (p016) where
|
||||
|
||||
@ -8,7 +9,7 @@ import ProjectEuler (digitSum)
|
||||
|
||||
p016 :: IO ()
|
||||
p016 = do
|
||||
let result = digitSum $ 2 ^ 1000
|
||||
let result = digitSum $ 2 ^ (1000 :: Int)
|
||||
putStrLn $
|
||||
"Project Euler, Problem 16\n"
|
||||
++ "Answer: "
|
||||
|
@ -9,7 +9,7 @@ module P020 (p020) where
|
||||
|
||||
import ProjectEuler (digitSum)
|
||||
|
||||
factorial :: (Integral a) => a -> a
|
||||
factorial :: Integer -> Integer
|
||||
factorial 0 = 1
|
||||
factorial n = n * factorial (n - 1)
|
||||
|
||||
|
@ -10,13 +10,10 @@ module P021 (p021) where
|
||||
|
||||
import ProjectEuler (sumProperDivisors)
|
||||
|
||||
properDivisors :: (Integral a) => a -> [a]
|
||||
properDivisors n = [x | x <- [1 .. n - 1], n `mod` x == 0]
|
||||
|
||||
amicable :: (Integral a) => a -> a -> Bool
|
||||
amicable :: Int -> Int -> Bool
|
||||
amicable x y = x /= y && sumProperDivisors x == y && sumProperDivisors y == x
|
||||
|
||||
sumAmicable :: (Integral a) => a -> a
|
||||
sumAmicable :: Int -> Int
|
||||
sumAmicable n = sum [x | x <- [1 .. n - 1], amicable x $ sumProperDivisors x]
|
||||
|
||||
p021 :: IO ()
|
||||
|
@ -19,7 +19,7 @@ nameScore s =
|
||||
|
||||
p022 :: IO ()
|
||||
p022 = do
|
||||
contents <- readFile "p022_names.txt"
|
||||
contents <- readFile "input/p022_names.txt"
|
||||
let name_scores = map nameScore . sort . splitOn "," $ filter (/= '"') contents
|
||||
result = sum $ zipWith (*) name_scores [1 ..]
|
||||
putStrLn $
|
||||
|
@ -16,15 +16,15 @@ import Data.List ((\\))
|
||||
import qualified Data.Set as Set
|
||||
import ProjectEuler (sumProperDivisors)
|
||||
|
||||
isAbundant :: (Integral a) => a -> Bool
|
||||
isAbundant :: Int -> Bool
|
||||
isAbundant n = sumProperDivisors n > n
|
||||
|
||||
abundantSums :: (Integral a) => [a]
|
||||
abundantSums :: [Int]
|
||||
abundantSums = Set.toList $ Set.fromList [x + y | x <- abundantList, y <- abundantList, x + y <= 28123, y >= x]
|
||||
where
|
||||
abundantList = [x | x <- [12 .. 28123], isAbundant x]
|
||||
|
||||
sumNotAbundant :: (Integral a) => a
|
||||
sumNotAbundant :: Int
|
||||
sumNotAbundant = sum $ [1 .. 28123] \\ abundantSums
|
||||
|
||||
p023 :: IO ()
|
||||
|
@ -22,8 +22,9 @@
|
||||
module P025 (p025) where
|
||||
|
||||
fibs :: [Integer]
|
||||
fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
|
||||
fibs = 0 : 1 : zipWith (+) fibs (drop 1 fibs)
|
||||
|
||||
thousandDigitFib :: Int
|
||||
thousandDigitFib = length $ takeWhile (\x -> length (show x) < 1000) fibs
|
||||
|
||||
p025 :: IO ()
|
||||
|
@ -16,21 +16,21 @@
|
||||
|
||||
module P026 (p026) where
|
||||
|
||||
removeFactor :: (Integral a) => a -> a -> a
|
||||
removeFactor :: Integer -> Integer -> Integer
|
||||
removeFactor f n
|
||||
| n `mod` f /= 0 = n
|
||||
| otherwise = removeFactor f (n `div` f)
|
||||
|
||||
findCycleLengthRecursive :: (Integral a) => a -> a -> a -> a
|
||||
findCycleLengthRecursive :: Integer -> Integer -> Integer -> Integer
|
||||
findCycleLengthRecursive n j k
|
||||
| n == 1 = 0
|
||||
| k `mod` n == 0 = j
|
||||
| otherwise = findCycleLengthRecursive n (j + 1) (k * 10 + 9)
|
||||
|
||||
findCycleLength :: (Integral a) => a -> a
|
||||
findCycleLength :: Integer -> Integer
|
||||
findCycleLength n = findCycleLengthRecursive ((removeFactor 2 . removeFactor 5) n) 1 9
|
||||
|
||||
maxRepeatingCycle :: (Integral a) => a -> a -> a
|
||||
maxRepeatingCycle :: Integer -> Integer -> Integer
|
||||
maxRepeatingCycle a b = snd . maximum $ zip xs [1 ..]
|
||||
where
|
||||
xs = map findCycleLength [a .. b]
|
||||
|
@ -27,6 +27,7 @@ import ProjectEuler (isPrime)
|
||||
findLengthPrimeSequence :: Int -> Int -> Int
|
||||
findLengthPrimeSequence a b = length $ takeWhile isPrime [n * n + a * n + b | n <- [0 ..]]
|
||||
|
||||
findCoefficients :: (Int, Int)
|
||||
findCoefficients =
|
||||
let as = [-999 .. 999]
|
||||
bs = filter isPrime [2 .. 1000]
|
||||
|
@ -15,7 +15,7 @@ module P029 (p029) where
|
||||
|
||||
import Data.List (nub)
|
||||
|
||||
powerCombinations :: (Integral a) => a -> [a]
|
||||
powerCombinations :: Integer -> [Integer]
|
||||
powerCombinations n = nub [x ^ y | x <- [2 .. n], y <- [2 .. n]]
|
||||
|
||||
p029 :: IO ()
|
||||
|
@ -5,6 +5,7 @@
|
||||
-- How many circular primes are there below one million?
|
||||
|
||||
module P035 (p035) where
|
||||
|
||||
import Data.List (inits, tails)
|
||||
import ProjectEuler (isPrime, primeSieve)
|
||||
|
||||
@ -12,7 +13,7 @@ isCircularPrime :: Int -> Bool
|
||||
isCircularPrime n
|
||||
| n == 2 = True
|
||||
| any (`elem` ['0', '2' .. '8']) (show n) = False
|
||||
| all (isPrime . read) rotations = True
|
||||
| all (isPrime . (read :: String -> Int)) rotations = True
|
||||
| otherwise = False
|
||||
where
|
||||
rotations = zipWith (++) (tails (show n)) (init (inits (show n)))
|
||||
|
@ -5,10 +5,12 @@
|
||||
|
||||
module P041 (p041) where
|
||||
|
||||
import Data.List (uncons)
|
||||
import Data.Maybe (fromJust)
|
||||
import ProjectEuler (isPandigital, isPrime)
|
||||
|
||||
maxPandigitalPrime :: Integer
|
||||
maxPandigitalPrime = head $ filter isPrime (filter isPandigital [7654321, 7654319 ..])
|
||||
maxPandigitalPrime = fst . fromJust $ uncons $ filter isPrime (filter isPandigital [7654321, 7654319 ..])
|
||||
|
||||
p041 :: IO ()
|
||||
p041 = do
|
||||
|
@ -4,10 +4,11 @@
|
||||
|
||||
module P052 (p052) where
|
||||
|
||||
import Data.List (sort)
|
||||
import Data.List (sort, uncons)
|
||||
import Data.Maybe (fromJust)
|
||||
|
||||
smallestPermutedMultiples :: Integer
|
||||
smallestPermutedMultiples = head [x | x <- [1 ..], sort (show x) == sort (show (2 * x)), sort (show x) == sort (show (3 * x)), sort (show x) == sort (show (4 * x)), sort (show x) == sort (show (5 * x)), sort (show x) == sort (show (6 * x))]
|
||||
smallestPermutedMultiples = fst . fromJust $ uncons [x | x <- [1 ..], sort (show x) == sort (show (2 * x)), sort (show x) == sort (show (3 * x)), sort (show x) == sort (show (4 * x)), sort (show x) == sort (show (5 * x)), sort (show x) == sort (show (6 * x))]
|
||||
|
||||
p052 :: IO ()
|
||||
p052 = do
|
||||
|
@ -43,12 +43,14 @@
|
||||
-- and in each hand there is a clear winner.
|
||||
--
|
||||
-- How many hands does Player 1 win?
|
||||
{-# OPTIONS_GHC -Wno-incomplete-patterns -Wno-incomplete-uni-patterns #-}
|
||||
|
||||
module P054 (p054) where
|
||||
|
||||
import Data.Function (on)
|
||||
import Data.List (groupBy, maximumBy, minimumBy, sort, sortBy)
|
||||
import Data.List (groupBy, maximumBy, minimumBy, sort, sortBy, uncons)
|
||||
import Data.Maybe (fromJust)
|
||||
import Data.Ord
|
||||
|
||||
data Value = Two | Three | Four | Five | Six | Seven | Eight | Nine | Ten | Jack | Queen | King | Ace
|
||||
deriving (Eq, Ord, Show, Bounded, Enum)
|
||||
@ -104,13 +106,13 @@ readGame g = PokerGame {player1 = map readCard (take 5 (words g)), player2 = map
|
||||
royalFlush :: Hand -> Bool
|
||||
royalFlush h =
|
||||
let hs = sort h
|
||||
in length (head (groupBy ((==) `on` suit) hs)) == 5 && [Ten .. Ace] == map (fromJust . value) hs
|
||||
in length (fst . fromJust $ uncons (groupBy ((==) `on` suit) hs)) == 5 && [Ten .. Ace] == map (fromJust . value) hs
|
||||
|
||||
straightFlush :: Hand -> Bool
|
||||
straightFlush h =
|
||||
let hs@(x : _) = sort h
|
||||
start = fromJust . value $ x
|
||||
in length (head (groupBy ((==) `on` suit) hs)) == 5
|
||||
in length (fst . fromJust $ uncons (groupBy ((==) `on` suit) hs)) == 5
|
||||
&& take 5 [start ..] == map (fromJust . value) hs
|
||||
|
||||
fourOfAKind :: Hand -> Bool
|
||||
@ -141,7 +143,7 @@ twoPairs :: Hand -> Bool
|
||||
twoPairs h =
|
||||
let hs = sort h
|
||||
g_hs = sortBy (flip compare `on` length) (groupBy ((==) `on` value) hs)
|
||||
in length (head g_hs) == 2 && length (head (tail g_hs)) == 2
|
||||
in length (fst . fromJust $ uncons g_hs) == 2 && length (fst . fromJust $ uncons (drop 1 g_hs)) == 2
|
||||
|
||||
pair :: Hand -> Bool
|
||||
pair h =
|
||||
@ -149,7 +151,7 @@ pair h =
|
||||
|
||||
findPairVal :: Hand -> Card
|
||||
findPairVal h =
|
||||
head $ concat $ sortBy (flip compare `on` length) (groupBy ((==) `on` value) (sort h))
|
||||
fst . fromJust $ uncons $ concat $ sortBy (flip compare `on` length) (groupBy ((==) `on` value) (sort h))
|
||||
|
||||
playGame :: PokerGame -> Int
|
||||
playGame g
|
||||
@ -222,8 +224,8 @@ playGame g
|
||||
| pair (player1 g) && pair (player2 g) =
|
||||
let p1 = findPairVal (player1 g)
|
||||
p2 = findPairVal (player2 g)
|
||||
xs = reverse . sort $ player1 g
|
||||
ys = reverse . sort $ player2 g
|
||||
xs = sortBy (comparing Down) $ player1 g
|
||||
ys = sortBy (comparing Down) $ player2 g
|
||||
in if p1 > p2
|
||||
then 1
|
||||
else
|
||||
@ -234,13 +236,13 @@ playGame g
|
||||
then 1
|
||||
else -1
|
||||
| otherwise =
|
||||
let xs = reverse . sort $ player1 g
|
||||
ys = reverse . sort $ player2 g
|
||||
let xs = sortBy (comparing Down) $ player1 g
|
||||
ys = sortBy (comparing Down) $ player2 g
|
||||
in if xs > ys then 1 else -1
|
||||
|
||||
p054 :: IO ()
|
||||
p054 = do
|
||||
contents <- readFile "p054_poker.txt"
|
||||
contents <- readFile "input/p054_poker.txt"
|
||||
let games = map readGame (lines contents)
|
||||
result = sum $ filter (== 1) $ map playGame games
|
||||
putStrLn $
|
||||
|
@ -1,3 +1,5 @@
|
||||
{-# OPTIONS_GHC -Wno-type-defaults #-}
|
||||
|
||||
module ProjectEuler
|
||||
( isPrime,
|
||||
primeSieve,
|
||||
@ -10,10 +12,11 @@ module ProjectEuler
|
||||
where
|
||||
|
||||
import Data.Char (digitToInt)
|
||||
import Data.List (nub)
|
||||
import Data.List (nub, uncons)
|
||||
import Data.List.Ordered (minus, unionAll)
|
||||
import Data.Maybe (fromJust)
|
||||
|
||||
isPrime :: (Integral n) => n -> Bool
|
||||
isPrime :: (Integral a) => a -> Bool
|
||||
isPrime 1 = False
|
||||
isPrime 2 = True
|
||||
isPrime 3 = True
|
||||
@ -23,15 +26,15 @@ isPrime n =
|
||||
candidates = [5, 11 .. limit]
|
||||
limit = floor (sqrt (fromIntegral n)) + 1
|
||||
|
||||
primeSieve :: (Integral n) => [n]
|
||||
primeSieve = 2 : 3 : [5, 7 ..] `minus` unionAll [[p * p, p * p + 2 * p ..] | p <- tail primeSieve]
|
||||
primeSieve :: (Integral a) => [a]
|
||||
primeSieve = 2 : 3 : [5, 7 ..] `minus` unionAll [[p * p, p * p + 2 * p ..] | p <- drop 1 primeSieve]
|
||||
|
||||
lcmm :: (Integral n) => [n] -> n
|
||||
lcmm :: [Integer] -> Integer
|
||||
lcmm values
|
||||
| length values == 2 = lcm (head values) (last values)
|
||||
| otherwise = lcm (head values) (lcmm (tail values))
|
||||
| length values == 2 = lcm (fst . fromJust $ uncons values) (last values)
|
||||
| otherwise = lcm (fst . fromJust $ uncons values) (lcmm (drop 1 values))
|
||||
|
||||
digitSum :: (Integral a, Show a) => a -> Int
|
||||
digitSum :: (Show a) => a -> Int
|
||||
digitSum n = sum $ map digitToInt $ show n
|
||||
|
||||
sumProperDivisors :: (Integral a) => a -> a
|
||||
|
Loading…
x
Reference in New Issue
Block a user