view 7-Haskell/day2.hs @ 103:98be775c533c default tip

An odd "non-determinism" example from StackOverflow It is clever, but doesn't make much sense as to how it gets its results
author IBBoard <dev@ibboard.co.uk>
date Sun, 14 Jul 2019 13:44:13 +0100
parents 39084e2b8744
children
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 after 2 have to be odd (or else they're a multiple of 2!), so increment up the odd numbers
    primes = 2 : [x | x <- [3, 5 ..], (mod ((product [1 .. x-1]) + 1) x) == 0]

    break_lines :: String -> Int -> [String]
    break_lines str len = break_lines' str "" "" len []

    break_lines' :: String -> String -> String -> Int -> [String] -> [String]
    break_lines' "" "" "" _ strings = strings
    break_lines' "" next_word line len strings = break_lines' "" "" "" len (strings ++ [line ++ next_word])
    break_lines' (char:rest) next_word line len strings
        | char == ' ' && candidate_length == len = break_lines' rest "" "" len (strings ++ [line ++ next_word]) -- if we've got a space at the right place, add the word but not the space
        | char == ' ' = break_lines' rest "" (line ++ next_word ++ " ") len strings -- else we've got a break so add the word and the space to the line
        -- Then, for non-space characters…
        | candidate_length < len = break_lines' rest (next_word ++ [char]) line len strings -- if we're not at the line length then add the character
        | candidate_length == len && line /= "" = break_lines' rest (next_word ++ [char]) "" len (strings ++ [line]) -- if we've got a partial line and our next word is getting too long then add the line as-is
        | length next_word == len = break_lines' rest ("-" ++ [char]) "" len (strings ++ [next_word]) -- if our candidate is more than our length and we've got a blank line then add our N characters of this word, and hyphenate the word
        | otherwise = break_lines' rest (next_word ++ [char]) line len strings -- otherwise we're within limits and can keep going
        where candidate_length = (length next_word + length line)

-- > break_lines "hello 1234567890123456789012345678901234567890123456789012345678901234567890123456789012345 lorem ipsum bibbety bobbety boo once upon a time there was a cat and it sat on a mat while the quick brown fox jumped over the lazy dog" 80
--   ["hello ","12345678901234567890123456789012345678901234567890123456789012345678901234567890","-12345 lorem ipsum bibbety bobbety boo once upon a time there was a cat and it ","sat on a mat while the quick brown fox jumped over the lazy dog"]--