view 7-Haskell/day2.hs @ 91:075ff4e4feaf

Fix the prime checking Greatest common denominator MAY work, but it's probably inefficient (I also wondered whether it wouldn't always work, but then the number can't be a prime!)
author IBBoard <dev@ibboard.co.uk>
date Mon, 17 Jun 2019 20:26:30 +0100
parents c27c87cd0f08
children 6f650dd96685
line wrap: on
line source

module Day2 where
    -- We could just "import Data.List" and then use "sort", but let's do it by hand with an ugly O(n^2) approach
    my_sort :: Ord a => [a] -> [a]
    my_sort lst = my_sort' (<) lst []

--    my_sort' :: Ord a => [a] -> [a] -> [a]
--    my_sort' [] res = res
--    my_sort' (h:t) [] = my_sort' t [h]
--    my_sort' (h:t) (h_res:t_res)
--        | h < h_res = my_sort' t (h:h_res:t_res)
--        | otherwise = my_sort' t (h_res:my_sort' (h:[]) t_res)

    my_sort' :: Ord a => (a -> a -> Bool) -> [a] -> [a] -> [a]
    my_sort' cmp [] res = res
    my_sort' cmp (h:t) [] = my_sort' cmp t [h]
    my_sort' cmp (h:t) (h_res:t_res)
        | cmp h h_res = my_sort' cmp t (h:h_res:t_res)
        | otherwise = my_sort' cmp t (h_res:my_sort' cmp (h:[]) t_res)
    
    parse_int :: String -> Int
    parse_int str = parse_int' str 0

    parse_int' :: String -> Int -> Int
    parse_int' "" val = val
    parse_int' (h:t) val
        | fromEnum h >= 48 && fromEnum h <= 57 = parse_int' t (val * 10 + ((fromEnum h) - 48))
        | otherwise = parse_int' t val
    
    every_three :: Integer -> [Integer]
    every_three = every_n 3

    every_five :: Integer -> [Integer]
    every_five = every_n 5

    every_n :: Integer -> Integer -> [Integer]
    every_n n x = [x, x + n ..]

    -- Usage: every_m_n (every_five) 5 (every_three) 3
    every_m_n :: (Integer -> [Integer]) -> Integer -> (Integer -> [Integer]) -> Integer -> [Integer]
    every_m_n _m x _n y = zipWith (+) (_m x) (_n y)

    halve :: Double -> Double
    halve x = (/ 2) x -- It's ugly, but it's the "partially applied" version of "x / 2" - "(/ 2)" becomes an anonymous function that gets applied to x

    new_line :: String -> String
    new_line x = (++ "\n") x

    -- Let's go Euclidean: https://en.wikipedia.org/wiki/Greatest_common_divisor#Euclid's_algorithm
    my_gcd :: Integer -> Integer -> Integer
    my_gcd a b
        | a == b = a
        | a > b = my_gcd (a - b) b
        | otherwise = my_gcd a (b - a)
    
    -- Wilson's theorem seems easiest: https://en.wikipedia.org/wiki/Wilson%27s_theorem
    primes :: [Integer]
    primes = [x | x <- [2 ..], (mod ((product [1 .. x-1]) + 1) x) == 0]