Skip to content

Instantly share code, notes, and snippets.

@sergey-sign
Last active December 5, 2017 09:40
Show Gist options
  • Save sergey-sign/0fc077494b1e86996d841c1eecbcd8d4 to your computer and use it in GitHub Desktop.
Save sergey-sign/0fc077494b1e86996d841c1eecbcd8d4 to your computer and use it in GitHub Desktop.
module Phone where
import Data.Char(isUpper, toLower)
import Data.List(maximumBy, sort, sortBy, groupBy)
import Data.Function(on)
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"
]
data KeyRule = KeyRule Digit [Digit] deriving Show
keyRules =
[ KeyRule '1' []
, KeyRule '2' "abc"
, KeyRule '3' "def"
, KeyRule '4' "ghi"
, KeyRule '5' "jkl"
, KeyRule '6' "mno"
, KeyRule '7' "pqrs"
, KeyRule '8' "tuv"
, KeyRule '9' "wxyz"
, KeyRule '*' "^"
, KeyRule '0' "+ "
, KeyRule '#' ".,"
]
makeRawDaPhone :: [KeyRule] -> [(Char, (Digit, Presses))]
makeRawDaPhone info = concatMap parceRule fullRules where
fullRules = map keyRule2pair info where
keyRule2pair (KeyRule d cs) = (d, cs ++ [d])
parceRule (phoneKey, chars) = map wrapPair pairs where
pairs = getCharAndPosition [] 1 chars
wrapPair (letter, presses) = (letter, (phoneKey, presses))
getCharAndPosition :: [(Digit, Presses)] -> Presses -> [Digit] -> [(Digit, Presses)]
getCharAndPosition acc position (c: []) = (c, position) : acc
getCharAndPosition acc position (c: cs) = getCharAndPosition ((c, position) : acc) (position + 1) cs
data DaPhone = DaPhone [(Char, (Digit, Presses))] deriving Show
daPhone :: DaPhone
daPhone = DaPhone $ makeRawDaPhone keyRules
-- validButtons = "1234567890*#"
type Digit = Char
-- Valid presses: 1 and up
type Presses = Int
-- assuming the default phone definition
-- 'a' -> [('2', 1)]
-- 'A' -> [('*', 1), ('2', 1)]
reverseTaps :: DaPhone -> Char -> [(Digit, Presses)]
reverseTaps (DaPhone _) '^' = []
reverseTaps (DaPhone dict) c = maybeAsResult $ lookup (toLower c) dict where
maybeAsResult Nothing = []
maybeAsResult (Just r) = tryFixUpperCase [r]
tryFixUpperCase = if isUpper c then (upperFlag :) else id
upperFlag = ('*', 1)
cellPhonesDead :: DaPhone -> String -> [(Digit, Presses)]
cellPhonesDead = concatMap . reverseTaps
fingerTaps :: [(Digit, Presses)] -> Presses
fingerTaps = sum . map snd
mostPopular :: String -> (Char, Presses)
mostPopular = mostPopularTap . cellPhonesDead daPhone
mostPopularTap :: Ord a => [(a, b)] -> (a, b)
mostPopularTap = maximumBy (compare `on` fst)
mostPopularLetter :: String -> Char -- Maybe Char?
mostPopularLetter = fst . mostPopular
mostPopularKey :: [String] -> Char
mostPopularKey ss = fst $ mostPopularTap taps where
taps = map mostPopular ss
coolestLtr :: [String] -> Char
coolestLtr ss = mostUsed letters where
letters = concat $ concatMap words ss
coolestWord :: [String] -> String
coolestWord ss = mostUsed lowerCaseText where
text = concatMap words ss
lowerCaseText = map (map toLower) text
mostUsed :: Ord a => [a] -> a
mostUsed ss = head $ head $ sortBy (flip compare `on` length ) $ groupBy (==) $ sort ss
@vvv
Copy link

vvv commented Dec 2, 2017

  • tryFixUpperCase is neat.

  • I forgot about maximumBy. And I never heard of on — it's cool!

  • I find mostUser name confusing. Did you mean “most used”?

  • Also mostPopularTap could be named better. It is generic, yet it's name is even more specific than that of mostPopular. :)

mostPopularTap :: Ord a => [(a, b)] -> (a, b)

mostPopular :: String -> (Char, Presses)
  • [nit] fingerTaps doesn't need parentheses. mostPopular and mostPopularTap would look better with pointfree.

@taras2k
Copy link

taras2k commented Dec 2, 2017

mostPopularLetter "Wannaplay20questionsYaU1sthahaLolok.HaveuevertastedalcoholLolyaWowurcoolhaha.UrturnOk.DouthinkIamprettyLolLolyaJustmakingsureroflurturn" gives '9' - I think it should be 'o'

@taras2k
Copy link

taras2k commented Dec 2, 2017

coolestWord is correct 👍

@erasmas
Copy link

erasmas commented Dec 5, 2017

@taras2k In your example popular character is a

mostPopular :: Ord a => [a] -> [(Int, a)]
mostPopular' xs = [(length x, head x) | x <- groups]
  where
    groups = (group . sort) xs
λ> (maximum . mostPopular') "Wannaplay20questionsYaU1sthahaLolok.HaveuevertastedalcoholLolyaWowurcoolhaha.UrturnOk.DouthinkIamprettyLolLolyaJustmakingsureroflurturn"
(15,'a')

@erasmas
Copy link

erasmas commented Dec 5, 2017

👍

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment