module Data.Text.Indent (Options (..), defaultOptions, guessOptions, fixIndentation) where
import Data.Char (isSpace)
import Data.Function (on)
import Data.List (groupBy, sortBy)
import qualified Data.Map.Strict as Map
import Data.Maybe (listToMaybe, mapMaybe)
import qualified Data.Set as Set
import qualified Data.Text as Text
data Options = Options
{ optionCharacter :: !Char
, optionMultiplier :: !Int
}
deriving (Show, Eq)
defaultOptions :: Options
defaultOptions = Options ' ' 2
possibleMultipliers :: Set.Set Int
possibleMultipliers = Set.fromList [1 .. 8]
guessOptions :: [Text.Text] -> Maybe Options
guessOptions =
(>>= toOptions)
. fmap (fmap keep66th)
. listToMaybe
. sortBy (on (flip compare) (maximum . snd))
. map gatherGrouped
. groupBy (on (==) fst)
. sortBy (on compare fst)
. filter (isSpace . fst)
. mapMaybe guessLineIndentation
where
gatherGrouped cs =
( fst (head cs)
, foldr (Map.unionWith (+) . snd) (Map.fromSet (const 0) possibleMultipliers) cs
)
moreThan66th x y = y >= div (x * 2) 3
keep66th vs = Map.filter (moreThan66th (maximum vs)) vs
pickMultiplier (m, _ ) [] = m
pickMultiplier l@(m, times) (r@(m', times') : ms)
| m' > m && moreThan66th times times' = pickMultiplier r ms
| m' < m && moreThan66th times' times = pickMultiplier l ms
| times' > times = pickMultiplier r ms
| otherwise = pickMultiplier l ms
toOptions (char, multipliers)
| Map.null multipliers = Nothing
| m <- Map.findMax multipliers = Just Options
{ optionCharacter = char
, optionMultiplier = pickMultiplier m (Map.toList (Map.delete (fst m) multipliers))
}
guessLineIndentation :: Text.Text -> Maybe (Char, Map.Map Int Int)
guessLineIndentation line
| Text.null line || Text.all isSpace line = Nothing
| otherwise = Just (initChar, lineMultipliers)
where
initChar = Text.head line
prefixLength = Text.length (Text.takeWhile (initChar ==) line)
lineMultipliers =
Map.fromSet (\multiplier -> 1 - signum (mod prefixLength multiplier)) possibleMultipliers
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
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 {blockPrefixLength = linePrefixLength line, blockLevel = newLevel} : blocks
, Text.append (mkPrefix newLevel) (lineBody line)
)
| linePrefixLength line < prevPrefixLength ->
fix (dropWhile (\block -> linePrefixLength line < blockPrefixLength block) blocks) line
| otherwise ->
( blocks
, Text.append (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
[] -> []