2015-04-29 00:06:22 +03:00
|
|
|
-- | String formatting helpers, starting to get a bit out of control.
|
|
|
|
|
2015-08-19 23:47:26 +03:00
|
|
|
module Hledger.Utils.String (
|
2020-07-16 13:28:48 +03:00
|
|
|
takeEnd,
|
2015-08-19 23:47:26 +03:00
|
|
|
-- * misc
|
|
|
|
lowercase,
|
|
|
|
uppercase,
|
|
|
|
underline,
|
|
|
|
stripbrackets,
|
|
|
|
unbracket,
|
|
|
|
-- quoting
|
|
|
|
quoteIfNeeded,
|
|
|
|
singleQuoteIfNeeded,
|
|
|
|
-- quotechars,
|
|
|
|
-- whitespacechars,
|
|
|
|
escapeQuotes,
|
|
|
|
words',
|
|
|
|
unwords',
|
2017-04-26 04:27:25 +03:00
|
|
|
stripAnsi,
|
2015-08-19 23:47:26 +03:00
|
|
|
-- * single-line layout
|
|
|
|
strip,
|
|
|
|
lstrip,
|
|
|
|
rstrip,
|
|
|
|
chomp,
|
2019-10-12 02:50:06 +03:00
|
|
|
singleline,
|
2015-08-19 23:47:26 +03:00
|
|
|
elideLeft,
|
|
|
|
elideRight,
|
2015-08-20 06:28:24 +03:00
|
|
|
formatString,
|
2015-08-19 23:47:26 +03:00
|
|
|
-- * multi-line layout
|
|
|
|
concatTopPadded,
|
|
|
|
concatBottomPadded,
|
2015-08-20 06:28:24 +03:00
|
|
|
concatOneLine,
|
|
|
|
vConcatLeftAligned,
|
2015-08-19 23:47:26 +03:00
|
|
|
vConcatRightAligned,
|
|
|
|
padtop,
|
|
|
|
padbottom,
|
|
|
|
padleft,
|
|
|
|
padright,
|
|
|
|
cliptopleft,
|
2015-09-29 07:33:18 +03:00
|
|
|
fitto,
|
|
|
|
-- * wide-character-aware layout
|
lib: textification begins! account names
The first of several conversions from String to (strict) Text, hopefully
reducing space and time usage.
This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1:
hledger -f data/100x100x10.journal stats
string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>>
text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>>
text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>>
text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>>
text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
|
|
|
charWidth,
|
2015-09-29 07:33:18 +03:00
|
|
|
strWidth,
|
|
|
|
takeWidth,
|
|
|
|
fitString,
|
|
|
|
fitStringMulti,
|
|
|
|
padLeftWide,
|
|
|
|
padRightWide
|
2015-08-19 23:47:26 +03:00
|
|
|
) where
|
|
|
|
|
|
|
|
|
|
|
|
import Data.Char
|
|
|
|
import Data.List
|
2018-05-22 01:47:56 +03:00
|
|
|
import Text.Megaparsec
|
|
|
|
import Text.Megaparsec.Char
|
2015-08-20 06:28:24 +03:00
|
|
|
import Text.Printf (printf)
|
2015-08-19 23:47:26 +03:00
|
|
|
|
|
|
|
import Hledger.Utils.Parse
|
|
|
|
import Hledger.Utils.Regex
|
|
|
|
|
2020-07-16 13:28:48 +03:00
|
|
|
|
|
|
|
-- | Take elements from the end of a list.
|
|
|
|
takeEnd n l = go (drop n l) l
|
|
|
|
where
|
|
|
|
go (_:xs) (_:ys) = go xs ys
|
|
|
|
go [] r = r
|
|
|
|
go _ [] = []
|
|
|
|
|
2015-08-19 23:47:26 +03:00
|
|
|
lowercase, uppercase :: String -> String
|
|
|
|
lowercase = map toLower
|
|
|
|
uppercase = map toUpper
|
|
|
|
|
|
|
|
-- | Remove leading and trailing whitespace.
|
|
|
|
strip :: String -> String
|
|
|
|
strip = lstrip . rstrip
|
|
|
|
|
|
|
|
-- | Remove leading whitespace.
|
|
|
|
lstrip :: String -> String
|
2016-12-20 20:29:12 +03:00
|
|
|
lstrip = dropWhile isSpace
|
2015-08-19 23:47:26 +03:00
|
|
|
|
|
|
|
-- | Remove trailing whitespace.
|
|
|
|
rstrip :: String -> String
|
|
|
|
rstrip = reverse . lstrip . reverse
|
|
|
|
|
|
|
|
-- | Remove trailing newlines/carriage returns.
|
|
|
|
chomp :: String -> String
|
|
|
|
chomp = reverse . dropWhile (`elem` "\r\n") . reverse
|
|
|
|
|
2020-01-05 04:37:55 +03:00
|
|
|
-- | Remove consecutive line breaks, replacing them with single space
|
2019-10-12 02:50:06 +03:00
|
|
|
singleline :: String -> String
|
2019-10-12 12:16:38 +03:00
|
|
|
singleline = unwords . filter (/="") . (map strip) . lines
|
2019-10-12 02:50:06 +03:00
|
|
|
|
2015-08-19 23:47:26 +03:00
|
|
|
stripbrackets :: String -> String
|
|
|
|
stripbrackets = dropWhile (`elem` "([") . reverse . dropWhile (`elem` "])") . reverse :: String -> String
|
|
|
|
|
|
|
|
elideLeft :: Int -> String -> String
|
|
|
|
elideLeft width s =
|
2020-07-16 13:28:48 +03:00
|
|
|
if length s > width then ".." ++ takeEnd (width - 2) s else s
|
2015-08-19 23:47:26 +03:00
|
|
|
|
|
|
|
elideRight :: Int -> String -> String
|
|
|
|
elideRight width s =
|
|
|
|
if length s > width then take (width - 2) s ++ ".." else s
|
|
|
|
|
2015-08-20 06:28:24 +03:00
|
|
|
-- | Clip and pad a string to a minimum & maximum width, and/or left/right justify it.
|
|
|
|
-- Works on multi-line strings too (but will rewrite non-unix line endings).
|
|
|
|
formatString :: Bool -> Maybe Int -> Maybe Int -> String -> String
|
|
|
|
formatString leftJustified minwidth maxwidth s = intercalate "\n" $ map (printf fmt) $ lines s
|
|
|
|
where
|
|
|
|
justify = if leftJustified then "-" else ""
|
|
|
|
minwidth' = maybe "" show minwidth
|
|
|
|
maxwidth' = maybe "" (("."++).show) maxwidth
|
|
|
|
fmt = "%" ++ justify ++ minwidth' ++ maxwidth' ++ "s"
|
|
|
|
|
2015-08-19 23:47:26 +03:00
|
|
|
underline :: String -> String
|
|
|
|
underline s = s' ++ replicate (length s) '-' ++ "\n"
|
|
|
|
where s'
|
|
|
|
| last s == '\n' = s
|
|
|
|
| otherwise = s ++ "\n"
|
|
|
|
|
|
|
|
-- | Double-quote this string if it contains whitespace, single quotes
|
|
|
|
-- or double-quotes, escaping the quotes as needed.
|
|
|
|
quoteIfNeeded :: String -> String
|
2019-11-30 16:34:59 +03:00
|
|
|
quoteIfNeeded s | any (`elem` s) (quotechars++whitespacechars++redirectchars) = "\"" ++ escapeDoubleQuotes s ++ "\""
|
2015-08-19 23:47:26 +03:00
|
|
|
| otherwise = s
|
|
|
|
-- | Single-quote this string if it contains whitespace or double-quotes.
|
|
|
|
-- No good for strings containing single quotes.
|
|
|
|
singleQuoteIfNeeded :: String -> String
|
|
|
|
singleQuoteIfNeeded s | any (`elem` s) whitespacechars = "'"++s++"'"
|
|
|
|
| otherwise = s
|
|
|
|
|
2019-11-30 16:34:59 +03:00
|
|
|
quotechars, whitespacechars, redirectchars :: [Char]
|
2015-08-19 23:47:26 +03:00
|
|
|
quotechars = "'\""
|
|
|
|
whitespacechars = " \t\n\r"
|
2019-11-30 16:34:59 +03:00
|
|
|
redirectchars = "<>"
|
2015-08-19 23:47:26 +03:00
|
|
|
|
|
|
|
escapeDoubleQuotes :: String -> String
|
|
|
|
escapeDoubleQuotes = regexReplace "\"" "\""
|
|
|
|
|
|
|
|
escapeQuotes :: String -> String
|
|
|
|
escapeQuotes = regexReplace "([\"'])" "\\1"
|
|
|
|
|
|
|
|
-- | Quote-aware version of words - don't split on spaces which are inside quotes.
|
|
|
|
-- NB correctly handles "a'b" but not "''a''". Can raise an error if parsing fails.
|
|
|
|
words' :: String -> [String]
|
|
|
|
words' "" = []
|
2016-07-29 18:57:10 +03:00
|
|
|
words' s = map stripquotes $ fromparse $ parsewithString p s
|
2015-08-19 23:47:26 +03:00
|
|
|
where
|
2018-03-25 16:53:44 +03:00
|
|
|
p = do ss <- (singleQuotedPattern <|> doubleQuotedPattern <|> pattern) `sepBy` skipSome spacenonewline
|
2015-08-19 23:47:26 +03:00
|
|
|
-- eof
|
|
|
|
return ss
|
|
|
|
pattern = many (noneOf whitespacechars)
|
|
|
|
singleQuotedPattern = between (char '\'') (char '\'') (many $ noneOf "'")
|
|
|
|
doubleQuotedPattern = between (char '"') (char '"') (many $ noneOf "\"")
|
|
|
|
|
|
|
|
-- | Quote-aware version of unwords - single-quote strings which contain whitespace
|
|
|
|
unwords' :: [String] -> String
|
|
|
|
unwords' = unwords . map quoteIfNeeded
|
|
|
|
|
|
|
|
-- | Strip one matching pair of single or double quotes on the ends of a string.
|
|
|
|
stripquotes :: String -> String
|
|
|
|
stripquotes s = if isSingleQuoted s || isDoubleQuoted s then init $ tail s else s
|
|
|
|
|
|
|
|
isSingleQuoted s@(_:_:_) = head s == '\'' && last s == '\''
|
|
|
|
isSingleQuoted _ = False
|
|
|
|
|
|
|
|
isDoubleQuoted s@(_:_:_) = head s == '"' && last s == '"'
|
|
|
|
isDoubleQuoted _ = False
|
|
|
|
|
|
|
|
unbracket :: String -> String
|
|
|
|
unbracket s
|
|
|
|
| (head s == '[' && last s == ']') || (head s == '(' && last s == ')') = init $ tail s
|
|
|
|
| otherwise = s
|
|
|
|
|
2015-09-29 07:33:18 +03:00
|
|
|
-- | Join several multi-line strings as side-by-side rectangular strings of the same height, top-padded.
|
|
|
|
-- Treats wide characters as double width.
|
2015-08-19 23:47:26 +03:00
|
|
|
concatTopPadded :: [String] -> String
|
|
|
|
concatTopPadded strs = intercalate "\n" $ map concat $ transpose padded
|
|
|
|
where
|
|
|
|
lss = map lines strs
|
|
|
|
h = maximum $ map length lss
|
|
|
|
ypad ls = replicate (difforzero h (length ls)) "" ++ ls
|
2015-09-29 07:33:18 +03:00
|
|
|
xpad ls = map (padLeftWide w) ls where w | null ls = 0
|
|
|
|
| otherwise = maximum $ map strWidth ls
|
2015-08-19 23:47:26 +03:00
|
|
|
padded = map (xpad . ypad) lss
|
|
|
|
|
2015-09-29 07:33:18 +03:00
|
|
|
-- | Join several multi-line strings as side-by-side rectangular strings of the same height, bottom-padded.
|
|
|
|
-- Treats wide characters as double width.
|
2015-08-19 23:47:26 +03:00
|
|
|
concatBottomPadded :: [String] -> String
|
|
|
|
concatBottomPadded strs = intercalate "\n" $ map concat $ transpose padded
|
|
|
|
where
|
|
|
|
lss = map lines strs
|
|
|
|
h = maximum $ map length lss
|
|
|
|
ypad ls = ls ++ replicate (difforzero h (length ls)) ""
|
2015-09-29 07:33:18 +03:00
|
|
|
xpad ls = map (padRightWide w) ls where w | null ls = 0
|
|
|
|
| otherwise = maximum $ map strWidth ls
|
2015-08-19 23:47:26 +03:00
|
|
|
padded = map (xpad . ypad) lss
|
|
|
|
|
2015-08-20 06:28:24 +03:00
|
|
|
|
|
|
|
-- | Join multi-line strings horizontally, after compressing each of
|
|
|
|
-- them to a single line with a comma and space between each original line.
|
|
|
|
concatOneLine :: [String] -> String
|
|
|
|
concatOneLine strs = concat $ map ((intercalate ", ").lines) strs
|
|
|
|
|
|
|
|
-- | Join strings vertically, left-aligned and right-padded.
|
|
|
|
vConcatLeftAligned :: [String] -> String
|
|
|
|
vConcatLeftAligned ss = intercalate "\n" $ map showfixedwidth ss
|
|
|
|
where
|
|
|
|
showfixedwidth = printf (printf "%%-%ds" width)
|
|
|
|
width = maximum $ map length ss
|
|
|
|
|
|
|
|
-- | Join strings vertically, right-aligned and left-padded.
|
2015-08-19 23:47:26 +03:00
|
|
|
vConcatRightAligned :: [String] -> String
|
|
|
|
vConcatRightAligned ss = intercalate "\n" $ map showfixedwidth ss
|
|
|
|
where
|
|
|
|
showfixedwidth = printf (printf "%%%ds" width)
|
|
|
|
width = maximum $ map length ss
|
|
|
|
|
|
|
|
-- | Convert a multi-line string to a rectangular string top-padded to the specified height.
|
|
|
|
padtop :: Int -> String -> String
|
|
|
|
padtop h s = intercalate "\n" xpadded
|
|
|
|
where
|
|
|
|
ls = lines s
|
|
|
|
sh = length ls
|
|
|
|
sw | null ls = 0
|
|
|
|
| otherwise = maximum $ map length ls
|
|
|
|
ypadded = replicate (difforzero h sh) "" ++ ls
|
|
|
|
xpadded = map (padleft sw) ypadded
|
|
|
|
|
|
|
|
-- | Convert a multi-line string to a rectangular string bottom-padded to the specified height.
|
|
|
|
padbottom :: Int -> String -> String
|
|
|
|
padbottom h s = intercalate "\n" xpadded
|
|
|
|
where
|
|
|
|
ls = lines s
|
|
|
|
sh = length ls
|
|
|
|
sw | null ls = 0
|
|
|
|
| otherwise = maximum $ map length ls
|
|
|
|
ypadded = ls ++ replicate (difforzero h sh) ""
|
|
|
|
xpadded = map (padleft sw) ypadded
|
|
|
|
|
|
|
|
difforzero :: (Num a, Ord a) => a -> a -> a
|
|
|
|
difforzero a b = maximum [(a - b), 0]
|
|
|
|
|
|
|
|
-- | Convert a multi-line string to a rectangular string left-padded to the specified width.
|
2015-09-29 07:33:18 +03:00
|
|
|
-- Treats wide characters as double width.
|
2015-08-19 23:47:26 +03:00
|
|
|
padleft :: Int -> String -> String
|
|
|
|
padleft w "" = concat $ replicate w " "
|
|
|
|
padleft w s = intercalate "\n" $ map (printf (printf "%%%ds" w)) $ lines s
|
|
|
|
|
|
|
|
-- | Convert a multi-line string to a rectangular string right-padded to the specified width.
|
2015-09-29 07:33:18 +03:00
|
|
|
-- Treats wide characters as double width.
|
2015-08-19 23:47:26 +03:00
|
|
|
padright :: Int -> String -> String
|
|
|
|
padright w "" = concat $ replicate w " "
|
|
|
|
padright w s = intercalate "\n" $ map (printf (printf "%%-%ds" w)) $ lines s
|
|
|
|
|
|
|
|
-- | Clip a multi-line string to the specified width and height from the top left.
|
|
|
|
cliptopleft :: Int -> Int -> String -> String
|
|
|
|
cliptopleft w h = intercalate "\n" . take h . map (take w) . lines
|
|
|
|
|
|
|
|
-- | Clip and pad a multi-line string to fill the specified width and height.
|
|
|
|
fitto :: Int -> Int -> String -> String
|
|
|
|
fitto w h s = intercalate "\n" $ take h $ rows ++ repeat blankline
|
|
|
|
where
|
|
|
|
rows = map (fit w) $ lines s
|
|
|
|
fit w = take w . (++ repeat ' ')
|
|
|
|
blankline = replicate w ' '
|
|
|
|
|
2015-09-29 07:33:18 +03:00
|
|
|
-- Functions below treat wide (eg CJK) characters as double-width.
|
|
|
|
|
2015-10-10 21:53:28 +03:00
|
|
|
-- | General-purpose wide-char-aware single-line string layout function.
|
2015-09-29 07:33:18 +03:00
|
|
|
-- It can left- or right-pad a short string to a minimum width.
|
2015-09-29 07:47:05 +03:00
|
|
|
-- It can left- or right-clip a long string to a maximum width, optionally inserting an ellipsis (the third argument).
|
|
|
|
-- It clips and pads on the right when the fourth argument is true, otherwise on the left.
|
2015-09-29 07:33:18 +03:00
|
|
|
-- It treats wide characters as double width.
|
|
|
|
fitString :: Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String
|
|
|
|
fitString mminwidth mmaxwidth ellipsify rightside s = (clip . pad) s
|
2015-04-29 00:06:22 +03:00
|
|
|
where
|
2015-09-29 07:33:18 +03:00
|
|
|
clip :: String -> String
|
|
|
|
clip s =
|
|
|
|
case mmaxwidth of
|
|
|
|
Just w
|
|
|
|
| strWidth s > w ->
|
|
|
|
case rightside of
|
|
|
|
True -> takeWidth (w - length ellipsis) s ++ ellipsis
|
|
|
|
False -> ellipsis ++ reverse (takeWidth (w - length ellipsis) $ reverse s)
|
|
|
|
| otherwise -> s
|
|
|
|
where
|
|
|
|
ellipsis = if ellipsify then ".." else ""
|
|
|
|
Nothing -> s
|
|
|
|
pad :: String -> String
|
|
|
|
pad s =
|
|
|
|
case mminwidth of
|
|
|
|
Just w
|
|
|
|
| sw < w ->
|
|
|
|
case rightside of
|
|
|
|
True -> s ++ replicate (w - sw) ' '
|
|
|
|
False -> replicate (w - sw) ' ' ++ s
|
|
|
|
| otherwise -> s
|
|
|
|
Nothing -> s
|
|
|
|
where sw = strWidth s
|
|
|
|
|
2015-09-29 07:47:05 +03:00
|
|
|
-- | A version of fitString that works on multi-line strings,
|
|
|
|
-- separate for now to avoid breakage.
|
|
|
|
-- This will rewrite any line endings to unix newlines.
|
|
|
|
fitStringMulti :: Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String
|
|
|
|
fitStringMulti mminwidth mmaxwidth ellipsify rightside s =
|
|
|
|
(intercalate "\n" . map (fitString mminwidth mmaxwidth ellipsify rightside) . lines) s
|
|
|
|
|
|
|
|
-- | Left-pad a string to the specified width.
|
2015-09-29 07:33:18 +03:00
|
|
|
-- Treats wide characters as double width.
|
|
|
|
-- Works on multi-line strings too (but will rewrite non-unix line endings).
|
|
|
|
padLeftWide :: Int -> String -> String
|
|
|
|
padLeftWide w "" = replicate w ' '
|
2015-09-29 07:47:05 +03:00
|
|
|
padLeftWide w s = intercalate "\n" $ map (fitString (Just w) Nothing False False) $ lines s
|
|
|
|
-- XXX not yet replaceable by
|
|
|
|
-- padLeftWide w = fitStringMulti (Just w) Nothing False False
|
2015-09-29 07:33:18 +03:00
|
|
|
|
2015-09-29 07:47:05 +03:00
|
|
|
-- | Right-pad a string to the specified width.
|
2015-09-29 07:33:18 +03:00
|
|
|
-- Treats wide characters as double width.
|
|
|
|
-- Works on multi-line strings too (but will rewrite non-unix line endings).
|
|
|
|
padRightWide :: Int -> String -> String
|
|
|
|
padRightWide w "" = replicate w ' '
|
2015-09-29 07:47:05 +03:00
|
|
|
padRightWide w s = intercalate "\n" $ map (fitString (Just w) Nothing False True) $ lines s
|
|
|
|
-- XXX not yet replaceable by
|
|
|
|
-- padRightWide w = fitStringMulti (Just w) Nothing False True
|
2015-04-29 00:06:22 +03:00
|
|
|
|
|
|
|
-- | Double-width-character-aware string truncation. Take as many
|
|
|
|
-- characters as possible from a string without exceeding the
|
|
|
|
-- specified width. Eg takeWidth 3 "りんご" = "り".
|
|
|
|
takeWidth :: Int -> String -> String
|
|
|
|
takeWidth _ "" = ""
|
|
|
|
takeWidth 0 _ = ""
|
|
|
|
takeWidth w (c:cs) | cw <= w = c:takeWidth (w-cw) cs
|
|
|
|
| otherwise = ""
|
|
|
|
where cw = charWidth c
|
|
|
|
|
|
|
|
-- from Pandoc (copyright John MacFarlane, GPL)
|
|
|
|
-- see also http://unicode.org/reports/tr11/#Description
|
|
|
|
|
2017-04-26 04:27:25 +03:00
|
|
|
-- | Calculate the render width of a string, considering
|
2019-07-15 13:28:52 +03:00
|
|
|
-- wide characters (counted as double width), ANSI escape codes
|
2017-04-26 04:27:25 +03:00
|
|
|
-- (not counted), and line breaks (in a multi-line string, the longest
|
2019-07-15 13:28:52 +03:00
|
|
|
-- line determines the width).
|
2015-04-29 00:06:22 +03:00
|
|
|
strWidth :: String -> Int
|
2015-10-11 01:08:28 +03:00
|
|
|
strWidth "" = 0
|
2017-04-26 04:27:25 +03:00
|
|
|
strWidth s = maximum $ map (foldr (\a b -> charWidth a + b) 0) $ lines s'
|
|
|
|
where s' = stripAnsi s
|
|
|
|
|
|
|
|
stripAnsi :: String -> String
|
|
|
|
stripAnsi = regexReplace "\ESC\\[([0-9]+;)*([0-9]+)?[ABCDHJKfmsu]" ""
|
2015-04-29 00:06:22 +03:00
|
|
|
|
2015-10-11 01:08:28 +03:00
|
|
|
-- | Get the designated render width of a character: 0 for a combining
|
|
|
|
-- character, 1 for a regular character, 2 for a wide character.
|
|
|
|
-- (Wide characters are rendered as exactly double width in apps and
|
2015-10-29 19:19:20 +03:00
|
|
|
-- fonts that support it.) (From Pandoc.)
|
2015-04-29 00:06:22 +03:00
|
|
|
charWidth :: Char -> Int
|
|
|
|
charWidth c =
|
|
|
|
case c of
|
|
|
|
_ | 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
|
|
|
|
| c >= '\x2329' && c <= '\x232A' -> 2
|
|
|
|
| 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
|
|
|
|
| c >= '\xFE70' && c <= '\xFEFF' -> 1
|
|
|
|
| c >= '\xFF01' && c <= '\xFF60' -> 2
|
|
|
|
| c >= '\xFF61' && c <= '\x16A38' -> 1
|
|
|
|
| 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
|
|
|
|
| otherwise -> 1
|
|
|
|
|