Skip to content

Instantly share code, notes, and snippets.

@zarak
Created January 28, 2021 13:01
Show Gist options
  • Save zarak/f1ff3ce6cc5f099a90280c6ce575bd7c to your computer and use it in GitHub Desktop.
Save zarak/f1ff3ce6cc5f099a90280c6ce575bd7c to your computer and use it in GitHub Desktop.
module Test.MySolutions where
import Prelude
import Data.Foldable (traverse_)
import Data.Int (even)
import Data.Monoid (power)
import Data.Monoid.Additive (Additive (..))
import Data.String.CodeUnits (toCharArray)
import Data.Traversable (sequence)
import Data.Tuple (Tuple(..))
import Control.Monad.State (State, execState)
import Control.Monad.State.Class (modify)
import Control.Monad.Reader (Reader, runReader)
import Control.Monad.Reader.Class (ask, local)
import Control.Monad.Writer (Writer, runWriter)
import Control.Monad.Writer.Class (tell)
import Data.String (joinWith)
-- Note to reader : Add your solutions to this file
testParens :: String -> Boolean
testParens inp =
let
openTally :: Char -> Int -> Int
openTally '(' tally | tally >= 0 = tally + 1
openTally ')' tally = tally - 1
openTally _ tally = tally
sumParens :: Array Char -> State Int Unit
sumParens = traverse_ \c -> modify (openTally c)
finalTally = execState (sumParens (toCharArray inp)) 0
in
finalTally == 0
type Level = Int
type Doc = (Reader Level) String
line :: String -> Doc
line s = do
level <- ask
pure $ ((power " " level) <> s)
indent :: Doc -> Doc
indent =
local (\x -> x + 1)
cat :: Array Doc -> Doc
cat arr = do
x <- sequence arr
pure $ joinWith "\n" x
render :: Doc -> String
render d =
runReader d 0
sumArrayWriter :: Array Int -> Writer (Additive Int) Unit
sumArrayWriter = traverse_ \n -> do
tell $ Additive n
pure unit
collatz :: Int -> Tuple Int (Array Int)
collatz n = runWriter $ collatzLog n 0
collatzLog :: Int -> Int -> Writer (Array Int) Int
collatzLog n acc
| (n > 1) = do
tell [n]
if even n
then
collatzLog (n / 2) (acc + 1)
else
collatzLog (3 * n + 1) (acc + 1)
| otherwise = do
tell [1]
pure acc
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment