Haskell Quiz/Grid Folding/Solution Dolio

From HaskellWiki
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.


The basis for my solution is simple. Consider each square to be a single-element list initially. Then, a row of such squares is a list of such lists. An entire grid is then a list of those lists.

When folding horizontally, one splits each row, reverses the half to go on top (as well as its elements, since they'll be flipped), and zips the two halves together by appending corresponding elements. This results in a top-first list of the stacked squares.

When folding vertically, one splits the grid in half, reverses the half to go on top, and zips the two grid halves together. The function that combines corresponding rows is yet another zip that appends corresponding elements (again, reversing the ones on top).

module Main where
import Control.Monad.Reader
import Data.Char
import System

grid n = break . map return $ [1..(n*n)]
 where break [] = []
       break l  = let (h,t) = splitAt n l in h : break t

fold 'T' = folder vzipper
fold 'B' = folder (flip vzipper)
fold 'L' = map (folder hzipper)
fold 'R' = map (folder $ flip hzipper)
fold _   = error "Unrecognized letter."

vzipper = zipWith (zipWith $ (++) . reverse) . reverse
hzipper = zipWith (++) . (map reverse . reverse)

folder z = uncurry z . ap (flip splitAt) ((`div` 2) . length)

pretty = unlines . map (unwords . map show)

output s | all isSpace s = error "Invalid folding scheme"
         | otherwise     = putStr s

main = do [n, s] <- getArgs
          output . pretty . foldl (flip fold) (grid $ read n) $ s