LCD Numbers

Quiz: [QUIZ] LCD Numbers (#14)
via: http://www.sampou.org/cgi-bin/cahier.cgi?blog%3aCahier%3a2005-01-08 (日付指定のリンクはできないのだろうか?)コメントで教えて頂きました。

module Main where
import Data.Array (listArray, (!))
import Data.List (transpose, groupBy, intersperse)
import Data.Maybe (fromMaybe, listToMaybe)
import Data.Char (isDigit, digitToInt)
import System.Environment (getArgs)
import System.Console.GetOpt 

lcdDigit :: Int -> [String]
lcdDigit = (!) $ listArray (0, 9) 
    $ transpose $ map (splitsLen 4) [
  " -       -   -       -   -   -   -   -  ",
  "| |   |   |   | | | |   |     | | | | | ",
  "         -   -   -   -   -       -   -  ",
  "| |   | |     |   |   | | |   | | |   | ",
  " -       -   -       -   -       -   -  "]

scale n = foldr1 (++) . zipWith ($) (cycle [holiz, vert])
  where holiz (x:y:z) = [x:replicate n y ++ z]
	vert = concat . replicate n . holiz 

lcdShow n = unlines . map (init . foldr1 (++)) . transpose 
	      . map (scale n . lcdDigit)

----------------------------------------------
main = getArgs >>= compileOpts -- aethetic `catch`

compileOpts args
  = case getOpt Permute options args of
      (os, [ds], []) | all isDigit ds
	  -> do	(n:_) <- sequence $ reverse os ++ [return 2]
		putStr $ lcdShow n (map digitToInt ds)
      (_, _, errs) -> ioError $ userError (concat errs ++ usage)

options = [Option "s" ["scale"] (ReqArg readIO "SCALE") "scale characters"]
usage = usageInfo "Usage: lcd [OPTIONS ..] digts" options


splitsLen :: Int -> [a] -> [[a]]
splitsLen n = unfoldr (\x -> listToMaybe x >> return (splitAt n x))

追記 (2005-01-12)

unfoldrを忘れていた。

splitsLen n = unfoldr (\x -> listToMaybe x >> return (splitAt n x))