Difference between revisions of "Haskell Quiz/Grid Folding/Solution Dolio"

From HaskellWiki
Jump to navigation Jump to search
m (unify folder)
m
 
(2 intermediate revisions by 2 users not shown)
Line 1: Line 1:
[[Category:Code]]
+
[[Category:Haskell Quiz solutions|Grid Folding]]
   
 
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.
 
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.
Line 6: Line 6:
   
 
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).
 
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.
 
   
 
<haskell>
 
<haskell>
 
module Main where
 
module Main where
 
import Control.Monad.Reader
 
import Control.Monad.Reader
  +
import Data.Char
 
import System
 
import System
 
data Direction = R | L | T | B deriving (Show, Read)
 
   
 
grid n = break . map return $ [1..(n*n)]
 
grid n = break . map return $ [1..(n*n)]
Line 20: Line 17:
 
break l = let (h,t) = splitAt n l in h : break t
 
break l = let (h,t) = splitAt n l in h : break t
   
fold T = folder vzipper
+
fold 'T' = folder vzipper
fold B = folder (flip vzipper)
+
fold 'B' = folder (flip vzipper)
fold L = map (folder hzipper)
+
fold 'L' = map (folder hzipper)
fold R = map (folder $ flip hzipper)
+
fold 'R' = map (folder $ flip hzipper)
  +
fold _ = error "Unrecognized letter."
   
vzipper = zipWith (zipWith ((++) . reverse)) . reverse
+
vzipper = zipWith (zipWith $ (++) . reverse) . reverse
 
hzipper = zipWith (++) . (map reverse . reverse)
 
hzipper = zipWith (++) . (map reverse . reverse)
   
folder z = uncurry z . ap (flip splitAt) (flip div 2 . length)
+
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"
pp = unlines . map unwords . map (map show)
 
  +
| otherwise = putStr s
   
 
main = do [n, s] <- getArgs
 
main = do [n, s] <- getArgs
putStr . pp . foldl (flip fold) (grid $ read n) . map (read . return) $ s
+
output . pretty . foldl (flip fold) (grid $ read n) $ s
 
</haskell>
 
</haskell>

Latest revision as of 11:14, 12 February 2010


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