{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Utils.Display
( indent,
)
where
import qualified Data.Text as Text
import PyF (fmt)
indent :: Int -> Text.Text -> Text.Text
indent :: Int -> Text -> Text
indent Int
nbSpaces Text
text = Text
indentedText
where
(Text
firstLine : [Text]
nextLines) = Text -> Text -> [Text]
Text.splitOn Text
"\n" Text
text
prefixedLines :: [Text]
prefixedLines = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (\Text
a -> [fmt|| {a}|]) [Text]
nextLines
indentedLines :: [Text]
indentedLines = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (\Text
a -> [fmt|{replicate nbSpaces ' '}{a}|]) (Text
firstLine Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
prefixedLines)
indentedText :: Text
indentedText = Text -> [Text] -> Text
Text.intercalate Text
"\n" [Text]
indentedLines