Haskell Quiz/PP Pascal/Solution Burton
< Haskell Quiz | PP Pascal
{--
*Main> ppPascal 10
1
1 1
1 2 1
1 3 3 1
1 4 6 4 1
1 5 10 10 5 1
1 6 15 20 15 6 1
1 7 21 35 35 21 7 1
1 8 28 56 70 56 28 8 1
1 9 36 84 126 126 84 36 9 1
--}
--Pascal's triangle from http://www.haskell.org/haskellwiki/Blow_your_mind
pascal :: [[Integer]]
pascal = iterate (\row -> zipWith (+) ([0] ++ row) (row ++ [0])) [1]
ppPascal :: Int -> IO ()
ppPascal n = mapM_ (putStrLn . ppRow) tr
where tr = take n pascal
mRow = last tr
pad = cols $ maximum $ mRow
cols n = if n < 10 then 1 else 1 + cols (n `div` 10)
ppRow r@(x:xs) = padRow ++ (showFirst x)
++ (concatMap showRest xs) ++ padRow
where showFirst e = (show e) ++ (padR e)
showRest e = padL ++ (show e) ++ padR e
padRow = replicate ((length mRow - length r)*pad) ' '
padL = replicate pad ' '
padR d = replicate (pad-(cols d)) ' '
A bit shorter than the above, though certainly not prettier. (reverse._.reverse) makes it easier to calculate the leading padding for each line. -- AlsonKemp
pascal :: [[Integer]]
pascal = iterate (\row -> zipWith (+) ([0] ++ row) (row ++ [0])) [1]
ppPascal :: Int -> IO ()
ppPascal n = mapM_ putStrLn $ reverse $ ppRow 0 (reverse tr)
where ppRow _ [] = []
ppRow lpads (x:xs) = (replicate lpads ' ' ++ concatMap (padNum pad) x) : (ppRow (lpads+pad) xs)
tr = take n pascal
padNum pads n = take (2*pads) (show n ++ (repeat ' '))
pad = 1 + (length $ show $ maximum $ last tr) `div` 2