2017-03-04 13:03:41 +01:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
2010-12-12 20:09:14 -08:00
|
|
|
{-
|
2017-05-13 23:30:13 +02:00
|
|
|
Copyright (C) 2010-2017 John MacFarlane <jgm@berkeley.edu>
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111(-1)307 USA
|
|
|
|
-}
|
|
|
|
|
|
|
|
{- |
|
|
|
|
Module : Text.Pandoc.Pretty
|
2017-05-13 23:30:13 +02:00
|
|
|
Copyright : Copyright (C) 2010-2017 John MacFarlane
|
2012-07-26 22:32:53 -07:00
|
|
|
License : GNU GPL, version 2 or above
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
A prettyprinting library for the production of text documents,
|
|
|
|
including wrapped text, indentated blocks, and tables.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Text.Pandoc.Pretty (
|
|
|
|
Doc
|
|
|
|
, render
|
|
|
|
, cr
|
|
|
|
, blankline
|
2014-07-27 07:56:55 -07:00
|
|
|
, blanklines
|
2010-12-12 20:09:14 -08:00
|
|
|
, space
|
|
|
|
, text
|
|
|
|
, char
|
|
|
|
, prefixed
|
|
|
|
, flush
|
|
|
|
, nest
|
|
|
|
, hang
|
2011-12-31 11:39:33 -08:00
|
|
|
, beforeNonBlank
|
2010-12-12 20:09:14 -08:00
|
|
|
, nowrap
|
2016-12-05 00:49:53 +01:00
|
|
|
, afterBreak
|
2010-12-12 20:09:14 -08:00
|
|
|
, offset
|
2015-02-03 14:30:46 +01:00
|
|
|
, minOffset
|
2010-12-12 20:09:14 -08:00
|
|
|
, height
|
|
|
|
, lblock
|
|
|
|
, cblock
|
|
|
|
, rblock
|
|
|
|
, (<>)
|
|
|
|
, (<+>)
|
|
|
|
, ($$)
|
|
|
|
, ($+$)
|
|
|
|
, isEmpty
|
|
|
|
, empty
|
|
|
|
, cat
|
|
|
|
, hcat
|
|
|
|
, hsep
|
|
|
|
, vcat
|
|
|
|
, vsep
|
2014-01-02 21:09:39 -08:00
|
|
|
, nestle
|
2011-11-18 13:10:45 -08:00
|
|
|
, chomp
|
2010-12-20 19:09:01 -08:00
|
|
|
, inside
|
2010-12-19 10:13:11 -08:00
|
|
|
, braces
|
|
|
|
, brackets
|
2010-12-19 12:39:49 -08:00
|
|
|
, parens
|
2010-12-22 00:22:28 -08:00
|
|
|
, quotes
|
|
|
|
, doubleQuotes
|
2012-01-25 23:15:18 -08:00
|
|
|
, charWidth
|
2012-01-25 23:30:21 -08:00
|
|
|
, realLength
|
2010-12-12 20:09:14 -08:00
|
|
|
)
|
|
|
|
|
|
|
|
where
|
2017-06-16 23:29:37 +02:00
|
|
|
import Control.Monad.State.Strict
|
2010-12-12 20:09:14 -08:00
|
|
|
import Data.Char (isSpace)
|
2017-03-04 13:03:41 +01:00
|
|
|
import Data.Foldable (toList)
|
|
|
|
import Data.List (intersperse)
|
2016-08-30 13:43:50 -04:00
|
|
|
import Data.Monoid ((<>))
|
2017-03-04 13:03:41 +01:00
|
|
|
import Data.Sequence (Seq, ViewL (..), fromList, mapWithIndex, singleton, viewl,
|
|
|
|
(<|))
|
|
|
|
import qualified Data.Sequence as Seq
|
|
|
|
import Data.String
|
2010-12-12 20:09:14 -08:00
|
|
|
|
2014-02-06 23:10:59 +01:00
|
|
|
data RenderState a = RenderState{
|
2017-03-04 13:03:41 +01:00
|
|
|
output :: [a] -- ^ In reverse order
|
|
|
|
, prefix :: String
|
|
|
|
, usePrefix :: Bool
|
|
|
|
, lineLength :: Maybe Int -- ^ 'Nothing' means no wrapping
|
|
|
|
, column :: Int
|
|
|
|
, newlines :: Int -- ^ Number of preceding newlines
|
2010-12-12 20:09:14 -08:00
|
|
|
}
|
|
|
|
|
|
|
|
type DocState a = State (RenderState a) ()
|
|
|
|
|
|
|
|
data D = Text Int String
|
|
|
|
| Block Int [String]
|
|
|
|
| Prefixed String Doc
|
2011-12-31 11:39:33 -08:00
|
|
|
| BeforeNonBlank Doc
|
2010-12-12 20:09:14 -08:00
|
|
|
| Flush Doc
|
|
|
|
| BreakingSpace
|
2016-12-05 00:49:53 +01:00
|
|
|
| AfterBreak String
|
2010-12-12 20:09:14 -08:00
|
|
|
| CarriageReturn
|
|
|
|
| NewLine
|
2014-07-27 07:56:55 -07:00
|
|
|
| BlankLines Int -- number of blank lines
|
2017-05-27 23:16:07 +02:00
|
|
|
deriving (Show, Eq)
|
2010-12-12 20:09:14 -08:00
|
|
|
|
2012-02-05 14:25:12 -08:00
|
|
|
newtype Doc = Doc { unDoc :: Seq D }
|
2017-05-27 23:16:07 +02:00
|
|
|
deriving (Monoid, Show, Eq)
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
instance IsString Doc where
|
|
|
|
fromString = text
|
|
|
|
|
2011-12-31 11:39:33 -08:00
|
|
|
isBlank :: D -> Bool
|
|
|
|
isBlank BreakingSpace = True
|
|
|
|
isBlank CarriageReturn = True
|
|
|
|
isBlank NewLine = True
|
2014-07-27 07:56:55 -07:00
|
|
|
isBlank (BlankLines _) = True
|
2011-12-31 11:39:33 -08:00
|
|
|
isBlank (Text _ (c:_)) = isSpace c
|
|
|
|
isBlank _ = False
|
|
|
|
|
2010-12-12 20:09:14 -08:00
|
|
|
-- | True if the document is empty.
|
|
|
|
isEmpty :: Doc -> Bool
|
2016-11-23 15:18:03 +01:00
|
|
|
isEmpty = Seq.null . unDoc
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
-- | The empty document.
|
|
|
|
empty :: Doc
|
|
|
|
empty = mempty
|
|
|
|
|
|
|
|
-- | Concatenate a list of 'Doc's.
|
|
|
|
cat :: [Doc] -> Doc
|
|
|
|
cat = mconcat
|
|
|
|
|
|
|
|
-- | Same as 'cat'.
|
|
|
|
hcat :: [Doc] -> Doc
|
|
|
|
hcat = mconcat
|
|
|
|
|
|
|
|
-- | Concatenate a list of 'Doc's, putting breakable spaces
|
|
|
|
-- between them.
|
2012-02-05 19:57:59 -08:00
|
|
|
infixr 6 <+>
|
2010-12-12 20:09:14 -08:00
|
|
|
(<+>) :: Doc -> Doc -> Doc
|
|
|
|
(<+>) x y = if isEmpty x
|
|
|
|
then y
|
|
|
|
else if isEmpty y
|
|
|
|
then x
|
|
|
|
else x <> space <> y
|
|
|
|
|
|
|
|
-- | Same as 'cat', but putting breakable spaces between the
|
|
|
|
-- 'Doc's.
|
|
|
|
hsep :: [Doc] -> Doc
|
|
|
|
hsep = foldr (<+>) empty
|
|
|
|
|
2012-02-05 19:57:59 -08:00
|
|
|
infixr 5 $$
|
2010-12-12 20:09:14 -08:00
|
|
|
-- | @a $$ b@ puts @a@ above @b@.
|
|
|
|
($$) :: Doc -> Doc -> Doc
|
|
|
|
($$) x y = if isEmpty x
|
|
|
|
then y
|
|
|
|
else if isEmpty y
|
|
|
|
then x
|
|
|
|
else x <> cr <> y
|
|
|
|
|
2012-02-05 19:57:59 -08:00
|
|
|
infixr 5 $+$
|
2015-04-02 21:09:01 -07:00
|
|
|
-- | @a $+$ b@ puts @a@ above @b@, with a blank line between.
|
2010-12-12 20:09:14 -08:00
|
|
|
($+$) :: Doc -> Doc -> Doc
|
|
|
|
($+$) x y = if isEmpty x
|
|
|
|
then y
|
|
|
|
else if isEmpty y
|
|
|
|
then x
|
|
|
|
else x <> blankline <> y
|
|
|
|
|
|
|
|
-- | List version of '$$'.
|
|
|
|
vcat :: [Doc] -> Doc
|
|
|
|
vcat = foldr ($$) empty
|
|
|
|
|
|
|
|
-- | List version of '$+$'.
|
|
|
|
vsep :: [Doc] -> Doc
|
|
|
|
vsep = foldr ($+$) empty
|
|
|
|
|
2014-01-02 21:09:39 -08:00
|
|
|
-- | Removes leading blank lines from a 'Doc'.
|
|
|
|
nestle :: Doc -> Doc
|
|
|
|
nestle (Doc d) = Doc $ go d
|
|
|
|
where go x = case viewl x of
|
2014-07-27 07:56:55 -07:00
|
|
|
(BlankLines _ :< rest) -> go rest
|
2017-03-04 13:03:41 +01:00
|
|
|
(NewLine :< rest) -> go rest
|
|
|
|
_ -> x
|
2014-01-02 21:09:39 -08:00
|
|
|
|
2011-11-18 13:10:45 -08:00
|
|
|
-- | Chomps trailing blank space off of a 'Doc'.
|
|
|
|
chomp :: Doc -> Doc
|
|
|
|
chomp d = Doc (fromList dl')
|
|
|
|
where dl = toList (unDoc d)
|
2013-02-28 20:22:08 -08:00
|
|
|
dl' = reverse $ go $ reverse dl
|
2017-03-04 13:03:41 +01:00
|
|
|
go [] = []
|
|
|
|
go (BreakingSpace : xs) = go xs
|
2013-02-28 20:22:08 -08:00
|
|
|
go (CarriageReturn : xs) = go xs
|
2017-03-04 13:03:41 +01:00
|
|
|
go (NewLine : xs) = go xs
|
|
|
|
go (BlankLines _ : xs) = go xs
|
|
|
|
go (Prefixed s d' : xs) = Prefixed s (chomp d') : xs
|
|
|
|
go xs = xs
|
2011-11-18 13:10:45 -08:00
|
|
|
|
2016-07-14 23:38:44 -07:00
|
|
|
outp :: (IsString a) => Int -> String -> DocState a
|
2012-08-13 15:52:41 -07:00
|
|
|
outp off s | off < 0 = do -- offset < 0 means newline characters
|
2010-12-12 20:09:14 -08:00
|
|
|
st' <- get
|
|
|
|
let rawpref = prefix st'
|
|
|
|
when (column st' == 0 && usePrefix st' && not (null rawpref)) $ do
|
|
|
|
let pref = reverse $ dropWhile isSpace $ reverse rawpref
|
|
|
|
modify $ \st -> st{ output = fromString pref : output st
|
2012-01-25 23:30:21 -08:00
|
|
|
, column = column st + realLength pref }
|
2014-07-27 07:56:55 -07:00
|
|
|
let numnewlines = length $ takeWhile (=='\n') $ reverse s
|
2012-08-13 15:52:41 -07:00
|
|
|
modify $ \st -> st { output = fromString s : output st
|
|
|
|
, column = 0
|
2014-07-27 07:56:55 -07:00
|
|
|
, newlines = newlines st + numnewlines }
|
2012-08-13 15:52:41 -07:00
|
|
|
outp off s = do -- offset >= 0 (0 might be combining char)
|
2010-12-12 20:09:14 -08:00
|
|
|
st' <- get
|
|
|
|
let pref = prefix st'
|
|
|
|
when (column st' == 0 && usePrefix st' && not (null pref)) $ do
|
|
|
|
modify $ \st -> st{ output = fromString pref : output st
|
2012-01-25 23:30:21 -08:00
|
|
|
, column = column st + realLength pref }
|
2010-12-12 20:09:14 -08:00
|
|
|
modify $ \st -> st{ output = fromString s : output st
|
|
|
|
, column = column st + off
|
|
|
|
, newlines = 0 }
|
|
|
|
|
|
|
|
-- | Renders a 'Doc'. @render (Just n)@ will use
|
|
|
|
-- a line length of @n@ to reflow text on breakable spaces.
|
|
|
|
-- @render Nothing@ will not reflow text.
|
2016-07-14 23:38:44 -07:00
|
|
|
render :: (IsString a) => Maybe Int -> Doc -> a
|
2010-12-12 20:09:14 -08:00
|
|
|
render linelen doc = fromString . mconcat . reverse . output $
|
|
|
|
execState (renderDoc doc) startingState
|
|
|
|
where startingState = RenderState{
|
|
|
|
output = mempty
|
|
|
|
, prefix = ""
|
|
|
|
, usePrefix = True
|
|
|
|
, lineLength = linelen
|
|
|
|
, column = 0
|
|
|
|
, newlines = 2 }
|
|
|
|
|
|
|
|
renderDoc :: (IsString a, Monoid a)
|
|
|
|
=> Doc -> DocState a
|
|
|
|
renderDoc = renderList . toList . unDoc
|
|
|
|
|
2015-01-19 12:46:27 +00:00
|
|
|
data IsBlock = IsBlock Int [String]
|
|
|
|
|
|
|
|
-- This would be nicer with a pattern synonym
|
|
|
|
-- pattern VBlock i s <- mkIsBlock -> Just (IsBlock ..)
|
|
|
|
|
2010-12-12 20:09:14 -08:00
|
|
|
renderList :: (IsString a, Monoid a)
|
|
|
|
=> [D] -> DocState a
|
|
|
|
renderList [] = return ()
|
|
|
|
renderList (Text off s : xs) = do
|
|
|
|
outp off s
|
|
|
|
renderList xs
|
|
|
|
|
|
|
|
renderList (Prefixed pref d : xs) = do
|
|
|
|
st <- get
|
|
|
|
let oldPref = prefix st
|
|
|
|
put st{ prefix = prefix st ++ pref }
|
|
|
|
renderDoc d
|
|
|
|
modify $ \s -> s{ prefix = oldPref }
|
|
|
|
renderList xs
|
|
|
|
|
|
|
|
renderList (Flush d : xs) = do
|
|
|
|
st <- get
|
|
|
|
let oldUsePrefix = usePrefix st
|
|
|
|
put st{ usePrefix = False }
|
|
|
|
renderDoc d
|
|
|
|
modify $ \s -> s{ usePrefix = oldUsePrefix }
|
|
|
|
renderList xs
|
|
|
|
|
2011-12-31 11:39:33 -08:00
|
|
|
renderList (BeforeNonBlank d : xs) =
|
|
|
|
case xs of
|
|
|
|
(x:_) | isBlank x -> renderList xs
|
|
|
|
| otherwise -> renderDoc d >> renderList xs
|
|
|
|
[] -> renderList xs
|
|
|
|
|
2016-11-23 15:18:03 +01:00
|
|
|
renderList [BlankLines _] = return ()
|
|
|
|
|
|
|
|
renderList (BlankLines m : BlankLines n : xs) =
|
|
|
|
renderList (BlankLines (max m n) : xs)
|
|
|
|
|
2014-07-27 07:56:55 -07:00
|
|
|
renderList (BlankLines num : xs) = do
|
2010-12-12 20:09:14 -08:00
|
|
|
st <- get
|
|
|
|
case output st of
|
2016-11-23 15:18:03 +01:00
|
|
|
_ | newlines st > num -> return ()
|
2014-07-27 07:56:55 -07:00
|
|
|
| otherwise -> replicateM_ (1 + num - newlines st) (outp (-1) "\n")
|
2010-12-12 20:09:14 -08:00
|
|
|
renderList xs
|
|
|
|
|
2014-10-20 20:26:08 -07:00
|
|
|
renderList (CarriageReturn : BlankLines m : xs) =
|
|
|
|
renderList (BlankLines m : xs)
|
|
|
|
|
2010-12-12 20:09:14 -08:00
|
|
|
renderList (CarriageReturn : xs) = do
|
|
|
|
st <- get
|
|
|
|
if newlines st > 0 || null xs
|
|
|
|
then renderList xs
|
|
|
|
else do
|
|
|
|
outp (-1) "\n"
|
|
|
|
renderList xs
|
|
|
|
|
|
|
|
renderList (NewLine : xs) = do
|
|
|
|
outp (-1) "\n"
|
|
|
|
renderList xs
|
|
|
|
|
2010-12-21 16:45:13 -08:00
|
|
|
renderList (BreakingSpace : CarriageReturn : xs) = renderList (CarriageReturn:xs)
|
|
|
|
renderList (BreakingSpace : NewLine : xs) = renderList (NewLine:xs)
|
2014-07-27 07:56:55 -07:00
|
|
|
renderList (BreakingSpace : BlankLines n : xs) = renderList (BlankLines n:xs)
|
2010-12-21 16:45:13 -08:00
|
|
|
renderList (BreakingSpace : BreakingSpace : xs) = renderList (BreakingSpace:xs)
|
2010-12-12 20:09:14 -08:00
|
|
|
renderList (BreakingSpace : xs) = do
|
2017-03-04 13:03:41 +01:00
|
|
|
let isText (Text _ _) = True
|
|
|
|
isText (Block _ _) = True
|
|
|
|
isText (AfterBreak _) = True
|
|
|
|
isText _ = False
|
2010-12-12 20:09:14 -08:00
|
|
|
let isBreakingSpace BreakingSpace = True
|
|
|
|
isBreakingSpace _ = False
|
|
|
|
let xs' = dropWhile isBreakingSpace xs
|
|
|
|
let next = takeWhile isText xs'
|
|
|
|
st <- get
|
|
|
|
let off = sum $ map offsetOf next
|
|
|
|
case lineLength st of
|
|
|
|
Just l | column st + 1 + off > l -> do
|
|
|
|
outp (-1) "\n"
|
|
|
|
renderList xs'
|
|
|
|
_ -> do
|
|
|
|
outp 1 " "
|
|
|
|
renderList xs'
|
|
|
|
|
2016-12-05 00:49:53 +01:00
|
|
|
renderList (AfterBreak s : xs) = do
|
|
|
|
st <- get
|
|
|
|
if newlines st > 0
|
|
|
|
then outp (realLength s) s
|
|
|
|
else return ()
|
|
|
|
renderList xs
|
|
|
|
|
2015-01-19 12:46:27 +00:00
|
|
|
renderList (Block i1 s1 : Block i2 s2 : xs) =
|
|
|
|
renderList (mergeBlocks False (IsBlock i1 s1) (IsBlock i2 s2) : xs)
|
2010-12-12 20:09:14 -08:00
|
|
|
|
2015-01-19 12:46:27 +00:00
|
|
|
renderList (Block i1 s1 : BreakingSpace : Block i2 s2 : xs) =
|
|
|
|
renderList (mergeBlocks True (IsBlock i1 s1) (IsBlock i2 s2) : xs)
|
2010-12-12 20:09:14 -08:00
|
|
|
|
2016-11-23 15:18:03 +01:00
|
|
|
renderList (Block _width lns : xs) = do
|
2010-12-12 20:09:14 -08:00
|
|
|
st <- get
|
|
|
|
let oldPref = prefix st
|
2012-01-25 23:30:21 -08:00
|
|
|
case column st - realLength oldPref of
|
2010-12-12 20:09:14 -08:00
|
|
|
n | n > 0 -> modify $ \s -> s{ prefix = oldPref ++ replicate n ' ' }
|
2017-03-04 13:03:41 +01:00
|
|
|
_ -> return ()
|
2016-11-23 15:18:03 +01:00
|
|
|
renderList $ intersperse CarriageReturn (map (Text 0) lns)
|
2010-12-12 20:09:14 -08:00
|
|
|
modify $ \s -> s{ prefix = oldPref }
|
|
|
|
renderList xs
|
|
|
|
|
2015-01-19 12:46:27 +00:00
|
|
|
mergeBlocks :: Bool -> IsBlock -> IsBlock -> D
|
|
|
|
mergeBlocks addSpace (IsBlock w1 lns1) (IsBlock w2 lns2) =
|
2010-12-12 20:09:14 -08:00
|
|
|
Block (w1 + w2 + if addSpace then 1 else 0) $
|
2016-11-23 15:18:03 +01:00
|
|
|
zipWith (\l1 l2 -> pad w1 l1 ++ l2) lns1' (map sp lns2')
|
|
|
|
where (lns1', lns2') = case (length lns1, length lns2) of
|
|
|
|
(x, y) | x > y -> (lns1,
|
|
|
|
lns2 ++ replicate (x - y) "")
|
|
|
|
| x < y -> (lns1 ++ replicate (y - x) "",
|
|
|
|
lns2)
|
|
|
|
| otherwise -> (lns1, lns2)
|
2012-01-25 23:30:21 -08:00
|
|
|
pad n s = s ++ replicate (n - realLength s) ' '
|
2010-12-12 20:09:14 -08:00
|
|
|
sp "" = ""
|
|
|
|
sp xs = if addSpace then (' ' : xs) else xs
|
|
|
|
|
|
|
|
offsetOf :: D -> Int
|
2017-03-04 13:03:41 +01:00
|
|
|
offsetOf (Text o _) = o
|
|
|
|
offsetOf (Block w _) = w
|
|
|
|
offsetOf BreakingSpace = 1
|
|
|
|
offsetOf _ = 0
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
-- | A literal string.
|
|
|
|
text :: String -> Doc
|
|
|
|
text = Doc . toChunks
|
2012-02-05 14:25:12 -08:00
|
|
|
where toChunks :: String -> Seq D
|
2010-12-12 20:09:14 -08:00
|
|
|
toChunks [] = mempty
|
|
|
|
toChunks s = case break (=='\n') s of
|
2012-02-05 14:25:12 -08:00
|
|
|
([], _:ys) -> NewLine <| toChunks ys
|
|
|
|
(xs, _:ys) -> Text (realLength xs) xs <|
|
|
|
|
(NewLine <| toChunks ys)
|
2012-01-25 23:30:21 -08:00
|
|
|
(xs, []) -> singleton $ Text (realLength xs) xs
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
-- | A character.
|
|
|
|
char :: Char -> Doc
|
|
|
|
char c = text [c]
|
|
|
|
|
|
|
|
-- | A breaking (reflowable) space.
|
|
|
|
space :: Doc
|
|
|
|
space = Doc $ singleton BreakingSpace
|
|
|
|
|
|
|
|
-- | A carriage return. Does nothing if we're at the beginning of
|
|
|
|
-- a line; otherwise inserts a newline.
|
|
|
|
cr :: Doc
|
|
|
|
cr = Doc $ singleton CarriageReturn
|
|
|
|
|
|
|
|
-- | Inserts a blank line unless one exists already.
|
|
|
|
-- (@blankline <> blankline@ has the same effect as @blankline@.
|
|
|
|
blankline :: Doc
|
2014-07-27 07:56:55 -07:00
|
|
|
blankline = Doc $ singleton (BlankLines 1)
|
|
|
|
|
2017-08-08 18:44:18 +03:00
|
|
|
-- | Inserts blank lines unless they exist already.
|
|
|
|
-- (@blanklines m <> blanklines n@ has the same effect as @blanklines (max m n)@.
|
2014-07-27 07:56:55 -07:00
|
|
|
blanklines :: Int -> Doc
|
|
|
|
blanklines n = Doc $ singleton (BlankLines n)
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
-- | Uses the specified string as a prefix for every line of
|
2010-12-20 19:09:01 -08:00
|
|
|
-- the inside document (except the first, if not at the beginning
|
2010-12-12 20:09:14 -08:00
|
|
|
-- of the line).
|
|
|
|
prefixed :: String -> Doc -> Doc
|
|
|
|
prefixed pref doc = Doc $ singleton $ Prefixed pref doc
|
|
|
|
|
|
|
|
-- | Makes a 'Doc' flush against the left margin.
|
|
|
|
flush :: Doc -> Doc
|
|
|
|
flush doc = Doc $ singleton $ Flush doc
|
|
|
|
|
|
|
|
-- | Indents a 'Doc' by the specified number of spaces.
|
|
|
|
nest :: Int -> Doc -> Doc
|
|
|
|
nest ind = prefixed (replicate ind ' ')
|
|
|
|
|
|
|
|
-- | A hanging indent. @hang ind start doc@ prints @start@,
|
|
|
|
-- then @doc@, leaving an indent of @ind@ spaces on every
|
|
|
|
-- line but the first.
|
|
|
|
hang :: Int -> Doc -> Doc -> Doc
|
|
|
|
hang ind start doc = start <> nest ind doc
|
|
|
|
|
2011-12-31 11:39:33 -08:00
|
|
|
-- | @beforeNonBlank d@ conditionally includes @d@ unless it is
|
|
|
|
-- followed by blank space.
|
|
|
|
beforeNonBlank :: Doc -> Doc
|
|
|
|
beforeNonBlank d = Doc $ singleton (BeforeNonBlank d)
|
|
|
|
|
2010-12-12 20:09:14 -08:00
|
|
|
-- | Makes a 'Doc' non-reflowable.
|
|
|
|
nowrap :: Doc -> Doc
|
2012-02-08 08:32:32 -08:00
|
|
|
nowrap doc = Doc $ mapWithIndex replaceSpace $ unDoc doc
|
|
|
|
where replaceSpace _ BreakingSpace = Text 1 " "
|
2017-03-04 13:03:41 +01:00
|
|
|
replaceSpace _ x = x
|
2010-12-12 20:09:14 -08:00
|
|
|
|
2016-12-05 00:49:53 +01:00
|
|
|
-- | Content to print only if it comes at the beginning of a line,
|
|
|
|
-- to be used e.g. for escaping line-initial `.` in groff man.
|
|
|
|
afterBreak :: String -> Doc
|
|
|
|
afterBreak s = Doc $ singleton (AfterBreak s)
|
|
|
|
|
2010-12-12 20:09:14 -08:00
|
|
|
-- | Returns the width of a 'Doc'.
|
|
|
|
offset :: Doc -> Int
|
2012-01-25 23:30:21 -08:00
|
|
|
offset d = case map realLength . lines . render Nothing $ d of
|
2017-03-04 13:03:41 +01:00
|
|
|
[] -> 0
|
|
|
|
os -> maximum os
|
2010-12-12 20:09:14 -08:00
|
|
|
|
2015-02-03 14:30:46 +01:00
|
|
|
-- | Returns the minimal width of a 'Doc' when reflowed at breakable spaces.
|
|
|
|
minOffset :: Doc -> Int
|
|
|
|
minOffset d = maximum (0: map realLength (lines $ render (Just 0) d))
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
-- | @lblock n d@ is a block of width @n@ characters, with
|
|
|
|
-- text derived from @d@ and aligned to the left.
|
|
|
|
lblock :: Int -> Doc -> Doc
|
|
|
|
lblock = block id
|
|
|
|
|
|
|
|
-- | Like 'lblock' but aligned to the right.
|
|
|
|
rblock :: Int -> Doc -> Doc
|
2012-01-25 23:30:21 -08:00
|
|
|
rblock w = block (\s -> replicate (w - realLength s) ' ' ++ s) w
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
-- | Like 'lblock' but aligned centered.
|
|
|
|
cblock :: Int -> Doc -> Doc
|
2012-01-25 23:30:21 -08:00
|
|
|
cblock w = block (\s -> replicate ((w - realLength s) `div` 2) ' ' ++ s) w
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
|
|
-- | Returns the height of a block or other 'Doc'.
|
|
|
|
height :: Doc -> Int
|
|
|
|
height = length . lines . render Nothing
|
|
|
|
|
2015-02-03 14:30:28 +01:00
|
|
|
block :: (String -> String) -> Int -> Doc -> Doc
|
|
|
|
block filler width d
|
2017-03-03 15:01:23 +01:00
|
|
|
| width < 1 && not (isEmpty d) = block filler 1 d
|
2015-02-03 14:30:28 +01:00
|
|
|
| otherwise = Doc $ singleton $ Block width $ map filler
|
|
|
|
$ chop width $ render (Just width) d
|
|
|
|
|
2010-12-12 20:09:14 -08:00
|
|
|
chop :: Int -> String -> [String]
|
|
|
|
chop _ [] = []
|
|
|
|
chop n cs = case break (=='\n') cs of
|
|
|
|
(xs, ys) -> if len <= n
|
|
|
|
then case ys of
|
|
|
|
[] -> [xs]
|
2016-11-23 15:18:03 +01:00
|
|
|
['\n'] -> [xs]
|
2010-12-12 20:09:14 -08:00
|
|
|
(_:zs) -> xs : chop n zs
|
|
|
|
else take n xs : chop n (drop n xs ++ ys)
|
2012-01-25 23:30:21 -08:00
|
|
|
where len = realLength xs
|
2010-12-12 20:09:14 -08:00
|
|
|
|
2010-12-19 12:39:49 -08:00
|
|
|
-- | Encloses a 'Doc' inside a start and end 'Doc'.
|
2010-12-20 19:09:01 -08:00
|
|
|
inside :: Doc -> Doc -> Doc -> Doc
|
|
|
|
inside start end contents =
|
2010-12-19 12:39:49 -08:00
|
|
|
start <> contents <> end
|
|
|
|
|
2010-12-19 10:13:11 -08:00
|
|
|
-- | Puts a 'Doc' in curly braces.
|
|
|
|
braces :: Doc -> Doc
|
2010-12-20 19:09:01 -08:00
|
|
|
braces = inside (char '{') (char '}')
|
2010-12-19 10:13:11 -08:00
|
|
|
|
|
|
|
-- | Puts a 'Doc' in square brackets.
|
|
|
|
brackets :: Doc -> Doc
|
2010-12-20 19:09:01 -08:00
|
|
|
brackets = inside (char '[') (char ']')
|
2010-12-19 12:39:49 -08:00
|
|
|
|
|
|
|
-- | Puts a 'Doc' in parentheses.
|
|
|
|
parens :: Doc -> Doc
|
2010-12-20 19:09:01 -08:00
|
|
|
parens = inside (char '(') (char ')')
|
2010-12-22 00:22:28 -08:00
|
|
|
|
|
|
|
-- | Wraps a 'Doc' in single quotes.
|
|
|
|
quotes :: Doc -> Doc
|
|
|
|
quotes = inside (char '\'') (char '\'')
|
|
|
|
|
|
|
|
-- | Wraps a 'Doc' in double quotes.
|
|
|
|
doubleQuotes :: Doc -> Doc
|
|
|
|
doubleQuotes = inside (char '"') (char '"')
|
2011-11-18 13:10:45 -08:00
|
|
|
|
2012-01-25 23:15:18 -08:00
|
|
|
-- | Returns width of a character in a monospace font: 0 for a combining
|
|
|
|
-- character, 1 for a regular character, 2 for an East Asian wide character.
|
|
|
|
charWidth :: Char -> Int
|
|
|
|
charWidth c =
|
|
|
|
case c of
|
2012-01-27 13:30:15 -08:00
|
|
|
_ | c < '\x0300' -> 1
|
|
|
|
| c >= '\x0300' && c <= '\x036F' -> 0 -- combining
|
|
|
|
| c >= '\x0370' && c <= '\x10FC' -> 1
|
|
|
|
| c >= '\x1100' && c <= '\x115F' -> 2
|
|
|
|
| c >= '\x1160' && c <= '\x11A2' -> 1
|
|
|
|
| c >= '\x11A3' && c <= '\x11A7' -> 2
|
|
|
|
| c >= '\x11A8' && c <= '\x11F9' -> 1
|
|
|
|
| c >= '\x11FA' && c <= '\x11FF' -> 2
|
|
|
|
| c >= '\x1200' && c <= '\x2328' -> 1
|
2012-01-25 23:15:18 -08:00
|
|
|
| c >= '\x2329' && c <= '\x232A' -> 2
|
2012-01-27 13:30:15 -08:00
|
|
|
| c >= '\x232B' && c <= '\x2E31' -> 1
|
|
|
|
| c >= '\x2E80' && c <= '\x303E' -> 2
|
|
|
|
| c == '\x303F' -> 1
|
|
|
|
| c >= '\x3041' && c <= '\x3247' -> 2
|
|
|
|
| c >= '\x3248' && c <= '\x324F' -> 1 -- ambiguous
|
|
|
|
| c >= '\x3250' && c <= '\x4DBF' -> 2
|
|
|
|
| c >= '\x4DC0' && c <= '\x4DFF' -> 1
|
|
|
|
| c >= '\x4E00' && c <= '\xA4C6' -> 2
|
|
|
|
| c >= '\xA4D0' && c <= '\xA95F' -> 1
|
|
|
|
| c >= '\xA960' && c <= '\xA97C' -> 2
|
|
|
|
| c >= '\xA980' && c <= '\xABF9' -> 1
|
|
|
|
| c >= '\xAC00' && c <= '\xD7FB' -> 2
|
|
|
|
| c >= '\xD800' && c <= '\xDFFF' -> 1
|
|
|
|
| c >= '\xE000' && c <= '\xF8FF' -> 1 -- ambiguous
|
|
|
|
| c >= '\xF900' && c <= '\xFAFF' -> 2
|
|
|
|
| c >= '\xFB00' && c <= '\xFDFD' -> 1
|
|
|
|
| c >= '\xFE00' && c <= '\xFE0F' -> 1 -- ambiguous
|
|
|
|
| c >= '\xFE10' && c <= '\xFE19' -> 2
|
|
|
|
| c >= '\xFE20' && c <= '\xFE26' -> 1
|
|
|
|
| c >= '\xFE30' && c <= '\xFE6B' -> 2
|
2012-06-30 11:51:52 -07:00
|
|
|
| c >= '\xFE70' && c <= '\xFEFF' -> 1
|
|
|
|
| c >= '\xFF01' && c <= '\xFF60' -> 2
|
|
|
|
| c >= '\xFF61' && c <= '\x16A38' -> 1
|
2012-01-27 13:30:15 -08:00
|
|
|
| c >= '\x1B000' && c <= '\x1B001' -> 2
|
|
|
|
| c >= '\x1D000' && c <= '\x1F1FF' -> 1
|
|
|
|
| c >= '\x1F200' && c <= '\x1F251' -> 2
|
|
|
|
| c >= '\x1F300' && c <= '\x1F773' -> 1
|
|
|
|
| c >= '\x20000' && c <= '\x3FFFD' -> 2
|
2012-01-25 23:15:18 -08:00
|
|
|
| otherwise -> 1
|
2012-01-25 23:30:21 -08:00
|
|
|
|
|
|
|
-- | Get real length of string, taking into account combining and double-wide
|
|
|
|
-- characters.
|
|
|
|
realLength :: String -> Int
|
2017-02-23 09:54:31 +01:00
|
|
|
realLength = sum . map charWidth
|