Skip to content

Instantly share code, notes, and snippets.

@essic
Created February 16, 2019 21:37
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save essic/21116d67b112ea314d893c83f64569fc to your computer and use it in GitHub Desktop.
Save essic/21116d67b112ea314d893c83f64569fc to your computer and use it in GitHub Desktop.
Kata (Haskell) - FooBarQix created by essic - https://repl.it/@essic/Kata-Haskell-FooBarQix
-- http://codingdojo.org/kata/FooBarQix/
{-# LANGUAGE OverloadedStrings #-}
import Data.Text as T
import qualified Data.Map.Strict as M
import qualified Data.Char as C
import qualified Data.List as L
import Data.Maybe (catMaybes, fromMaybe)
newtype Digit = D Text
deriving (Show,Eq)
newtype Number = N [Digit]
deriving (Show, Eq)
isNumeric :: Text -> Maybe Text
isNumeric t =
(const t) <$> (textToInt t)
toNumber :: Text -> Maybe Number
toNumber =
fmap (N . fmap D . T.chunksOf 1 ) . isNumeric
digits :: Number -> [Digit]
digits (N ds) = ds
digitToText :: Digit -> Text
digitToText (D t) = t
isDivisibleBy :: Int -> Number -> Maybe (Text -> Text)
isDivisibleBy i number = do
n <- numberToInt number
case n % i of
0 -> Just id
x -> Nothing
where
(%) :: Int -> Int -> Int
(%) = mod
foo :: Number -> Maybe Text
foo = fmap ($ "Foo") . isDivisibleBy 3
bar :: Number -> Maybe Text
bar = fmap ($ "Bar") . isDivisibleBy 5
qix :: Number -> Maybe Text
qix = fmap ($ "Qix") . isDivisibleBy 7
replaceWithZero :: Text -> Text
replaceWithZero t =
T.concat $ T.replace "0" "*" <$> T.chunksOf 1 t
is :: Text -> Digit -> Maybe Bool
is t (D d)
| t == d = Just True
| otherwise = Nothing
isFoo :: Digit -> Maybe Text
isFoo = fmap (const "Foo") . is "3"
isBar :: Digit -> Maybe Text
isBar = fmap (const "Bar") . is "5"
isQix :: Digit -> Maybe Text
isQix = fmap (const "Qix") . is "7"
isZero :: Digit -> Maybe Text
isZero = fmap (const "*") . is "0"
numberToInt :: Number -> Maybe Int
numberToInt (N digits) =
case reads . unpack $ T.concat ( digitToText <$> digits) of
[(s,_)] -> Just s
_ -> Nothing
textToInt :: Text -> Maybe Int
textToInt t =
case reads . unpack $ t of
[(s,_)] -> Just s
_ -> Nothing
replaceNumberIfAnyTrue :: [Number -> Maybe Text] -> Number -> Maybe Text
replaceNumberIfAnyTrue fs number =
case catMaybes $ ($ number) <$> fs of
[] -> Nothing
r -> Just $ T.concat r
replaceDigit :: [Digit -> Maybe Text] -> Digit -> Maybe Text
replaceDigit [] _ = Nothing
replaceDigit (f:fs) d =
case f d of
Nothing -> replaceDigit fs d
r -> r
exampleStep2 :: M.Map Text Text
exampleStep2 =
let results =
[
("101","1*1")
, ("303","FooFoo*Foo")
, ("105","FooBarQix*Bar")
, ("10101","FooQix**")
]
in
M.fromList results
exampleStep1 :: M.Map Text Text
exampleStep1 =
let results =
[
("1","1")
, ("2","2")
, ("3","FooFoo")
, ("4","4")
, ("5","BarBar")
, ("6","Foo")
, ("7","QixQix")
, ("8","8")
, ("9","Foo")
, ("10","Bar")
, ("13","Foo")
, ("15","FooBarBar")
, ("21","FooQix")
, ("33","FooFooFoo")
, ("51","FooBar")
, ("53" ,"BarFoo")
]
in
M.fromList results
-- We made it (Maybe Text) instead of Text as specified in the Kata, for convinience, it cost nothing to be safe in Haskell :p
computeStep1 :: Text -> Maybe Text
computeStep1 input = do
t <- isNumeric input
number <- toNumber t
case (replaceNumberIfAnyTrue [foo,bar,qix] number,T.concat . catMaybes $ (replaceDigit [isFoo,isBar,isQix]) <$> (digits number)) of
(Nothing,"") -> pure input
(Nothing,x) -> pure x
(Just fbrResults,"") -> pure fbrResults
(Just fbrResults,x) -> pure $ T.concat [fbrResults,x]
computeStep2 :: Text -> Maybe Text
computeStep2 input = do
t <- isNumeric input
number <- toNumber t
case (replaceNumberIfAnyTrue [foo,bar,qix] number,T.concat . catMaybes $ (replaceDigit [isFoo,isBar,isQix,isZero]) <$> (digits number)) of
(Nothing, "") -> pure t
(Nothing, x ) -> pure $ if T.all (\c -> '*' == c) x then replaceWithZero t else x
(Just fbrResults , "") -> pure fbrResults
(Just fbrResults , x) -> pure $ T.concat [fbrResults,x]
runExampleStep1 :: M.Map Text Text
runExampleStep1 =
M.fromList $
(\t ->
case computeStep1 t of
Just r -> (t,r)
Nothing -> (t,"ERROR, Can't compute!")
) <$> M.keys exampleStep1
runExampleStep2 :: M.Map Text Text
runExampleStep2 =
M.fromList $
(\t ->
case computeStep2 t of
Just r -> (t,r)
Nothing -> (t,"ERROR, Can't compute!")
) <$> M.keys exampleStep2
main :: IO ()
main = do
print . toNumber . replaceWithZero $ "101"
computedStep1 <- pure runExampleStep1
computedStep2 <- pure runExampleStep2
print computedStep1
(print $ computedStep1 == exampleStep1)
print computedStep2
(print $ computedStep2 == exampleStep2)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment