-- | String formatting helpers, starting to get a bit out of control.

module Hledger.Utils.String (
 takeEnd,
 -- * misc
 lowercase,
 uppercase,
 underline,
 stripbrackets,
 unbracket,
 -- quoting
 quoteIfNeeded,
 singleQuoteIfNeeded,
 -- quotechars,
 -- whitespacechars,
 words',
 unwords',
 stripAnsi,
 -- * single-line layout
 strip,
 lstrip,
 rstrip,
 chomp,
 chomp1,
 singleline,
 elideLeft,
 elideRight,
 formatString,
 -- * multi-line layout
 concatTopPadded,
 concatBottomPadded,
 concatOneLine,
 vConcatLeftAligned,
 vConcatRightAligned,
 padtop,
 padbottom,
 padleft,
 padright,
 cliptopleft,
 fitto,
 -- * wide-character-aware layout
 charWidth,
 strWidth,
 strWidthAnsi,
 takeWidth,
 fitString,
 fitStringMulti,
 padLeftWide,
 padRightWide
 ) where


import Data.Char (isSpace, toLower, toUpper)
import Data.Default (def)
import Data.List (intercalate)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Text.Megaparsec ((<|>), between, many, noneOf, sepBy)
import Text.Megaparsec.Char (char)
import Text.Printf (printf)

import Hledger.Utils.Parse
import Hledger.Utils.Regex (toRegex', regexReplace)
import Text.Tabular (Header(..), Properties(..))
import Text.Tabular.AsciiWide (Align(..), TableOpts(..), textCell, renderRow)
import Text.WideString (charWidth, strWidth)


-- | Take elements from the end of a list.
takeEnd :: Int -> [a] -> [a]
takeEnd Int
n [a]
l = [a] -> [a] -> [a]
forall a a. [a] -> [a] -> [a]
go (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
n [a]
l) [a]
l
  where
    go :: [a] -> [a] -> [a]
go (a
_:[a]
xs) (a
_:[a]
ys) = [a] -> [a] -> [a]
go [a]
xs [a]
ys
    go []     [a]
r      = [a]
r
    go [a]
_      []     = []

lowercase, uppercase :: String -> String
lowercase :: String -> String
lowercase = (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower
uppercase :: String -> String
uppercase = (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper

-- | Remove leading and trailing whitespace.
strip :: String -> String
strip :: String -> String
strip = String -> String
lstrip (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
rstrip

-- | Remove leading whitespace.
lstrip :: String -> String
lstrip :: String -> String
lstrip = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace

-- | Remove trailing whitespace.
rstrip :: String -> String
rstrip :: String -> String
rstrip = String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
lstrip (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse

-- | Remove all trailing newlines/carriage returns.
chomp :: String -> String
chomp :: String -> String
chomp = String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
"\r\n") (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse

-- | Remove all trailing newline/carriage returns, leaving just one trailing newline.
chomp1 :: String -> String
chomp1 :: String -> String
chomp1 = (String -> String -> String
forall a. [a] -> [a] -> [a]
++String
"\n") (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
chomp

-- | Remove consecutive line breaks, replacing them with single space
singleline :: String -> String
singleline :: String -> String
singleline = [String] -> String
unwords ([String] -> String) -> (String -> [String]) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/=String
"") ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
strip) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines

stripbrackets :: String -> String
stripbrackets :: String -> String
stripbrackets = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
"([") (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
"])") (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse :: String -> String

elideLeft :: Int -> String -> String
elideLeft :: Int -> String -> String
elideLeft Int
width String
s =
    if String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
width then String
".." String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
forall a. Int -> [a] -> [a]
takeEnd (Int
width Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) String
s else String
s

elideRight :: Int -> String -> String
elideRight :: Int -> String -> String
elideRight Int
width String
s =
    if String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
width then Int -> String -> String
forall a. Int -> [a] -> [a]
take (Int
width Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".." else String
s

-- | 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 :: Bool -> Maybe Int -> Maybe Int -> String -> String
formatString Bool
leftJustified Maybe Int
minwidth Maybe Int
maxwidth String
s = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> String
forall r. PrintfType r => String -> r
printf String
fmt) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
s
    where
      justify :: String
justify = if Bool
leftJustified then String
"-" else String
""
      minwidth' :: String
minwidth' = String -> (Int -> String) -> Maybe Int -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" Int -> String
forall a. Show a => a -> String
show Maybe Int
minwidth
      maxwidth' :: String
maxwidth' = String -> (Int -> String) -> Maybe Int -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" ((String
"."String -> String -> String
forall a. [a] -> [a] -> [a]
++)(String -> String) -> (Int -> String) -> Int -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Int -> String
forall a. Show a => a -> String
show) Maybe Int
maxwidth
      fmt :: String
fmt = String
"%" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
justify String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
minwidth' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
maxwidth' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"s"

underline :: String -> String
underline :: String -> String
underline String
s = String
s' String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> Char -> String
forall a. Int -> a -> [a]
replicate (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s) Char
'-' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
    where s' :: String
s'
            | String -> Char
forall a. [a] -> a
last String
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n' = String
s
            | Bool
otherwise = String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"

-- | Double-quote this string if it contains whitespace, single quotes
-- or double-quotes, escaping the quotes as needed.
quoteIfNeeded :: String -> String
quoteIfNeeded :: String -> String
quoteIfNeeded String
s | (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
s) (String
quotecharsString -> String -> String
forall a. [a] -> [a] -> [a]
++String
whitespacecharsString -> String -> String
forall a. [a] -> [a] -> [a]
++String
redirectchars) = Char -> String -> String
showChar Char
'"' (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> String -> String
escapeQuotes String
s String
"\""
                | Bool
otherwise = String
s
  where
    escapeQuotes :: String -> String -> String
escapeQuotes []       String
x = String
x
    escapeQuotes (Char
'"':String
cs) String
x = String -> String -> String
showString String
"\\\"" (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> String -> String
escapeQuotes String
cs String
x
    escapeQuotes (Char
c:String
cs)   String
x = Char -> String -> String
showChar Char
c        (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> String -> String
escapeQuotes String
cs String
x

-- | Single-quote this string if it contains whitespace or double-quotes.
-- No good for strings containing single quotes.
singleQuoteIfNeeded :: String -> String
singleQuoteIfNeeded :: String -> String
singleQuoteIfNeeded String
s | (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
s) (String
quotecharsString -> String -> String
forall a. [a] -> [a] -> [a]
++String
whitespacechars) = String
"'"String -> String -> String
forall a. [a] -> [a] -> [a]
++String
sString -> String -> String
forall a. [a] -> [a] -> [a]
++String
"'"
                      | Bool
otherwise = String
s

quotechars, whitespacechars, redirectchars :: [Char]
quotechars :: String
quotechars      = String
"'\""
whitespacechars :: String
whitespacechars = String
" \t\n\r"
redirectchars :: String
redirectchars   = String
"<>"

-- | 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' :: String -> [String]
words' String
"" = []
words' String
s  = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
stripquotes ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ Either (ParseErrorBundle String CustomErr) [String] -> [String]
forall t e a.
(Show t, Show (Token t), Show e) =>
Either (ParseErrorBundle t e) a -> a
fromparse (Either (ParseErrorBundle String CustomErr) [String] -> [String])
-> Either (ParseErrorBundle String CustomErr) [String] -> [String]
forall a b. (a -> b) -> a -> b
$ Parsec CustomErr String [String]
-> String -> Either (ParseErrorBundle String CustomErr) [String]
forall e a.
Parsec e String a -> String -> Either (ParseErrorBundle String e) a
parsewithString Parsec CustomErr String [String]
p String
s
    where
      p :: Parsec CustomErr String [String]
p = do [String]
ss <- (ParsecT CustomErr String Identity String
singleQuotedPattern ParsecT CustomErr String Identity String
-> ParsecT CustomErr String Identity String
-> ParsecT CustomErr String Identity String
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT CustomErr String Identity String
doubleQuotedPattern ParsecT CustomErr String Identity String
-> ParsecT CustomErr String Identity String
-> ParsecT CustomErr String Identity String
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT CustomErr String Identity String
pattern) ParsecT CustomErr String Identity String
-> ParsecT CustomErr String Identity ()
-> Parsec CustomErr String [String]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
`sepBy` ParsecT CustomErr String Identity ()
forall s (m :: * -> *).
(Stream s, Token s ~ Char) =>
ParsecT CustomErr s m ()
skipNonNewlineSpaces1
             -- eof
             [String] -> Parsec CustomErr String [String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
ss
      pattern :: ParsecT CustomErr String Identity String
pattern = ParsecT CustomErr String Identity Char
-> ParsecT CustomErr String Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many ([Token String] -> ParsecT CustomErr String Identity (Token String)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
noneOf String
[Token String]
whitespacechars)
      singleQuotedPattern :: ParsecT CustomErr String Identity String
singleQuotedPattern = ParsecT CustomErr String Identity Char
-> ParsecT CustomErr String Identity Char
-> ParsecT CustomErr String Identity String
-> ParsecT CustomErr String Identity String
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Token String -> ParsecT CustomErr String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'\'') (Token String -> ParsecT CustomErr String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'\'') (ParsecT CustomErr String Identity Char
-> ParsecT CustomErr String Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (ParsecT CustomErr String Identity Char
 -> ParsecT CustomErr String Identity String)
-> ParsecT CustomErr String Identity Char
-> ParsecT CustomErr String Identity String
forall a b. (a -> b) -> a -> b
$ [Token String] -> ParsecT CustomErr String Identity (Token String)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
noneOf String
[Token String]
"'")
      doubleQuotedPattern :: ParsecT CustomErr String Identity String
doubleQuotedPattern = ParsecT CustomErr String Identity Char
-> ParsecT CustomErr String Identity Char
-> ParsecT CustomErr String Identity String
-> ParsecT CustomErr String Identity String
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Token String -> ParsecT CustomErr String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'"') (Token String -> ParsecT CustomErr String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'"') (ParsecT CustomErr String Identity Char
-> ParsecT CustomErr String Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (ParsecT CustomErr String Identity Char
 -> ParsecT CustomErr String Identity String)
-> ParsecT CustomErr String Identity Char
-> ParsecT CustomErr String Identity String
forall a b. (a -> b) -> a -> b
$ [Token String] -> ParsecT CustomErr String Identity (Token String)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
noneOf String
[Token String]
"\"")

-- | Quote-aware version of unwords - single-quote strings which contain whitespace
unwords' :: [String] -> String
unwords' :: [String] -> String
unwords' = [String] -> String
unwords ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quoteIfNeeded

-- | Strip one matching pair of single or double quotes on the ends of a string.
stripquotes :: String -> String
stripquotes :: String -> String
stripquotes String
s = if String -> Bool
isSingleQuoted String
s Bool -> Bool -> Bool
|| String -> Bool
isDoubleQuoted String
s then String -> String
forall a. [a] -> [a]
init (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> String
forall a. [a] -> [a]
tail String
s else String
s

isSingleQuoted :: String -> Bool
isSingleQuoted s :: String
s@(Char
_:Char
_:String
_) = String -> Char
forall a. [a] -> a
head String
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\'' Bool -> Bool -> Bool
&& String -> Char
forall a. [a] -> a
last String
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\''
isSingleQuoted String
_ = Bool
False

isDoubleQuoted :: String -> Bool
isDoubleQuoted s :: String
s@(Char
_:Char
_:String
_) = String -> Char
forall a. [a] -> a
head String
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'"' Bool -> Bool -> Bool
&& String -> Char
forall a. [a] -> a
last String
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'"'
isDoubleQuoted String
_ = Bool
False

unbracket :: String -> String
unbracket :: String -> String
unbracket String
s
    | (String -> Char
forall a. [a] -> a
head String
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'[' Bool -> Bool -> Bool
&& String -> Char
forall a. [a] -> a
last String
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
']') Bool -> Bool -> Bool
|| (String -> Char
forall a. [a] -> a
head String
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'(' Bool -> Bool -> Bool
&& String -> Char
forall a. [a] -> a
last String
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
')') = String -> String
forall a. [a] -> [a]
init (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> String
forall a. [a] -> [a]
tail String
s
    | Bool
otherwise = String
s

-- | Join several multi-line strings as side-by-side rectangular strings of the same height, top-padded.
-- Treats wide characters as double width.
concatTopPadded :: [String] -> String
concatTopPadded :: [String] -> String
concatTopPadded = Text -> String
TL.unpack (Text -> String) -> ([String] -> Text) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableOpts -> Header Cell -> Text
renderRow TableOpts
forall a. Default a => a
def{tableBorders :: Bool
tableBorders=Bool
False, borderSpaces :: Bool
borderSpaces=Bool
False}
                (Header Cell -> Text)
-> ([String] -> Header Cell) -> [String] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Properties -> [Header Cell] -> Header Cell
forall h. Properties -> [Header h] -> Header h
Group Properties
NoLine ([Header Cell] -> Header Cell)
-> ([String] -> [Header Cell]) -> [String] -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Header Cell) -> [String] -> [Header Cell]
forall a b. (a -> b) -> [a] -> [b]
map (Cell -> Header Cell
forall h. h -> Header h
Header (Cell -> Header Cell) -> (String -> Cell) -> String -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Align -> Text -> Cell
textCell Align
BottomLeft (Text -> Cell) -> (String -> Text) -> String -> Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack)

-- | Join several multi-line strings as side-by-side rectangular strings of the same height, bottom-padded.
-- Treats wide characters as double width.
concatBottomPadded :: [String] -> String
concatBottomPadded :: [String] -> String
concatBottomPadded = Text -> String
TL.unpack (Text -> String) -> ([String] -> Text) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableOpts -> Header Cell -> Text
renderRow TableOpts
forall a. Default a => a
def{tableBorders :: Bool
tableBorders=Bool
False, borderSpaces :: Bool
borderSpaces=Bool
False}
                   (Header Cell -> Text)
-> ([String] -> Header Cell) -> [String] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Properties -> [Header Cell] -> Header Cell
forall h. Properties -> [Header h] -> Header h
Group Properties
NoLine ([Header Cell] -> Header Cell)
-> ([String] -> [Header Cell]) -> [String] -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Header Cell) -> [String] -> [Header Cell]
forall a b. (a -> b) -> [a] -> [b]
map (Cell -> Header Cell
forall h. h -> Header h
Header (Cell -> Header Cell) -> (String -> Cell) -> String -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Align -> Text -> Cell
textCell Align
TopLeft (Text -> Cell) -> (String -> Text) -> String -> Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack)

-- | 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 :: [String] -> String
concatOneLine [String]
strs = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", ")([String] -> String) -> (String -> [String]) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.String -> [String]
lines) [String]
strs

-- | Join strings vertically, left-aligned and right-padded.
vConcatLeftAligned :: [String] -> String
vConcatLeftAligned :: [String] -> String
vConcatLeftAligned [String]
ss = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
showfixedwidth [String]
ss
    where
      showfixedwidth :: String -> String
showfixedwidth = String -> String -> String
forall r. PrintfType r => String -> r
printf (String -> Int -> String
forall r. PrintfType r => String -> r
printf String
"%%-%ds" Int
width)
      width :: Int
width = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Int) -> [String] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
ss

-- | Join strings vertically, right-aligned and left-padded.
vConcatRightAligned :: [String] -> String
vConcatRightAligned :: [String] -> String
vConcatRightAligned [String]
ss = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
showfixedwidth [String]
ss
    where
      showfixedwidth :: String -> String
showfixedwidth = String -> String -> String
forall r. PrintfType r => String -> r
printf (String -> Int -> String
forall r. PrintfType r => String -> r
printf String
"%%%ds" Int
width)
      width :: Int
width = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Int) -> [String] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
ss

-- | Convert a multi-line string to a rectangular string top-padded to the specified height.
padtop :: Int -> String -> String
padtop :: Int -> String -> String
padtop Int
h String
s = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String]
xpadded
    where
      ls :: [String]
ls = String -> [String]
lines String
s
      sh :: Int
sh = [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
ls
      sw :: Int
sw | [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
ls = Int
0
         | Bool
otherwise = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Int) -> [String] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
ls
      ypadded :: [String]
ypadded = Int -> String -> [String]
forall a. Int -> a -> [a]
replicate (Int -> Int -> Int
forall a. (Num a, Ord a) => a -> a -> a
difforzero Int
h Int
sh) String
"" [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
ls
      xpadded :: [String]
xpadded = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> String -> String
padleft Int
sw) [String]
ypadded

-- | Convert a multi-line string to a rectangular string bottom-padded to the specified height.
padbottom :: Int -> String -> String
padbottom :: Int -> String -> String
padbottom Int
h String
s = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String]
xpadded
    where
      ls :: [String]
ls = String -> [String]
lines String
s
      sh :: Int
sh = [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
ls
      sw :: Int
sw | [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
ls = Int
0
         | Bool
otherwise = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Int) -> [String] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
ls
      ypadded :: [String]
ypadded = [String]
ls [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ Int -> String -> [String]
forall a. Int -> a -> [a]
replicate (Int -> Int -> Int
forall a. (Num a, Ord a) => a -> a -> a
difforzero Int
h Int
sh) String
""
      xpadded :: [String]
xpadded = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> String -> String
padleft Int
sw) [String]
ypadded

difforzero :: (Num a, Ord a) => a -> a -> a
difforzero :: a -> a -> a
difforzero a
a a
b = [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [(a
a a -> a -> a
forall a. Num a => a -> a -> a
- a
b), a
0]

-- | Convert a multi-line string to a rectangular string left-padded to the specified width.
-- Treats wide characters as double width.
padleft :: Int -> String -> String
padleft :: Int -> String -> String
padleft Int
w String
"" = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ Int -> String -> [String]
forall a. Int -> a -> [a]
replicate Int
w String
" "
padleft Int
w String
s = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> String
forall r. PrintfType r => String -> r
printf (String -> Int -> String
forall r. PrintfType r => String -> r
printf String
"%%%ds" Int
w)) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
s

-- | Convert a multi-line string to a rectangular string right-padded to the specified width.
-- Treats wide characters as double width.
padright :: Int -> String -> String
padright :: Int -> String -> String
padright Int
w String
"" = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ Int -> String -> [String]
forall a. Int -> a -> [a]
replicate Int
w String
" "
padright Int
w String
s = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> String
forall r. PrintfType r => String -> r
printf (String -> Int -> String
forall r. PrintfType r => String -> r
printf String
"%%-%ds" Int
w)) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
s

-- | Clip a multi-line string to the specified width and height from the top left.
cliptopleft :: Int -> Int -> String -> String
cliptopleft :: Int -> Int -> String -> String
cliptopleft Int
w Int
h = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> (String -> [String]) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
h ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
w) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines

-- | Clip and pad a multi-line string to fill the specified width and height.
fitto :: Int -> Int -> String -> String
fitto :: Int -> Int -> String -> String
fitto Int
w Int
h String
s = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
h ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
rows [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> [String]
forall a. a -> [a]
repeat String
blankline
    where
      rows :: [String]
rows = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> String -> String
fit Int
w) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
s
      fit :: Int -> String -> String
fit Int
w = Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
w (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char -> String
forall a. a -> [a]
repeat Char
' ')
      blankline :: String
blankline = Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
w Char
' '

-- Functions below treat wide (eg CJK) characters as double-width.

-- | General-purpose wide-char-aware single-line string layout function.
-- It can left- or right-pad a short string to a minimum width.
-- 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.
-- It treats wide characters as double width.
fitString :: Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String
fitString :: Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String
fitString Maybe Int
mminwidth Maybe Int
mmaxwidth Bool
ellipsify Bool
rightside String
s = (String -> String
clip (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
pad) String
s
  where
    clip :: String -> String
    clip :: String -> String
clip String
s =
      case Maybe Int
mmaxwidth of
        Just Int
w
          | String -> Int
strWidth String
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
w ->
            case Bool
rightside of
              Bool
True  -> Int -> String -> String
takeWidth (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
ellipsis) String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ellipsis
              Bool
False -> String
ellipsis String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. [a] -> [a]
reverse (Int -> String -> String
takeWidth (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
ellipsis) (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> String
forall a. [a] -> [a]
reverse String
s)
          | Bool
otherwise -> String
s
          where
            ellipsis :: String
ellipsis = if Bool
ellipsify then String
".." else String
""
        Maybe Int
Nothing -> String
s
    pad :: String -> String
    pad :: String -> String
pad String
s =
      case Maybe Int
mminwidth of
        Just Int
w
          | Int
sw Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
w ->
            case Bool
rightside of
              Bool
True  -> String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sw) Char
' '
              Bool
False -> Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sw) Char
' ' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
          | Bool
otherwise -> String
s
        Maybe Int
Nothing -> String
s
      where sw :: Int
sw = String -> Int
strWidth String
s

-- | 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 :: Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String
fitStringMulti Maybe Int
mminwidth Maybe Int
mmaxwidth Bool
ellipsify Bool
rightside String
s =
  (String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> (String -> [String]) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String
fitString Maybe Int
mminwidth Maybe Int
mmaxwidth Bool
ellipsify Bool
rightside) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines) String
s

-- | Left-pad a string to the specified width.
-- Treats wide characters as double width.
-- Works on multi-line strings too (but will rewrite non-unix line endings).
padLeftWide :: Int -> String -> String
padLeftWide :: Int -> String -> String
padLeftWide Int
w String
"" = Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
w Char
' '
padLeftWide Int
w String
s  = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String
fitString (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
w) Maybe Int
forall a. Maybe a
Nothing Bool
False Bool
False) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
s
-- XXX not yet replaceable by
-- padLeftWide w = fitStringMulti (Just w) Nothing False False

-- | Right-pad a string to the specified width.
-- Treats wide characters as double width.
-- Works on multi-line strings too (but will rewrite non-unix line endings).
padRightWide :: Int -> String -> String
padRightWide :: Int -> String -> String
padRightWide Int
w String
"" = Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
w Char
' '
padRightWide Int
w String
s  = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String
fitString (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
w) Maybe Int
forall a. Maybe a
Nothing Bool
False Bool
True) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
s
-- XXX not yet replaceable by
-- padRightWide w = fitStringMulti (Just w) Nothing False True

-- | 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 :: Int -> String -> String
takeWidth Int
_ String
""     = String
""
takeWidth Int
0 String
_      = String
""
takeWidth Int
w (Char
c:String
cs) | Int
cw Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
w   = Char
cChar -> String -> String
forall a. a -> [a] -> [a]
:Int -> String -> String
takeWidth (Int
wInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
cw) String
cs
                   | Bool
otherwise = String
""
  where cw :: Int
cw = Char -> Int
charWidth Char
c

-- | Like strWidth, but also strips ANSI escape sequences before
-- calculating the width.
--
-- This is no longer used in code, as widths are calculated before
-- adding ANSI escape sequences, but is being kept around for now.
strWidthAnsi :: String -> Int
strWidthAnsi :: String -> Int
strWidthAnsi = String -> Int
strWidth (String -> Int) -> (String -> String) -> String -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
stripAnsi

-- | Strip ANSI escape sequences from a string.
--
-- >>> stripAnsi "\ESC[31m-1\ESC[m"
-- "-1"
stripAnsi :: String -> String
stripAnsi :: String -> String
stripAnsi String
s = (String -> String)
-> (String -> String) -> Either String String -> String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> String
forall a. a
err String -> String
forall a. a -> a
id (Either String String -> String) -> Either String String -> String
forall a b. (a -> b) -> a -> b
$ Regexp -> String -> String -> Either String String
regexReplace Regexp
ansire String
"" String
s
 where
   err :: a
err    = String -> a
forall a. HasCallStack => String -> a
error String
"stripAnsi: invalid replacement pattern"      -- PARTIAL, shouldn't happen
   ansire :: Regexp
ansire = Text -> Regexp
toRegex' (Text -> Regexp) -> Text -> Regexp
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
"\ESC\\[([0-9]+;)*([0-9]+)?[ABCDHJKfmsu]"  -- PARTIAL, should succeed