LoginSignup
0
0

More than 5 years have passed since last update.

1日1個 @nabetani さんの作った問題を解くAdventCalendarの12日目です。

今日の問題は http://nabetani.sakura.ne.jp/hena/ord5railsontiles/ にあります。

{-# LANGUAGE TupleSections #-}
module Doukaku.Rails (solve) where
import Data.Char (ord, chr)

solve :: String -> String
solve input = go 1 0
  where
    go p d = label p : case move p d of
      Just (p', d') -> go p' d'
      Nothing       -> []
    move p d = fmap (, direct .@. d') (conn p .@. d')
      where
        d'  = panel (input !! p) .@. d

label :: Int -> Char
label = chr . (+ ord 'A')

conn :: Int -> (Maybe Int, Maybe Int, Maybe Int, Maybe Int)
conn n = (wrap x (y - 1), wrap (x + 1) y, wrap x (y + 1), wrap (x - 1) y)
  where
    (y, x) = divMod n 3
    wrap x' y'
      | x' < 0 || 3 <= x' || y' < 0 || 3 <= y' = Nothing
      | otherwise = Just (x' + y' * 3)

direct :: (Int, Int, Int, Int)
direct = (2, 3, 0, 1)

panel :: Char -> (Int, Int, Int, Int)
panel '0' = (2, 3, 0, 1)
panel '1' = (1, 0, 3, 2)
panel '2' = (3, 2, 1, 0)

(.@.) :: (a, a, a, a) -> Int -> a
(n, _, _, _) .@. 0 = n
(_, n, _, _) .@. 1 = n
(_, _, n, _) .@. 2 = n
(_, _, _, n) .@. 3 = n

パネルの位置×上下左右で状態を表現し、伴う遷移関数を用意しました。
パネルの位置はアルファベットに対応した整数値で表しており、connは各パネルの上下左右がどこにつながっているか、
panelは各パネルの上下左右がそのパネル内のどこにつながっているか、
directは各パネルの上下左右から次のパネルに移ると次のパネルの上下左右のいずれの方向に着くかをそれぞれ表します。
directはほぼ自明なので要らないかもしれないですが、一応定義しました。
goの再帰でパネルからはみ出でNothingになるまで回し続けてます。

http://qiita.com/Nabetani/items/0ddde0164a745cd09c34 に他の方の回答もありますので、見ると参考になるでしょう。

0
0
0

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
0
0