module Data.String.Interpolate.Util (unindent) where
import           Control.Arrow ((>>>))
import           Data.Char
unindent :: String -> String
unindent =
      lines_
  >>> removeLeadingEmptyLine
  >>> trimLastLine
  >>> removeIndentation
  >>> concat
  where
    isEmptyLine :: String -> Bool
    isEmptyLine = all isSpace
    lines_ :: String -> [String]
    lines_ [] = []
    lines_ s = case span (/= '\n') s of
      (first, '\n' : rest) -> (first ++ "\n") : lines_ rest
      (first, rest) -> first : lines_ rest
    removeLeadingEmptyLine :: [String] -> [String]
    removeLeadingEmptyLine xs = case xs of
      y:ys | isEmptyLine y -> ys
      _ -> xs
    trimLastLine :: [String] -> [String]
    trimLastLine (a : b : r) = a : trimLastLine (b : r)
    trimLastLine [a] = if all (== ' ') a
      then []
      else [a]
    trimLastLine [] = []
    removeIndentation :: [String] -> [String]
    removeIndentation ys = map (dropSpaces indentation) ys
      where
        dropSpaces 0 s = s
        dropSpaces n (' ' : r) = dropSpaces (n - 1) r
        dropSpaces _ s = s
        indentation = minimalIndentation ys
        minimalIndentation =
            safeMinimum 0
          . map (length . takeWhile (== ' '))
          . removeEmptyLines
        removeEmptyLines = filter (not . isEmptyLine)
        safeMinimum :: Ord a => a -> [a] -> a
        safeMinimum x xs = case xs of
          [] -> x
          _ -> minimum xs