Skip to content

Instantly share code, notes, and snippets.

@louy2
Last active January 12, 2020 08:58
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 louy2/e89c985cd5b4b3bc510c8e94a67056ba to your computer and use it in GitHub Desktop.
Save louy2/e89c985cd5b4b3bc510c8e94a67056ba to your computer and use it in GitHub Desktop.
Learning Monadic Functional Programming with Paiza.jp
-- https://paiza.jp/works/mondai/skillcheck_sample/diff_str?language_uid=haskell
{-# LANGUAGE OverloadedStrings #-}
import Prelude hiding (getLine, putStrLn)
import Data.Text (Text, pack, unpack)
import Data.Text.IO (getLine, putStrLn)
import Control.Applicative (liftA2)
diffStr :: Text -> Text -> Text
diffStr s1 s2 = if s1 == s2 then "OK" else "NG"
main :: IO ()
main = liftA2 diffStr getLine getLine
>>= putStrLn
-- https://paiza.jp/works/mondai/skillcheck_sample/fizz-buzz?language_uid=haskell
(%) = mod
fizzBuzz :: Int -> String
fizzBuzz n =
if (n % 3 == 0) && (n % 5 == 0) then "Fizz Buzz"
else if n % 3 == 0 then "Fizz"
else if n % 5 == 0 then "Buzz"
else show n
main = readLn >>= mapM (putStrLn . fizzBuzz) . flip take [1..]
-- https://paiza.jp/works/mondai/skillcheck_sample/min_num?language_uid=haskell
import Data.Semigroup (Min(..), getMin, (<>))
import Control.Applicative (liftA2)
import Control.Monad (foldM)
readIntLn :: IO Int
readIntLn = readLn
main = foldM
((<$>) . (<>))
mempty
(replicate 5 (Min <$> readIntLn))
>>= print . getMin
-- https://paiza.jp/works/mondai/skillcheck_sample/sort-number?language_uid=haskell
import Data.IntMap.Strict (IntMap, insertWith, mapWithKey)
import qualified Data.IntMap.Strict as IntMap
import Control.Monad (foldM)
readIntLn :: IO Int
readIntLn = readLn
main = readIntLn >>= (\lineCount
-> foldM
(\imap -> fmap (\key -> insertWith (+) key 1 imap))
IntMap.empty
(replicate lineCount readIntLn))
>>= sequence . mapWithKey (\key count
-> mapM print $ replicate count key)
-- https://paiza.jp/works/mondai/skillcheck_sample/word-count?language_uid=haskell
import Prelude hiding (getLine, words)
import Data.Text.IO (getLine)
import Data.Text (Text, words, unpack)
import Data.HashMap.Strict (HashMap, fromList, fromListWith, toList)
import qualified Data.HashMap.Strict as HashMap
import Data.List (foldl', sortOn)
getPos = fst . snd
wordCount :: [Text] -> [(Text, (Int, Int))]
wordCount =
sortOn getPos . toList
. fromListWith (\(np, nc) (p, c) -> (min np p, c + 1))
. flip zip (zip [0..] (repeat 1))
showEntry :: (Text, (Int, Int)) -> String
showEntry (w, (_, c)) = unwords [unpack w, show c]
main :: IO ()
main = mapM_ putStrLn =<< (fmap showEntry . wordCount . words) <$> getLine
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment