Haskell Quiz/Grid Folding/Solution Dolio

From HaskellWiki
< Haskell Quiz‎ | Grid Folding
Revision as of 17:34, 27 October 2006 by Dolio (talk | contribs) (creation)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search


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).

This doesn't do any fancy error checking. The method above results in null lists for invalid sequences of folds, and will result in blank output. Sequences that are too short to stack all the squares will result in a representation of whatever the grid would look be at the end of that sequence.

module Main where
import Control.Monad.Reader
import System

data Direction = R | L | T | B deriving (Show, Read)

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

fold T = vfolder vzipper
fold B = vfolder (flip vzipper)
fold L = hfolder hzipper
fold R = hfolder (flip hzipper)

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

vfolder z = uncurry z . ap (flip splitAt) (flip div 2 . length)
hfolder z = map (uncurry z . ap (flip splitAt) (flip div 2 . length))

pp = unlines . map unwords . map (map show)

main = do [n, s] <- getArgs
          putStr . pp . foldl (flip fold) (grid $ read n) . map (read . return) $ s