Haskell Quiz/PP Pascal/Solution Ltriant

From HaskellWiki
< Haskell Quiz‎ | PP Pascal
Revision as of 02:54, 2 November 2006 by Ltriant (talk | contribs)
Jump to navigation Jump to search


Works...kind of; adds a space or two (or three) to the end of each line.

Edit: doesn't add spaces to the end anymore :)

module Main where

import System.Environment ( getArgs )

fac :: Integer -> Integer
fac n = product [1..n]

nck :: Integer -> Integer -> Integer
nck n k = (fac n) `div` ((fac $ n - k) * (fac k))

rstrip :: Eq a => a -> [a] -> [a]
rstrip n t = reverse $ dropWhile (== n) $ reverse t

space_len :: Integer -> Integer
space_len n = mylength $ show $ (n-1) `nck` ((n-1) `div` 2)

mylength :: [a] -> Integer
mylength = toInteger . length

indent :: Integer -> [String] -> [String]
indent n t =
    (concat $ replicate (fromInteger $ (n-p) * space_len n)  " "):t
    where p = mylength t

space_out :: Integer -> [Integer] -> [String]
space_out n t =
    map (\x -> show x ++ (concat $ replicate (num_spaces x) " ")) t
    where num_spaces x = fromInteger $ (2 * space_len n) - (mylength $ show x)

pp_pascal :: Integer -> [String]
pp_pascal n =
    map (rstrip ' ' . concat . indent n . space_out n) $ f 0 n
    where f acc n | acc == n  = []
                  | otherwise = (map (nck acc) [0..acc]):(f (acc+1) n)

main :: IO ()
main =
    do args <- getArgs
       case args of
         [v] -> mapM_ putStrLn $ pp_pascal (read v :: Integer)
         _   -> error "No argument specified."