Skip to content

Instantly share code, notes, and snippets.

@taras2k
Last active December 5, 2017 19:53
Show Gist options
  • Save taras2k/90a774243aa57daceb53f977cd64b12c to your computer and use it in GitHub Desktop.
Save taras2k/90a774243aa57daceb53f977cd64b12c to your computer and use it in GitHub Desktop.
phone from haskell book
module Phone where
import Data.Char (isLetter, isUpper, toLower, toUpper)
import Data.List (elemIndex, elemIndices, find, nub, sortBy)
import Data.Maybe (fromMaybe)
import Data.Tuple (swap)
phone :: [(Char, String)]
phone =
[ ('0', " +_0")
, ('1', "1")
, ('2', "ABC2")
, ('3', "DEF3")
, ('4', "GHI4")
, ('5', "JKL5")
, ('6', "MNO6")
, ('7', "PQRS7")
, ('8', "TUV8")
, ('9', "WXYZ9")
, ('*', "^*")
, ('#', ".,#")
]
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
reverseTaps :: Char -> [(Digit, Presses)]
reverseTaps d =
if isUpper d
then ('*', 1) : low
else low
where
upperD = toUpper d
found = find (elem upperD . snd) phone
cell =
fromMaybe
(error ("symbol " ++ [d] ++ " was not found in the phone"))
found
(Just chrIndex) = elemIndex (toUpper d) (snd cell)
low = [(fst cell, succ chrIndex)]
-- assuming the default phone definition
-- 'a' -> [('2', 1)]
-- 'A' -> [('*', 1), ('2', 1)]
fingerTaps :: [(Digit, Presses)] -> Presses
fingerTaps dp = sum (map snd dp)
cellPhonesDead :: String -> [(Digit, Presses)]
cellPhonesDead = concatMap reverseTaps
symbolCost :: Char -> Presses
symbolCost = fingerTaps . reverseTaps
symbolCostInSentence :: String -> Char -> (Char, Presses)
symbolCostInSentence sent c = (loC, totalCost)
where
loC = toLower c
upC = toUpper c
cost l = symbolCost l * length (elemIndices l sent)
totalCost = cost upC + cost loC
mostPopularLetter :: String -> (Char, Presses)
mostPopularLetter msg =
swap $ maximum $ nub $ map (swap . symbolCostInSentence msg) msg
coolestLtr :: [String] -> (Char, Presses)
coolestLtr messages = mostPopularLetter (concat messages)
wordCost' :: String -> Presses
wordCost' s = sum (map (snd . symbolCostInSentence s) s)
wordCost :: String -> Presses
wordCost = sum . map symbolCost
toLowerStr :: String -> String
toLowerStr = map toLower
toLowerStrOnlyLetters :: String -> String
toLowerStrOnlyLetters = toLowerStr . filter isLetter
filterNonLetters :: [String] -> [String]
filterNonLetters = map (filter isLetter)
-- coolWords transforms list of messages into the list of words and calculates cost for every word,
-- stores them as tuple into [(word,Presses)] list. Then transform the list [(word0, 10),(word1,11) , (word0, 10) ..]
-- with repetive items to the list with calculated all Presses for the same word .
-- Last step is sorting by Presses number.
-- Function also takes into account case when word have different censitivity in a sentence.
coolWords :: [String] -> [(String, Presses)]
coolWords messages =
sortBy (flip (compare . snd) . snd) (nub $ map (mrg arr . fst) arr)
where
mrg y x = (x, foldr ((+) . snd) 0 (filter ((== x) . fst) y))
wordList = filterNonLetters (concatMap words messages)
arr = zipWith (\x y -> (toLowerStr x, y)) wordList (map wordCost wordList)
coolestWord :: [String] -> String
coolestWord [] = ""
coolestWord messages = fst (head (coolWords messages))
sortBtnUsagesInText :: [String] -> [(Digit, Presses)]
sortBtnUsagesInText messages =
sortBy (\a b -> compare (snd b) (snd a)) (nub $ map (mrg lst . fst) lst)
where
mrg y x = (x, foldr ((+) . snd) 0 (filter ((== x) . fst) y))
lst = cellPhonesDead (concat messages)
main :: IO ()
main = do
putStrLn ("Coolest word " ++ show (coolestWord convo))
putStrLn ("Button popularity " ++ show (sortBtnUsagesInText convo))
@taras2k
Copy link
Author

taras2k commented Dec 2, 2017

implemented remaining undefined functions , cleaned up stuff, fixed issues

@k-bx
Copy link

k-bx commented Dec 2, 2017

Looks great overall!

I think mostPopularLetter is a big heavy in complexity, for each letter we count its cost in sentence, even if the value is not needed. On the other hand, we didn't yet familiarize ourselves with key-value maps in haskell, which make these kind of algorithms way easier.

@taras2k
Copy link
Author

taras2k commented Dec 2, 2017

Yep , I agree it looks awkward ( mostPopularLetter ) - but it works - this is my excuse 😕

@taras2k
Copy link
Author

taras2k commented Dec 3, 2017

another point I have missed - word case sensitivity in the text. Word weight should be combined despite of sensitivity. Fixed it.

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