{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeApplications #-}
module Headroom.HeaderFn.UpdateCopyright
(
SelectedAuthors(..)
, UpdateCopyrightMode(..)
, updateCopyright
, updateYears
)
where
import Headroom.Data.Has ( Has(..) )
import Headroom.Data.Regex ( re
, replace
)
import Headroom.Data.TextExtra ( mapLines
, read
)
import Headroom.HeaderFn.Types ( HeaderFn(..) )
import Headroom.Types ( CurrentYear(..) )
import RIO
import qualified RIO.NonEmpty as NE
import qualified RIO.Text as T
newtype SelectedAuthors = SelectedAuthors (NonEmpty Text) deriving (Eq, Show)
data UpdateCopyrightMode
= UpdateAllAuthors
| UpdateSelectedAuthors !SelectedAuthors
deriving (Eq, Show)
updateCopyright :: (Has CurrentYear env, Has UpdateCopyrightMode env)
=> HeaderFn env
updateCopyright = HeaderFn $ \input -> do
currentYear <- viewL
mode <- viewL
pure $ mapLines (update mode currentYear) input
where
update mode year line | shouldUpdate mode line = updateYears year line
| otherwise = line
shouldUpdate UpdateAllAuthors _ = True
shouldUpdate (UpdateSelectedAuthors (SelectedAuthors authors)) input =
any (`T.isInfixOf` input) (NE.toList authors)
updateYears :: CurrentYear
-> Text
-> Text
updateYears (CurrentYear year) = processYear . processRange
where
processYear = replace [re|(?!\d{4}-)(?<!-)(\d{4})|] processYear'
processRange = replace [re|(\d{4})-(\d{4})|] processRange'
replaceYear curr | read curr == Just year = tshow year
| otherwise = mconcat [curr, "-", tshow year]
replaceRange full fY tY | read tY == Just year = full
| otherwise = mconcat [fY, "-", tshow year]
processYear' _ (curr : _) = replaceYear curr
processYear' full _ = full
processRange' full (fromY : toY : _) = replaceRange full fromY toY
processRange' full _ = full