Skip to content

Instantly share code, notes, and snippets.

@ygrenzinger
Created December 27, 2016 20:56
Show Gist options
  • Save ygrenzinger/5ec8eaea158668966b513a83fe7bd06d to your computer and use it in GitHub Desktop.
Save ygrenzinger/5ec8eaea158668966b513a83fe7bd06d to your computer and use it in GitHub Desktop.
Phone.hs
module Phone where
import Data.Char (isUpper, toLower)
import Control.Arrow
import Data.List (maximumBy)
type Digit = Char
type Presses = Int
type Key = (Digit, String)
type Keys = [(Digit, String)]
data DaPhone = DaPhone Keys
keyboard :: DaPhone
keyboard = DaPhone [('2', "abc"),
('3', "def"),
('4', "ghi"),
('5', "jkl"),
('6', "mno"),
('7', "pqrs"),
('8', "tuv"),
('9', "wxyz"),
('0', " "),
('#', ".,")]
numberOfKeyPresses :: Char -> String -> Presses
numberOfKeyPresses c xs = length (takeWhile (c /=) xs) + 1
keyContain :: Char -> Key -> Bool
keyContain c (_, xs) = c `elem` xs
reverseTaps :: DaPhone -> Char -> [(Digit, Presses)]
reverseTaps p@(DaPhone ks) c = if isUpper c
then ('*', 1) : reverseTaps p (toLower c)
else map (Control.Arrow.second (numberOfKeyPresses c)) $ filter (keyContain c) ks
cellPhonesDead :: DaPhone -> String-> [(Digit, Presses)]
cellPhonesDead keys = concatMap (reverseTaps keys)
fingerTaps :: [(Digit, Presses)] -> Presses
fingerTaps = foldr (\(_, p) acc -> p + acc) 0
mostPopularLetter :: String -> Char
mostPopularLetter = fst . maximumBy (\(_, a) (_, b) -> compare a b) . cellPhonesDead keyboard
coolestLtr :: [String] -> Char
coolestLtr = undefined
coolestWord :: [String] -> String
coolestWord = undefined
convo :: [String]
convo =
["Wanna play 20 questions",
"Ya",
"U 1st haha",
"Lol ok. Have u ever tasted alcohol lol",
"Lol ya",
"Wow ur cool haha. Ur turn",
"Ok. Do u think I am pretty Lol",
"Lol ya",
"Haha thanks just making sure rofl ur turn"]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment