Skip to content

Instantly share code, notes, and snippets.

@mihassan
Created May 30, 2024 21:50
Show Gist options
  • Save mihassan/167117f71a7d500c98e9f4fb410c30ca to your computer and use it in GitHub Desktop.
Save mihassan/167117f71a7d500c98e9f4fb410c30ca to your computer and use it in GitHub Desktop.
Solution of the hacker rank expressions problem in Haskell
{-# LANGUAGE RecordWildCards #-}
-- | Problem https://www.hackerrank.com/challenges/expressions
import Control.Arrow
import Data.List
import Data.Maybe
import Data.Set (Set)
import qualified Data.Set as Set
data Op = Add | Sub | Mul
deriving (Show, Eq)
allOps :: [Op]
allOps = [Add, Sub, Mul]
showOp :: Op -> String
showOp Add = "+"
showOp Sub = "-"
showOp Mul = "*"
evalOp :: Op -> Int -> Int -> Int
evalOp Add = (+)
evalOp Sub = (-)
evalOp Mul = (*)
data Expr = Val Int | App Expr Op Int -- left-associative
deriving (Show)
showExpr :: Expr -> String
showExpr (Val x) = show x
showExpr (App e op x) = showExpr e ++ showOp op ++ show x
evalModExpr :: Int -> Expr -> Int
evalModExpr m (Val x) = x `mod` m
evalModExpr m (App e op x) = evalOp op (evalModExpr m e) x `mod` m
data Tree = Tree
{ level :: Int,
expr :: Expr,
edges :: [Tree]
}
deriving (Show)
parse :: String -> [Int]
parse = lines >>> last >>> words >>> map read
solve :: [Int] -> Expr
solve = buildTree >>> findExpr
buildTree :: [Int] -> Tree
buildTree (x : xs) =
Tree 0 (Val x) [go 1 (Val x) op xs | op <- allOps]
where
go :: Int -> Expr -> Op -> [Int] -> Tree
go l e o [x] = Tree l (App e o x) []
go l e o (x : xs) = Tree l (App e o x) [go (l + 1) (App e o x) o' xs | o' <- allOps]
findExpr :: Tree -> Expr
findExpr t = fromJust . snd $ go Set.empty t
where
go :: Set (Int, Int) -> Tree -> (Set (Int, Int), Maybe Expr)
go s t@Tree {..}
| (level, v) `Set.member` s = (s, Nothing)
| v == 0 && null edges = (s', Just expr)
| otherwise = foldl' f (s', Nothing) edges
where
v = evalModExpr 101 expr
s' = Set.insert (level, v) s
f (s, Just e) _ = (s, Just e)
f (s, Nothing) t' = go s t'
main :: IO ()
main = interact $ showExpr . solve . parse
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment