Skip to content

Commit

Permalink
Solve 57ebdf1c2d45a0ecd7002cd5
Browse files Browse the repository at this point in the history
  • Loading branch information
tbsklg committed Sep 14, 2024
1 parent 10d2bfe commit a2c8f39
Show file tree
Hide file tree
Showing 2 changed files with 24 additions and 0 deletions.
12 changes: 12 additions & 0 deletions src/Kyu6/InsideOut.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module Kyu6.InsideOut where

insideOut :: String -> String
insideOut xs = unwords $ map turnWord $ words xs

turnWord :: String -> String
turnWord xs
| even l = reverse (take m xs) ++ reverse (drop m xs)
| otherwise = reverse (take m xs) ++ [xs !! m] ++ reverse (drop (m + 1) xs)
where
l = length xs
m = l `div` 2
12 changes: 12 additions & 0 deletions test/Kyu6/InsideOutSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module Kyu6.InsideOutSpec where

import Kyu6.InsideOut
import Test.Hspec

spec :: Spec
spec = do
describe "Inside Out Strings" $ do
it "Basic tests" $ do
insideOut "man i need a taxi up to ubud" `shouldBe` "man i ende a atix up to budu"
insideOut "what time are we climbing up the volcano" `shouldBe` "hwta item are we milcgnib up the lovcona"
insideOut "take me to semynak" `shouldBe` "atek me to mesykan"

0 comments on commit a2c8f39

Please sign in to comment.