Skip to content

Commit 9f14d07

Browse files
committed
Solve 'The Speed of Letters' kata
1 parent 51bba0a commit 9f14d07

File tree

2 files changed

+60
-0
lines changed

2 files changed

+60
-0
lines changed

src/SpeedOfLetters.hs

Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,40 @@
1+
{-# LANGUAGE TupleSections #-}
2+
3+
module SpeedOfLetters (speedify) where
4+
5+
-- https://www.codewars.com/kata/5fc7caa854783c002196f2cb/train/haskell
6+
7+
import Data.List (groupBy, sortOn)
8+
import Data.Maybe (fromJust, fromMaybe, isJust)
9+
10+
speedify :: String -> String
11+
speedify = makeText . rebuildLetters
12+
13+
makeText :: [(Int, Char)] -> String
14+
makeText = go 0
15+
where
16+
go :: Int -> [(Int, Char)] -> String
17+
go _ [] = []
18+
go index chars@((i, c) : xs)
19+
| i == index = c : go (index + 1) xs
20+
| i < index = go index xs
21+
| otherwise = ' ' : go (index + 1) chars
22+
23+
rebuildLetters :: String -> [(Int, Char)]
24+
rebuildLetters = map last . groupOn fst . sortOn fst . zipWith (curry run) [0 ..]
25+
26+
run :: (Int, Char) -> (Int, Char)
27+
run (index, c) = (,c) . (+ index) . lookupLetter $ c
28+
29+
lookupLetter :: Char -> Int
30+
lookupLetter c
31+
| isJust mIndex = fromJust mIndex
32+
| otherwise = error "Letter not found"
33+
where
34+
mIndex = lookup c letterIndices
35+
36+
letterIndices :: [(Char, Int)]
37+
letterIndices = zip ['A' .. 'Z'] [0 ..]
38+
39+
groupOn :: (Eq b) => (a -> b) -> [a] -> [[a]]
40+
groupOn get = groupBy (\a b -> get a == get b)

test/SpeedOfLettersSpec.hs

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
module SpeedOfLettersSpec where
2+
3+
import SpeedOfLetters (speedify)
4+
import Test.HUnit
5+
import Test.Hspec
6+
7+
spec :: Spec
8+
spec = do
9+
describe "Fixed Tests" $ do
10+
it "Works for some example strings" $ do
11+
assertEqual (show "AZ") "A Z" $
12+
speedify "AZ"
13+
assertEqual (show "ABC") "A B C" $
14+
speedify "ABC"
15+
assertEqual (show "ACE") "A C E" $
16+
speedify "ACE"
17+
assertEqual (show "CBA") " A" $
18+
speedify "CBA"
19+
assertEqual (show "HELLOWORLD") " E H DLL OLO R W" $
20+
speedify "HELLOWORLD"

0 commit comments

Comments
 (0)