module Data.Text.Indent (Options (..), defaultOptions, fixIndentation) where
import Data.Char (isSpace)
import Data.Semigroup ((<>))
import qualified Data.Text as Text
data Line = Line
{ linePrefixLength :: !Int
, lineBody :: !Text.Text
}
toLine :: Char -> Text.Text -> Line
toLine character line = Line
{ linePrefixLength = Text.length prefix
, lineBody = body
}
where
(prefix, body) = Text.span (== character) line
data Block = Block
{ blockPrefixLength :: !Int
, blockLevel :: !Int
}
findBlock :: [Block] -> Block
findBlock [] = Block 0 0
findBlock (block : _) = block
data Options = Options
{ optionCharacter :: !Char
, optionMultiplier :: !Int
}
deriving (Show, Eq)
defaultOptions :: Options
defaultOptions = Options ' ' 2
fixIndentation :: Options -> [Text.Text] -> [Text.Text]
fixIndentation (Options character multiplier) =
run [] . map (toLine character)
where
mkPrefix level = Text.replicate (level * multiplier) (Text.singleton character)
isEmptyLine = Text.all isSpace . lineBody
fix blocks line =
case findBlock blocks of
Block prevPrefixLength prevLevel
| linePrefixLength line > prevPrefixLength
, newLevel <- prevLevel + 1 ->
( Block (linePrefixLength line) newLevel : blocks
, mkPrefix newLevel <> lineBody line
)
| linePrefixLength line < prevPrefixLength
, blocks' <- dropWhile (\block -> blockPrefixLength block > linePrefixLength line) blocks
, block <- findBlock blocks' ->
( blocks'
, mkPrefix (blockLevel block) <> lineBody line
)
| otherwise ->
( blocks
, mkPrefix prevLevel <> lineBody line
)
run blocks lines =
case lines of
line : lines
| isEmptyLine line -> Text.empty : run blocks lines
| (blocks', line') <- fix blocks line -> line' : run blocks' lines
[] -> []