{-# LANGUAGE OverloadedStrings #-}
module Hledger.Utils.Text
(
textCapitalise,
textUnbracket,
wrap,
textChomp,
quoteIfSpaced,
textQuoteIfNeeded,
escapeDoubleQuotes,
escapeBackslash,
stripquotes,
textElideRight,
formatText,
textConcatTopPadded,
textConcatBottomPadded,
fitText,
linesPrepend,
linesPrepend2,
unlinesB,
WideBuilder(..),
wbToText,
wbFromText,
wbUnpack,
textTakeWidth,
readDecimal,
tests_Text
)
where
import Data.Char (digitToInt)
import Data.Default (def)
import Data.Maybe (catMaybes)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import Text.DocLayout (charWidth, realLength)
import Test.Tasty (testGroup)
import Test.Tasty.HUnit ((@?=), testCase)
import Text.Tabular.AsciiWide
(Align(..), Header(..), Properties(..), TableOpts(..), renderRow, textCell)
import Text.WideString (WideBuilder(..), wbToText, wbFromText, wbUnpack)
textCapitalise :: Text -> Text
textCapitalise :: Text -> Text
textCapitalise Text
t = Text -> Text
T.toTitle Text
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cs where (Text
c,Text
cs) = Int -> Text -> (Text, Text)
T.splitAt Int
1 Text
t
textElideRight :: Int -> Text -> Text
textElideRight :: Int -> Text -> Text
textElideRight Int
width Text
t =
if Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
width then Int -> Text -> Text
T.take (Int
width Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
".." else Text
t
wrap :: Text -> Text -> Text -> Text
wrap :: Text -> Text -> Text -> Text
wrap Text
start Text
end Text
x = Text
start Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
end
textChomp :: Text -> Text
textChomp :: Text -> Text
textChomp = (Char -> Bool) -> Text -> Text
T.dropWhileEnd (Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'\r', Char
'\n'])
formatText :: Bool -> Maybe Int -> Maybe Int -> Text -> Text
formatText :: Bool -> Maybe Int -> Maybe Int -> Text -> Text
formatText Bool
leftJustified Maybe Int
minwidth Maybe Int
maxwidth Text
t =
Text -> [Text] -> Text
T.intercalate Text
"\n" ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text
pad (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
clip) ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ if Text -> Bool
T.null Text
t then [Text
""] else Text -> [Text]
T.lines Text
t
where
pad :: Text -> Text
pad = (Text -> Text)
-> (Int -> Text -> Text) -> Maybe Int -> Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text -> Text
forall a. a -> a
id Int -> Text -> Text
justify Maybe Int
minwidth
clip :: Text -> Text
clip = (Text -> Text)
-> (Int -> Text -> Text) -> Maybe Int -> Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text -> Text
forall a. a -> a
id Int -> Text -> Text
T.take Maybe Int
maxwidth
justify :: Int -> Text -> Text
justify Int
n = if Bool
leftJustified then Int -> Char -> Text -> Text
T.justifyLeft Int
n Char
' ' else Int -> Char -> Text -> Text
T.justifyRight Int
n Char
' '
quoteIfSpaced :: T.Text -> T.Text
quoteIfSpaced :: Text -> Text
quoteIfSpaced Text
s | Text -> Bool
isSingleQuoted Text
s Bool -> Bool -> Bool
|| Text -> Bool
isDoubleQuoted Text
s = Text
s
| Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Char
c -> (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
c) Text
s) [Char]
whitespacechars = Text
s
| Bool
otherwise = Text -> Text
textQuoteIfNeeded Text
s
textQuoteIfNeeded :: T.Text -> T.Text
textQuoteIfNeeded :: Text -> Text
textQuoteIfNeeded Text
s | (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Char
c -> (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
c) Text
s) ([Char]
quotechars[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
whitespacechars) = Text
"\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escapeDoubleQuotes Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
| Bool
otherwise = Text
s
quotechars, whitespacechars :: [Char]
quotechars :: [Char]
quotechars = [Char]
"'\""
whitespacechars :: [Char]
whitespacechars = [Char]
" \t\n\r"
escapeDoubleQuotes :: T.Text -> T.Text
escapeDoubleQuotes :: Text -> Text
escapeDoubleQuotes = HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"\"" Text
"\\\""
escapeBackslash :: T.Text -> T.Text
escapeBackslash :: Text -> Text
escapeBackslash = HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"\\" Text
"\\\\"
stripquotes :: Text -> Text
stripquotes :: Text -> Text
stripquotes Text
s = if Text -> Bool
isSingleQuoted Text
s Bool -> Bool -> Bool
|| Text -> Bool
isDoubleQuoted Text
s then HasCallStack => Text -> Text
Text -> Text
T.init (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ HasCallStack => Text -> Text
Text -> Text
T.tail Text
s else Text
s
isSingleQuoted :: Text -> Bool
isSingleQuoted :: Text -> Bool
isSingleQuoted Text
s =
Text -> Int
T.length Text
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2 Bool -> Bool -> Bool
&& HasCallStack => Text -> Char
Text -> Char
T.head Text
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\'' Bool -> Bool -> Bool
&& HasCallStack => Text -> Char
Text -> Char
T.last Text
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\''
isDoubleQuoted :: Text -> Bool
isDoubleQuoted :: Text -> Bool
isDoubleQuoted Text
s =
Text -> Int
T.length Text
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2 Bool -> Bool -> Bool
&& HasCallStack => Text -> Char
Text -> Char
T.head Text
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'"' Bool -> Bool -> Bool
&& HasCallStack => Text -> Char
Text -> Char
T.last Text
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'"'
textUnbracket :: Text -> Text
textUnbracket :: Text -> Text
textUnbracket Text
s = Int -> Text -> Text
T.drop Int
stripN (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.dropEnd Int
stripN Text
s
where
matchBracket :: Char -> Maybe Char
matchBracket :: Char -> Maybe Char
matchBracket Char
'(' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
')'
matchBracket Char
'[' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
']'
matchBracket Char
_ = Maybe Char
forall a. Maybe a
Nothing
expectedClosingBrackets :: [Char]
expectedClosingBrackets = [Maybe Char] -> [Char]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Char] -> [Char]) -> [Maybe Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ (Maybe Char -> Bool) -> [Maybe Char] -> [Maybe Char]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Maybe Char -> Maybe Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Maybe Char
forall a. Maybe a
Nothing) ([Maybe Char] -> [Maybe Char]) -> [Maybe Char] -> [Maybe Char]
forall a b. (a -> b) -> a -> b
$ Char -> Maybe Char
matchBracket (Char -> Maybe Char) -> [Char] -> [Maybe Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> [Char]
T.unpack Text
s
stripN :: Int
stripN = [(Char, Char)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([(Char, Char)] -> Int) -> [(Char, Char)] -> Int
forall a b. (a -> b) -> a -> b
$ ((Char, Char) -> Bool) -> [(Char, Char)] -> [(Char, Char)]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile ((Char -> Char -> Bool) -> (Char, Char) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
(==)) ([(Char, Char)] -> [(Char, Char)])
-> [(Char, Char)] -> [(Char, Char)]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> [(Char, Char)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Char]
expectedClosingBrackets ([Char] -> [(Char, Char)]) -> [Char] -> [(Char, Char)]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
forall a. [a] -> [a]
reverse ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ Text -> [Char]
T.unpack Text
s
textConcatTopPadded :: [Text] -> Text
textConcatTopPadded :: [Text] -> Text
textConcatTopPadded = LazyText -> Text
TL.toStrict (LazyText -> Text) -> ([Text] -> LazyText) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableOpts -> Header Cell -> LazyText
renderRow TableOpts
forall a. Default a => a
def{tableBorders=False, borderSpaces=False}
(Header Cell -> LazyText)
-> ([Text] -> Header Cell) -> [Text] -> LazyText
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)
-> ([Text] -> [Header Cell]) -> [Text] -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Header Cell) -> [Text] -> [Header Cell]
forall a b. (a -> b) -> [a] -> [b]
map (Cell -> Header Cell
forall h. h -> Header h
Header (Cell -> Header Cell) -> (Text -> Cell) -> Text -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Align -> Text -> Cell
textCell Align
BottomLeft)
textConcatBottomPadded :: [Text] -> Text
textConcatBottomPadded :: [Text] -> Text
textConcatBottomPadded = LazyText -> Text
TL.toStrict (LazyText -> Text) -> ([Text] -> LazyText) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableOpts -> Header Cell -> LazyText
renderRow TableOpts
forall a. Default a => a
def{tableBorders=False, borderSpaces=False}
(Header Cell -> LazyText)
-> ([Text] -> Header Cell) -> [Text] -> LazyText
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)
-> ([Text] -> [Header Cell]) -> [Text] -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Header Cell) -> [Text] -> [Header Cell]
forall a b. (a -> b) -> [a] -> [b]
map (Cell -> Header Cell
forall h. h -> Header h
Header (Cell -> Header Cell) -> (Text -> Cell) -> Text -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Align -> Text -> Cell
textCell Align
TopLeft)
fitText :: Maybe Int -> Maybe Int -> Bool -> Bool -> Text -> Text
fitText :: Maybe Int -> Maybe Int -> Bool -> Bool -> Text -> Text
fitText Maybe Int
mminwidth Maybe Int
mmaxwidth Bool
ellipsify Bool
rightside = Text -> Text
clip (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
pad
where
clip :: Text -> Text
clip :: Text -> Text
clip Text
s =
case Maybe Int
mmaxwidth of
Just Int
w
| Text -> Int
forall a. HasChars a => a -> Int
realLength Text
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
w ->
if Bool
rightside
then Int -> Text -> Text
textTakeWidth (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
T.length Text
ellipsis) Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ellipsis
else Text
ellipsis Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
T.reverse (Int -> Text -> Text
textTakeWidth (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
T.length Text
ellipsis) (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.reverse Text
s)
| Bool
otherwise -> Text
s
where
ellipsis :: Text
ellipsis = if Bool
ellipsify then Text
".." else Text
""
Maybe Int
Nothing -> Text
s
pad :: Text -> Text
pad :: Text -> Text
pad Text
s =
case Maybe Int
mminwidth of
Just Int
w
| Int
sw Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
w ->
if Bool
rightside
then Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sw) Text
" "
else Int -> Text -> Text
T.replicate (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sw) Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s
| Bool
otherwise -> Text
s
Maybe Int
Nothing -> Text
s
where sw :: Int
sw = Text -> Int
forall a. HasChars a => a -> Int
realLength Text
s
textTakeWidth :: Int -> Text -> Text
textTakeWidth :: Int -> Text -> Text
textTakeWidth Int
_ Text
"" = Text
""
textTakeWidth Int
0 Text
_ = Text
""
textTakeWidth Int
w Text
t | Bool -> Bool
not (Text -> Bool
T.null Text
t),
let c :: Char
c = HasCallStack => Text -> Char
Text -> Char
T.head Text
t,
let cw :: Int
cw = Char -> Int
charWidth Char
c,
Int
cw Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
w
= Char -> Text -> Text
T.cons Char
c (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
textTakeWidth (Int
wInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
cw) (HasCallStack => Text -> Text
Text -> Text
T.tail Text
t)
| Bool
otherwise = Text
""
linesPrepend :: Text -> Text -> Text
linesPrepend :: Text -> Text -> Text
linesPrepend Text
prefix = [Text] -> Text
T.unlines ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text
prefixText -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines
linesPrepend2 :: Text -> Text -> Text -> Text
linesPrepend2 :: Text -> Text -> Text -> Text
linesPrepend2 Text
prefix1 Text
prefix2 Text
s = [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ case Text -> [Text]
T.lines Text
s of
[] -> []
Text
l:[Text]
ls -> (Text
prefix1Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
l) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text
prefix2Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) [Text]
ls
unlinesB :: [TB.Builder] -> TB.Builder
unlinesB :: [Builder] -> Builder
unlinesB = (Builder -> Builder) -> [Builder] -> Builder
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Char -> Builder
TB.singleton Char
'\n')
readDecimal :: Text -> Integer
readDecimal :: Text -> Integer
readDecimal = (Integer -> Char -> Integer) -> Integer -> Text -> Integer
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' Integer -> Char -> Integer
step Integer
0
where step :: Integer -> Char -> Integer
step Integer
a Char
c = Integer
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
10 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Char -> Int
digitToInt Char
c)
tests_Text :: TestTree
tests_Text = [Char] -> [TestTree] -> TestTree
testGroup [Char]
"Text" [
[Char] -> Assertion -> TestTree
testCase [Char]
"quoteIfSpaced" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Text -> Text
quoteIfSpaced Text
"a'a" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"a'a"
Text -> Text
quoteIfSpaced Text
"a\"a" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"a\"a"
Text -> Text
quoteIfSpaced Text
"a a" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"\"a a\""
Text -> Text
quoteIfSpaced Text
"mimi's cafe" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"\"mimi's cafe\""
Text -> Text
quoteIfSpaced Text
"\"alex\" cafe" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"\"\\\"alex\\\" cafe\""
Text -> Text
quoteIfSpaced Text
"le'shan's cafe" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"\"le'shan's cafe\""
Text -> Text
quoteIfSpaced Text
"\"be'any's\" cafe" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"\"\\\"be'any's\\\" cafe\"",
[Char] -> Assertion -> TestTree
testCase [Char]
"textUnbracket" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Text -> Text
textUnbracket Text
"()" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
""
Text -> Text
textUnbracket Text
"(a)" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"a"
Text -> Text
textUnbracket Text
"(ab)" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"ab"
Text -> Text
textUnbracket Text
"[ab]" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"ab"
Text -> Text
textUnbracket Text
"([ab])" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"ab"
Text -> Text
textUnbracket Text
"(()b)" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"()b"
Text -> Text
textUnbracket Text
"[[]b]" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"[]b"
Text -> Text
textUnbracket Text
"[()b]" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"()b"
Text -> Text
textUnbracket Text
"[([]())]" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"[]()"
Text -> Text
textUnbracket Text
"[([[[()]]])]" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
""
Text -> Text
textUnbracket Text
"[([[[(]]])]" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"("
Text -> Text
textUnbracket Text
"[([[[)]]])]" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
")"
]