Skip to content

Instantly share code, notes, and snippets.

@phi16
Created April 12, 2015 03:57
Show Gist options
  • Save phi16/e77ba1844923e83a10a1 to your computer and use it in GitHub Desktop.
Save phi16/e77ba1844923e83a10a1 to your computer and use it in GitHub Desktop.
import Data.Monoid
import Data.List
import Control.Applicative
import Control.Monad
import Control.Monad.State
for :: [a] -> (a -> b) -> [b]
for = flip map
data Process i o a = Process {
runProcess :: i -> (a, i, o)
}
instance Functor (Process i o) where
fmap f (Process t) = Process $ \i -> let
(v, i', o) = t i
in (f v, i', o)
instance Monoid o => Applicative (Process i o) where
pure x = Process $ \i -> (x, i, mempty)
f <*> x = Process $ \i -> let
(x', i', o) = runProcess x i
(f', i'', p) = runProcess f i'
in (f' x', i'', o <> p)
instance Monoid o => Monad (Process i o) where
return = pure
(Process u) >>= f = Process $ \i -> let
(v, i', o) = u i
(w, i'', p) = runProcess (f v) i'
in (w, i'', o <> p)
type Proc = Process [String] [String]
ioProcess :: Proc () -> String -> String
ioProcess p i = let
((), _, o) = runProcess p $ lines i
in unlines $ zipWith (\s t -> concat ["Case #",show t,": ",s]) o [1..]
line :: Proc String
line = Process $ \i -> case i of
(x:xs) -> (x, xs, [])
[] -> ([], [], [])
out :: String -> Proc ()
out s = Process $ \i -> ((), i, [s])
run :: Proc String -> Proc ()
run p = do
t <- read <$> line
replicateM_ t $ p >>= out
main :: IO ()
main = interact $ ioProcess $ run solveD
solveA :: Proc String
solveA = do
v <- head . tail . words <$> line
let
vs = map (read . return) v
r (s,f) d = if d+s > 0
then (d+s-1, f)
else (0, f+1)
i = (0,0)
return $ show $ snd $ foldl r i vs
solveB :: Proc String
solveB = do
void $ line
ps <- map read . words <$> line
let
mx = maximum ps
vs = for [1..mx] $ \n -> let
nf = fromIntegral n :: Float
u = sum $ map (pred . ceiling . (/nf) . fromIntegral) ps
in u + n :: Int
return $ show $ minimum vs
data Unit = U | I | J | K deriving (Show, Eq)
type Q = (Bool, Unit)
readQ :: Char -> Q
readQ 'i' = (False, I)
readQ 'j' = (False, J)
readQ 'k' = (False, K)
xor :: Bool -> Bool -> Bool
xor True b = not b
xor False b = b
mul :: Q -> Q -> Q
mul (a,p) (b,q) = (a`xor`b`xor`c, r) where
(c,r) = m p q
m U b = (False, b)
m b U = (False, b)
m I J = (False, K)
m J K = (False, I)
m K I = (False, J)
m a b
| a == b = (True, U)
| otherwise = (True, snd $ m b a)
pow :: Q -> Int -> Q
pow q 0 = (False, U)
pow q 1 = q
pow q n = let p = pow q (n`div`2) in case n`mod`2 of
1 -> p`mul`p`mul`q
0 -> p`mul`p
solveC :: Proc String
solveC = do
[_, r] <- map read . words <$> line
qs <- map readQ <$> line
let
len = length qs
qi = scanl1 mul qs
qkR = scanr1 mul qs
qa = head qkR
qk = reverse qkR
case qa`pow`(r`mod`4) of
(True, U) -> let
ps = map (qa`pow`) [0..3]
qis = concatMap (\p -> map (p`mul`) qi) ps
qks = concatMap (\p -> map (`mul`p) qk) ps
ip = elemIndex (False,I) qis
kp = elemIndex (False,K) qks
in case (ip, kp) of
(Just i, Just k) -> if i+k+2 < len*r
then return $ "YES"
else return $ "NO"
_ -> return "NO"
_ -> return "NO"
solveD :: Proc String
solveD = do
[x,r,c] <- map read . words <$> line
case r*c`mod`x of
0 -> procD x r c
_ -> return "RICHARD"
procD :: Int -> Int -> Int -> Proc String
procD 1 _ _ = return "GABRIEL"
procD 2 _ _ = return "GABRIEL"
procD 3 r c
| r <= 1 || c <= 1 = return "RICHARD"
| otherwise = return "GABRIEL"
procD 4 r c
| r <= 2 || c <= 2 = return "RICHARD"
| otherwise = return "GABRIEL"
procD 5 r c
| r <= 2 || c <= 2 = return "RICHARD"
| r*c == 15 = return "RICHARD"
| otherwise = return "GABRIEL"
procD 6 r c
| r <= 3 || c <= 3 = return "RICHARD"
| otherwise = return "GABRIEL"
procD x r c = return "RICHARD"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment