{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Headroom.FileSupport
(
extractFileInfo
, addHeader
, dropHeader
, replaceHeader
, findHeader
, findBlockHeader
, findLineHeader
, firstMatching
, lastMatching
, splitInput
)
where
import Headroom.Regex ( compile'
, joinPatterns
, match'
)
import Headroom.Types ( FileInfo(..)
, FileType(..)
, HeaderConfig(..)
, HeaderSyntax(..)
)
import RIO
import qualified RIO.HashMap as HM
import qualified RIO.List as L
import qualified RIO.Text as T
import Text.Regex.PCRE.Light ( Regex )
extractFileInfo :: FileType
-> HeaderConfig
-> Text
-> FileInfo
extractFileInfo fiFileType fiHeaderConfig input =
let fiHeaderPos = findHeader fiHeaderConfig input
fiVariables = extractVariables fiFileType fiHeaderConfig input
in FileInfo { .. }
addHeader :: FileInfo
-> Text
-> Text
-> Text
addHeader FileInfo {..} _ text | isJust fiHeaderPos = text
addHeader FileInfo {..} header text = result
where
(before, middle, after) = splitInput hcPutAfter hcPutBefore text
HeaderConfig {..} = fiHeaderConfig
before' = stripLinesEnd before
middle' = stripLinesStart middle
margin [] _ = []
margin _ size = replicate size ""
marginBefore = margin before' hcMarginBefore
marginAfter = margin (middle' <> after) hcMarginAfter
result = T.unlines $ concat joined
joined = [before', marginBefore, [header], marginAfter, middle', after]
dropHeader :: FileInfo
-> Text
-> Text
dropHeader (FileInfo _ _ Nothing _) text = text
dropHeader (FileInfo _ _ (Just (start, end)) _) text = result
where
before = take start inputLines
after = drop (end + 1) inputLines
inputLines = T.lines text
result = T.unlines (stripLinesEnd before ++ stripLinesStart after)
replaceHeader :: FileInfo
-> Text
-> Text
-> Text
replaceHeader fileInfo header = addHeader' . dropHeader'
where
addHeader' = addHeader infoWithoutPos header
dropHeader' = dropHeader fileInfo
infoWithoutPos = set fiHeaderPosL Nothing fileInfo
findHeader :: HeaderConfig
-> Text
-> Maybe (Int, Int)
findHeader HeaderConfig {..} input = case hcHeaderSyntax of
BlockComment start end -> findBlockHeader start end inLines splitAt
LineComment prefix -> findLineHeader prefix inLines splitAt
where
(before, headerArea, _) = splitInput hcPutAfter hcPutBefore input
splitAt = L.length before
inLines = T.strip <$> headerArea
findBlockHeader :: Text
-> Text
-> [Text]
-> Int
-> Maybe (Int, Int)
findBlockHeader startsWith endsWith = go Nothing Nothing
where
isStart = T.isPrefixOf startsWith
isEnd = T.isSuffixOf endsWith
go _ _ (x : _) i | isStart x && isEnd x = Just (i, i)
go _ _ (x : xs) i | isStart x = go (Just i) Nothing xs (i + 1)
go (Just start) _ (x : _) i | isEnd x = Just (start, i)
go start end (_ : xs) i = go start end xs (i + 1)
go _ _ [] _ = Nothing
findLineHeader :: Text
-> [Text]
-> Int
-> Maybe (Int, Int)
findLineHeader prefix = go Nothing
where
isPrefix = T.isPrefixOf prefix
go Nothing (x : xs) i | isPrefix x = go (Just i) xs (i + 1)
go Nothing (_ : xs) i = go Nothing xs (i + 1)
go (Just start) (x : xs) i | isPrefix x = go (Just start) xs (i + 1)
go (Just start) _ i = Just (start, i - 1)
go _ [] _ = Nothing
firstMatching :: Regex
-> [Text]
-> Maybe Int
firstMatching regex input = go input 0
where
cond x = isJust $ match' regex x
go (x : _) i | cond x = Just i
go (_ : xs) i = go xs (i + 1)
go [] _ = Nothing
lastMatching :: Regex
-> [Text]
-> Maybe Int
lastMatching regex input = go input 0 Nothing
where
cond x = isJust $ match' regex x
go (x : xs) i _ | cond x = go xs (i + 1) (Just i)
go (_ : xs) i pos = go xs (i + 1) pos
go [] _ pos = pos
splitInput :: [Text] -> [Text] -> Text -> ([Text], [Text], [Text])
splitInput [] [] input = ([], T.lines input, [])
splitInput fstSplit sndSplit input = (before, middle, after)
where
(middle', after ) = L.splitAt sndSplitAt inLines
(before , middle) = L.splitAt fstSplitAt middle'
fstSplitAt = maybe 0 (+ 1) (findSplit lastMatching fstSplit middle')
sndSplitAt = fromMaybe len (findSplit firstMatching sndSplit inLines)
inLines = T.lines input
len = L.length inLines
findSplit f ps i = joinPatterns ps >>= (`f` i) . compile'
extractVariables :: FileType -> HeaderConfig -> Text -> HashMap Text Text
extractVariables _ _ _ = HM.empty
stripLinesEnd :: [Text] -> [Text]
stripLinesEnd = takeWhile (not . T.null . T.strip)
stripLinesStart :: [Text] -> [Text]
stripLinesStart = dropWhile (T.null . T.strip)
fiHeaderPosL :: Lens' FileInfo (Maybe (Int, Int))
fiHeaderPosL = lens fiHeaderPos (\x y -> x { fiHeaderPos = y })