Files
2025-12-09 16:32:32 +01:00

88 lines
2.9 KiB
Haskell

module Phone where
import Data.Char (ord)
import Data.List (sortBy)
data DaPhone = DaPhone
convo :: [String]
convo =
[ "Wanna play 20 questions"
, "Ya"
, "U 1st haha"
, "Lol ok. Have u ever tasted alcohol"
, "Lol ya"
, "Wow ur cool haha. Ur turn"
, "Ok. Do u think I am pretty Lol"
, "Lol ya"
, "Just making sure rofl ur turn" ]
-- validButtons = "1234567890*#"
type Digit = Char
-- Valid presses: 1 and up
type Presses = Int
data Button = Button Digit String
-- assuming the default phone definition
-- 'a' -> [('2', 1)]
-- 'A' -> [('*', 1), ('2', 1)]
reverseTaps :: DaPhone -> Char -> [(Digit, Presses)]
reverseTaps _ c
| c == '.' = [('#', 1)]
| c == ',' = [('#', 2)]
| c == '#' = [('#', 3)]
| c == '+' = [('0', 1)]
| c == ' ' = [('0', 2)]
| c == '0' = [('0', 3)]
| (ord c) >= (ord 'w') = [('9', (ord c) - (ord 'w') + 1)]
| (ord c) >= (ord 't') = [('8', (ord c) - (ord 't') + 1)]
| (ord c) >= (ord 'p') = [('7', (ord c) - (ord 'p') + 1)]
| (ord c) >= (ord 'm') = [('6', (ord c) - (ord 'm') + 1)]
| (ord c) >= (ord 'j') = [('5', (ord c) - (ord 'j') + 1)]
| (ord c) >= (ord 'g') = [('4', (ord c) - (ord 'g') + 1)]
| (ord c) >= (ord 'd') = [('3', (ord c) - (ord 'd') + 1)]
| (ord c) >= (ord 'a') = [('2', (ord c) - (ord 'a') + 1)]
| (ord c) >= (ord 'W') = [('*', 1), ('9', (ord c) - (ord 'W') + 1)]
| (ord c) >= (ord 'T') = [('*', 1), ('8', (ord c) - (ord 'T') + 1)]
| (ord c) >= (ord 'P') = [('*', 1), ('7', (ord c) - (ord 'P') + 1)]
| (ord c) >= (ord 'M') = [('*', 1), ('6', (ord c) - (ord 'M') + 1)]
| (ord c) >= (ord 'J') = [('*', 1), ('5', (ord c) - (ord 'J') + 1)]
| (ord c) >= (ord 'G') = [('*', 1), ('4', (ord c) - (ord 'G') + 1)]
| (ord c) >= (ord 'D') = [('*', 1), ('3', (ord c) - (ord 'D') + 1)]
| (ord c) >= (ord 'A') = [('*', 1), ('2', (ord c) - (ord 'A') + 1)]
| c == '9' = [('9', 5)]
| c == '8' = [('8', 4)]
| c == '7' = [('7', 5)]
| c == '6' = [('6', 4)]
| c == '5' = [('5', 4)]
| c == '4' = [('4', 4)]
| c == '3' = [('3', 4)]
| c == '2' = [('2', 4)]
| c == '1' = [('2', 1)]
cellPhonesDead :: DaPhone -> String -> [(Digit, Presses)]
cellPhonesDead dp s = concat (map (reverseTaps dp) s)
fingerTaps :: [(Digit, Presses)] -> Presses
fingerTaps = foldr f 0
where f (_, p) acc = p + acc
mostPopularLetter :: String -> Char
mostPopularLetter c = fst $ head (sortBy (\(_, x1) (_, x2) -> compare x2 x1) $ foldr foldF [] c)
where foldF c [] = [(c, 1)]
foldF c ((x, n):xs)
| c == x = (x, n + 1) : xs
| otherwise = (x, n) : (foldF c xs)
coolestLtr :: [String] -> Char
coolestLtr = mostPopularLetter . concat
coolestWord :: [String] -> String
coolestWord c = fst $ head (sortBy (\(_, x1) (_, x2) -> compare x2 x1) $ foldr foldF [] (words (concat c)))
where foldF c [] = [(c, 1)]
foldF c ((x, n):xs)
| c == x = (x, n + 1) : xs
| otherwise = (x, n) : (foldF c xs)