Created
October 19, 2020 20:43
-
-
Save vrom911/c813e95fbc0f22a445415b52d603fd55 to your computer and use it in GitHub Desktop.
My solutions to the Chris Penner's 'Silly Job Interview Questions In Haskell' post: https://chrispenner.ca/posts/interview
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module ChrisPenner where | |
import Data.Array ((!)) | |
import Data.Foldable (for_, foldl', maximumBy) | |
import Data.List (sort) | |
import Data.Map.Strict (Map) | |
import Data.Ord (comparing) | |
import qualified Data.Array as A | |
import qualified Data.Map.Strict as Map | |
-- Works in O(n) | |
palindrome :: String -> Bool | |
palindrome str = str == reverse str | |
type Array = A.Array Int | |
-- Works in O(n) with smaller constant and O(1) in the best case | |
palindromeArray :: Array Char -> Bool | |
palindromeArray arr = | |
let (start, end) = A.bounds arr | |
in go start end | |
where | |
go :: Int -> Int -> Bool | |
go i j | |
| i >= j = True | |
| otherwise = arr ! i == arr ! j && go (i + 1) (j - 1) | |
fizzBuzz :: Int -> String | |
fizzBuzz x | |
| x `mod` 15 == 0 = "Fizz Buzz" | |
| x `mod` 3 == 0 = "Fizz" | |
| x `mod` 5 == 0 = "Buzz" | |
| otherwise = show x | |
printFizzBuzz :: IO () | |
printFizzBuzz = for_ [1..100] (putStrLn . fizzBuzz) | |
type ElemIndexed = (Int, Int) | |
{- Works for O(n^2 log n) | |
(Could be O (n ^ 2) if using normal HashMap) | |
-} | |
sum3ToN :: Int -> [Int] -> [(Int, Int, Int)] | |
sum3ToN n l = map triplesIndxToElems $ getTriples lIndexed | |
where | |
lIndexed :: [ElemIndexed] | |
lIndexed = zip l [0 .. ] | |
pairs :: [(ElemIndexed, ElemIndexed)] | |
pairs = [(xi, yj) | xi@(_x, i) <- lIndexed, yj@(_y, j) <- lIndexed, i < j ] | |
mapOfSums :: Map Int [(Int, Int)] | |
mapOfSums = Map.fromListWith (++) $ map toSumPair pairs | |
toSumPair :: (ElemIndexed, ElemIndexed) -> (Int, [(Int, Int)]) | |
toSumPair ((x, i), (y, j)) = (x + y, [(i, j)]) | |
getTriples :: [ElemIndexed] -> [(Int, Int, Int)] | |
getTriples [] = [] | |
getTriples ((x, i):xs) = curTriples ++ getTriples xs | |
where | |
curTriples = case Map.lookup (n - x) mapOfSums of | |
Just inds -> map (\(j, k) -> (j, k, i)) $ | |
filter (uniqueIndexes i) inds | |
Nothing -> [] | |
uniqueIndexes :: Int -> (Int, Int) -> Bool | |
uniqueIndexes i (j, k) = i > j && i > k | |
lArray :: Array Int | |
lArray = A.listArray (0, length l - 1) l | |
triplesIndxToElems :: (Int, Int, Int) -> (Int, Int, Int) | |
triplesIndxToElems (i, j, k) = (lArray ! i, lArray ! j, lArray ! k) | |
-- Works in O(n log n + m log m + min n m) ~ O (max m n * log (max m n)) | |
isAnagram :: String -> String -> Bool | |
isAnagram str1 str2 = sort str1 == sort str2 | |
-- Works in O(n + m) (with proper HashMap) | |
isAnagramMap :: String -> String -> Bool | |
isAnagramMap str1 str2 = checkStr2 str2 map1 | |
where | |
map1 :: Map Char Int | |
map1 = foldl' (\m c -> Map.insertWith (+) c 1 m) mempty str1 | |
checkStr2 :: String -> Map Char Int -> Bool | |
checkStr2 [] m = Map.null m | |
checkStr2 (c:str) m = case Map.lookup c m of | |
Just _ -> checkStr2 str $ Map.alter change c m | |
Nothing -> False | |
where | |
change :: Maybe Int -> Maybe Int | |
change (Just i) = let newI = i - 1 in | |
if newI <= 0 | |
then Nothing | |
else Just newI | |
change Nothing = Nothing | |
-- Works in O(n) | |
minMax :: [Int] -> Maybe (Int, Int) | |
minMax [] = Nothing | |
minMax (x:xs) = Just $ go (x, x) xs | |
where | |
go :: (Int, Int) -> [Int] -> (Int, Int) | |
go res [] = res | |
go (mn, mx) (y:ys) = go (min mn y, max mx y) ys | |
-- Works in O(n) where n is the amount of words (< len of txt) | |
mostFrequent :: String -> Maybe String | |
mostFrequent txt = case Map.assocs wordsMap of | |
[] -> Nothing | |
xs -> Just $ fst $ maximumBy (comparing snd) xs | |
where | |
wordsMap :: Map String Int | |
wordsMap = foldl' (\m str -> Map.insertWith (+) str 1 m) mempty (words txt) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment