Skip to content

Instantly share code, notes, and snippets.

@specdrake
Last active May 24, 2020 17:03
Show Gist options
  • Save specdrake/db5fec1ecedf5e47feef694743ca030b to your computer and use it in GitHub Desktop.
Save specdrake/db5fec1ecedf5e47feef694743ca030b to your computer and use it in GitHub Desktop.
module Phone where
import Data.List
import Data.Char
data DaPhone = Lower (Digit, String) deriving (Eq, Show)
but1 :: DaPhone
but1 = Lower ('1', "1")
but2 :: DaPhone
but2 = Lower ('2', "abc2")
but3 :: DaPhone
but3 = Lower ('3', "def3")
but4 :: DaPhone
but4 = Lower ('4', "ghi4")
but5 :: DaPhone
but5 = Lower ('5', "jkl5")
but6 :: DaPhone
but6 = Lower ('6', "mno6")
but7 :: DaPhone
but7 = Lower ('7', "pqrs7")
but8 :: DaPhone
but8 = Lower ('8', "tuv8")
but9 :: DaPhone
but9 = Lower ('9', "wxyz9")
butstar :: DaPhone
butstar = Lower('*', "^*")
but0 :: DaPhone
but0 = Lower ('0', " +_0")
buthash :: DaPhone
buthash = Lower ('#', ".,#")
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"]
-- validButtons = "1234567890*#"
type Digit = Char
-- Valid presses: 1 and up
type Presses = Int
reverseTaps :: DaPhone -> Char -> [(Digit, Presses)]
reverseTaps (Lower tup) ch = if isUpper ch then [('*', 1), (fst tup, p)] else [(fst tup, p)]
where p = (elemIn (snd tup) (toLower ch)) + 1
func :: Char -> DaPhone
func ch
| elem ch ['1'] = but1
| elem ch ('2':['a'..'c'] ++ ['A'..'C']) = but2
| elem ch ('3':['d'..'f'] ++ ['D' .. 'F']) = but3
| elem ch ('4':['g'..'i'] ++ ['G' .. 'I']) = but4
| elem ch ('5':['j'..'l'] ++ ['J' .. 'L']) = but5
| elem ch ('6':['m'..'o'] ++ ['M' .. 'O'])= but6
| elem ch ('7':['p'..'s'] ++ ['P' .. 'S']) = but7
| elem ch ('8':['t'..'v'] ++ ['T' .. 'V']) = but8
| elem ch ('9':['w'..'z'] ++ ['W' .. 'Z']) = but9
| elem ch (['*', '^']) = butstar
| elem ch ('0':['+', '_', ' ']) = but0
| elem ch ('#':['.', ',']) = buthash
| otherwise = undefined
elemIn :: Eq a => [a] -> a -> Int
elemIn ls x = go 0 ls x
where go :: Eq a => Int -> [a] -> a -> Int
go i (l:ls) x = if x == l then i else (go (i+1) ls x)
go i [] _ = -1
-- assuming the default phone definition
-- 'a' -> ('2', 1)
-- 'A' -> [('*', 1), ('2', 1)]
cellPhonesDead :: String -> [(Digit, Presses)]
cellPhonesDead (x:xs) = reverseTaps (func x) x ++ cellPhonesDead xs
cellPhonesDead "" = []
fingerTaps :: [(Digit, Presses)] -> Presses
fingerTaps ldp = foldl (\z (a,b) -> b + z ) 0 ldp
mostPopularLetter :: String -> Char
mostPopularLetter str = head . last . sortBy (\a b -> compare (length a) (length b)) . group . sort . map toLower $ str
coolestLtr :: [String] -> Char
coolestLtr lstr = mostPopularLetter . filter (isAlphaNum) . concat $ lstr
coolestWord :: [String] -> String
coolestWord lstr = head . last . sortBy (\a b -> compare (length a) (length b)) . group . sort . concat . map words $ lstr
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment