----------------------------------------------------------------------------- -- -- Module : HCube.Common -- Copyright : (c) Todd Wegner 2012 -- License : BSD-style (see the LICENSE file) -- -- Maintainer : echbar137@yahoo.co.in -- Stability : provisional -- Portability : portable -- -- Common utility functions that should not be exported. ----------------------------------------------------------------------------- {-# LANGUAGE Safe #-} {-# OPTIONS_HADDOCK hide #-} module HCube.Common where import Control.Monad (liftM) import Data.List import HCube.Data getLine2 = liftM reverse $ f "" where f rd = getChar >>= g where g '\n' = return rd g '\b' = putStr " \b" >> if null rd then f "" else f $ tail rd g ch = f (ch:rd) -- Pretty prints two columns per screen. twoPagesOnOne :: String -> [String] -> [String] twoPagesOnOne sp tx = f $ splitAt (length tx `div` 2) tx where f (l1, l2) = g l1 l2 g (x:xs) (y:ys) = concat [x, sp, y] : g xs ys g [] [] = [] g xs [] = xs g [] xs = xs -- Pretty prints four columns per screen. fourPagesOnOne :: String -> [String] -> [String] fourPagesOnOne sp = twoPagesOnOne sp . twoPagesOnOne sp -- Pads spaces on the right. padR :: Int -> String -> String padR ln chs = chs ++ (replicate f ' ') where f = ln - length chs -- Pads spaces on the left. padL :: Int -> String -> String padL ln chs = (replicate f ' ') ++ chs where f = ln - length chs prShow :: Show a => Int -> a -> String prShow nm = padR nm . show plShow :: Show a => Int -> a -> String plShow nm = padL nm . show