#ifndef MIN_VERSION_base
#if __GLASGOW_HASKELL__ >= 709
#define MIN_VERSION_base(major1,major2,minor) (((major1) <= 4) && ((major2) <= 8))
#elif __GLASGOW_HASKELL__ >= 707
#define MIN_VERSION_base(major1,major2,minor) (((major1) <= 4) && ((major2) <= 7))
#elif __GLASGOW_HASKELL__ >= 706
#define MIN_VERSION_base(major1,major2,minor) (((major1) <= 4) && ((major2) <= 6))
#else
#define MIN_VERSION_base(major1,major2,minor) 0
#endif
#endif
#ifdef __GLASGOW_HASKELL__
#define OVERLOADED_STRINGS 1
#endif
#ifdef OVERLOADED_STRINGS
#endif
module Text.PrettyPrint.Boxes
(
#ifdef TESTING
Box(Box, content)
#else
Box
#endif
, nullBox
, emptyBox
, char
, text
, para
, columns
, (<>)
, (<+>)
, hcat
, hsep
, (//)
, (/+/)
, vcat
, vsep
, punctuateH, punctuateV
#ifdef TESTING
, Alignment(..)
#else
, Alignment
#endif
#ifdef TESTING
, Content(..)
#endif
, left, right
, top, bottom
, center1, center2
, moveLeft
, moveRight
, moveUp
, moveDown
, alignHoriz
, alignVert
, align
, rows
, cols
, render
, printBox
) where
#if MIN_VERSION_base(4,8,0)
import Prelude hiding (Word)
#endif
#if MIN_VERSION_base(4,4,0)
import Data.String (words, unwords)
#else
import Data.List (words, unwords)
#endif
#ifdef OVERLOADED_STRINGS
import Data.String (IsString(..))
#endif
import Control.Arrow ((***), first)
import Data.List (foldl', intersperse)
import Data.List.Split (chunksOf)
data Box = Box { rows :: Int
, cols :: Int
, content :: Content
}
deriving (Show)
#ifdef OVERLOADED_STRINGS
instance IsString Box where
fromString = text
#endif
data Alignment = AlignFirst
| AlignCenter1
| AlignCenter2
| AlignLast
deriving (Eq, Read, Show)
top :: Alignment
top = AlignFirst
bottom :: Alignment
bottom = AlignLast
left :: Alignment
left = AlignFirst
right :: Alignment
right = AlignLast
center1 :: Alignment
center1 = AlignCenter1
center2 :: Alignment
center2 = AlignCenter2
data Content = Blank
| Text String
| Row [Box]
| Col [Box]
| SubBox Alignment Alignment Box
deriving (Show)
nullBox :: Box
nullBox = emptyBox 0 0
emptyBox :: Int -> Int -> Box
emptyBox r c = Box r c Blank
char :: Char -> Box
char c = Box 1 1 (Text [c])
text :: String -> Box
text t = Box 1 (length t) (Text t)
(<>) :: Box -> Box -> Box
l <> r = hcat top [l,r]
(<+>) :: Box -> Box -> Box
l <+> r = hcat top [l, emptyBox 0 1, r]
(//) :: Box -> Box -> Box
t // b = vcat left [t,b]
(/+/) :: Box -> Box -> Box
t /+/ b = vcat left [t, emptyBox 1 0, b]
hcat :: Alignment -> [Box] -> Box
hcat a bs = Box h w (Row $ map (alignVert a h) bs)
where h = maximum . (0:) . map rows $ bs
w = sum . map cols $ bs
hsep :: Int -> Alignment -> [Box] -> Box
hsep sep a bs = punctuateH a (emptyBox 0 sep) bs
vcat :: Alignment -> [Box] -> Box
vcat a bs = Box h w (Col $ map (alignHoriz a w) bs)
where h = sum . map rows $ bs
w = maximum . (0:) . map cols $ bs
vsep :: Int -> Alignment -> [Box] -> Box
vsep sep a bs = punctuateV a (emptyBox sep 0) bs
punctuateH :: Alignment -> Box -> [Box] -> Box
punctuateH a p bs = hcat a (intersperse p bs)
punctuateV :: Alignment -> Box -> [Box] -> Box
punctuateV a p bs = vcat a (intersperse p bs)
para :: Alignment -> Int -> String -> Box
para a n t = (\ss -> mkParaBox a (length ss) ss) $ flow n t
columns :: Alignment -> Int -> Int -> String -> [Box]
columns a w h t = map (mkParaBox a h) . chunksOf h $ flow w t
mkParaBox :: Alignment -> Int -> [String] -> Box
mkParaBox a n = alignVert top n . vcat a . map text
flow :: Int -> String -> [String]
flow n t = map (take n)
. getLines
$ foldl' addWordP (emptyPara n) (map mkWord . words $ t)
data Para = Para { paraWidth :: Int
, paraContent :: ParaContent
}
data ParaContent = Block { fullLines :: [Line]
, lastLine :: Line
}
emptyPara :: Int -> Para
emptyPara pw = Para pw (Block [] (Line 0 []))
getLines :: Para -> [String]
getLines (Para _ (Block ls l))
| lLen l == 0 = process ls
| otherwise = process (l:ls)
where process = map (unwords . reverse . map getWord . getWords) . reverse
data Line = Line { lLen :: Int, getWords :: [Word] }
mkLine :: [Word] -> Line
mkLine ws = Line (sum (map wLen ws) + length ws 1) ws
startLine :: Word -> Line
startLine = mkLine . (:[])
data Word = Word { wLen :: Int, getWord :: String }
mkWord :: String -> Word
mkWord w = Word (length w) w
addWordP :: Para -> Word -> Para
addWordP (Para pw (Block fl l)) w
| wordFits pw w l = Para pw (Block fl (addWordL w l))
| otherwise = Para pw (Block (l:fl) (startLine w))
addWordL :: Word -> Line -> Line
addWordL w (Line len ws) = Line (len + wLen w + 1) (w:ws)
wordFits :: Int -> Word -> Line -> Bool
wordFits pw w l = lLen l == 0 || lLen l + wLen w + 1 <= pw
alignHoriz :: Alignment -> Int -> Box -> Box
alignHoriz a c b = Box (rows b) c $ SubBox a AlignFirst b
alignVert :: Alignment -> Int -> Box -> Box
alignVert a r b = Box r (cols b) $ SubBox AlignFirst a b
align :: Alignment -> Alignment -> Int -> Int -> Box -> Box
align ah av r c = Box r c . SubBox ah av
moveUp :: Int -> Box -> Box
moveUp n b = alignVert top (rows b + n) b
moveDown :: Int -> Box -> Box
moveDown n b = alignVert bottom (rows b + n) b
moveLeft :: Int -> Box -> Box
moveLeft n b = alignHoriz left (cols b + n) b
moveRight :: Int -> Box -> Box
moveRight n b = alignHoriz right (cols b + n) b
render :: Box -> String
render = unlines . renderBox
takeP :: a -> Int -> [a] -> [a]
takeP _ n _ | n <= 0 = []
takeP b n [] = replicate n b
takeP b n (x:xs) = x : takeP b (n1) xs
takePA :: Alignment -> a -> Int -> [a] -> [a]
takePA c b n = glue . (takeP b (numRev c n) *** takeP b (numFwd c n)) . split
where split t = first reverse . splitAt (numRev c (length t)) $ t
glue = uncurry (++) . first reverse
numFwd AlignFirst n = n
numFwd AlignLast _ = 0
numFwd AlignCenter1 n = n `div` 2
numFwd AlignCenter2 n = (n+1) `div` 2
numRev AlignFirst _ = 0
numRev AlignLast n = n
numRev AlignCenter1 n = (n+1) `div` 2
numRev AlignCenter2 n = n `div` 2
blanks :: Int -> String
blanks = flip replicate ' '
renderBox :: Box -> [String]
renderBox (Box r c Blank) = resizeBox r c [""]
renderBox (Box r c (Text t)) = resizeBox r c [t]
renderBox (Box r c (Row bs)) = resizeBox r c
. merge
. map (renderBoxWithRows r)
$ bs
where merge = foldr (zipWith (++)) (repeat [])
renderBox (Box r c (Col bs)) = resizeBox r c
. concatMap (renderBoxWithCols c)
$ bs
renderBox (Box r c (SubBox ha va b)) = resizeBoxAligned r c ha va
. renderBox
$ b
renderBoxWithRows :: Int -> Box -> [String]
renderBoxWithRows r b = renderBox (b{rows = r})
renderBoxWithCols :: Int -> Box -> [String]
renderBoxWithCols c b = renderBox (b{cols = c})
resizeBox :: Int -> Int -> [String] -> [String]
resizeBox r c = takeP (blanks c) r . map (takeP ' ' c)
resizeBoxAligned :: Int -> Int -> Alignment -> Alignment -> [String] -> [String]
resizeBoxAligned r c ha va = takePA va (blanks c) r . map (takePA ha ' ' c)
printBox :: Box -> IO ()
printBox = putStr . render