1
0
Fork 0

Add main functions to any that were missing

main
Bill Ewanick 2023-09-18 19:40:01 -04:00
parent 6e17fe91f5
commit 683ad67214
6 changed files with 78 additions and 20 deletions

View File

@ -221,4 +221,6 @@ ans :: [Integer]
ans = take 10 $ reverse . digits $ sum oneHundredFiftyDigitNumbers
main :: IO ()
main = print ans
main = do
print ans
print (sum oneHundredFiftyDigitNumbers)

View File

@ -63,3 +63,5 @@ test = map (filter . multipleOf) [1..10]
-- lol
solve = foldl1 lcm [1..20]
main = print solve

View File

@ -13,16 +13,29 @@ Find the difference between the sum of the squares
of the first one hundred natural numbers
and the square of the sum.
-}
upperRange = 100
upperRange :: Integer
upperRange = 1_000_000
square :: Num a => a -> a
square n = n^2
squares :: [Integer]
squares = map square [1..upperRange]
sum' :: [Integer] -> Integer
sum' = go 0
where
go acc [] = acc
go acc (x:xs) = go (acc+x) xs
sumOfSquares = sum' squares
sumOfSquares :: Integer
sumOfSquares = sum squares
squareOfTheSum = (sum [1..upperRange])^2
squareOfTheSum :: Integer
squareOfTheSum = sum [1..upperRange] ^2
solution :: Integer
solution = squareOfTheSum - sumOfSquares
main :: IO ()
main = print solution

View File

@ -1,6 +1,9 @@
-- https://projecteuler.net/problem=7
-- Find the 10_001 prime number
-- import Data.Numbers.Primes (primes)
import Math.NumberTheory.Primes (primes)
primes1 :: [Integer]
primes1 = 2:3:prs
where
@ -30,3 +33,8 @@ primes2 = 2:([3..] `minus` composites)
primes3 = sieve [2..]
where
sieve (p : xs) = p : sieve [x | x <- xs, x `mod` p > 0]
main :: IO ()
main = print $ "Arithmoi - Math.NumberTheory.Primes: " <> show ans
ans = primes !! 10_000_000

View File

@ -28,6 +28,7 @@ What is the value of this product?
module Main where
import Data.Char (ord)
import Data.Foldable (maximumBy)
import Data.List (sort)
import Data.List.Split (splitOn)
@ -46,9 +47,16 @@ digits = go []
main :: IO ()
main = print ans
ans :: [[Integer]]
ans = (windowsOf 13 . digits) thousandDigitNum
-- "9878799272442"
ans :: ([Integer], Integer)
ans = (l, p)
where
l = maximumBy c $ (windowsOf 13 . digits) thousandDigitNum
p = product l
c a b
| product a > product b = GT
| product a < product b = LT
| otherwise = EQ
-- "([5,5,7,6,6,8,9,6,6,4,8,9,5],23514624000)"
-- what dose it mean to have the greatest product in adjacent digits?
-- why ask it like that???

View File

@ -17,14 +17,39 @@ Find the product `abc`.
-}
main :: IO ()
main = print answer
main = do
print answer
print (product answer)
answer :: String
answer = "I dunno"
-- head $ [(a,b,c) | a <- [1..limit], b <- [a+1..limit], c <- [limit - a - b], a < b, b < c, a^2 + b^2 == c^2]
answer :: [Integer]
answer = head $
[ [a, b, c] |
a <- [1 .. limit],
b <- [a + 1 .. limit],
c <- [limit - a - b],
b < c,
a ^ 2 + b ^ 2 == c ^ 2]
where limit = 1000
limit = 1000
version1 = [ [a, b, c] |
a <- [1 .. limit],
b <- [a + 1 .. limit],
c <- [limit - a - b],
b < c,
a ^ 2 + b ^ 2 == c ^ 2]
version2 = [ [a, b, c] |
a <- [1 .. limit],
b <- [a + 1 .. limit],
c <- [limit - a - b],
b < c,
a ^ 2 + b ^ 2 == c ^ 2]
solve :: Integer -> [(Integer, Integer, Integer)]
solve x = takeWhile (\(a,b,c) -> a + b + c <= 1000) $ primitiveTriplesUnder x
solve x = takeWhile (\(a,b,c) -> a + b + c == 1000) $ primitiveTriplesUnder x
euclid'sFormula :: Num c => (c, c) -> (c, c, c)
euclid'sFormula (m, n) = (a,b,c)
@ -96,10 +121,10 @@ ans' limit = [(a, b, c)
-}
-- Computers are fast, so we can implement a brute-force search to directly solve the problem.
perim = 1000
main = putStrLn (show ans)
ans = head [a * b * (perim - a - b) | a <- [1..perim], b <- [a+1..perim], isIntegerRightTriangle a b]
isIntegerRightTriangle a b = a < b && b < c
&& a * a + b * b == c * c
where c = perim - a - b
-- -- Computers are fast, so we can implement a brute-force search to directly solve the problem.
-- perim = 1000
-- main = putStrLn (show ans)
-- ans = head [a * b * (perim - a - b) | a <- [1..perim], b <- [a+1..perim], isIntegerRightTriangle a b]
-- isIntegerRightTriangle a b = a < b && b < c
-- && a * a + b * b == c * c
-- where c = perim - a - b