{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes       #-}
{-# LANGUAGE StrictData        #-}
{-# LANGUAGE TypeApplications  #-}

{-|
Module      : Headroom.PostProcess.UpdateCopyright
Description : /Post-processor/ for updating years in copyrights
Copyright   : (c) 2019-2021 Vaclav Svejcar
License     : BSD-3-Clause
Maintainer  : vaclav.svejcar@gmail.com
Stability   : experimental
Portability : POSIX

This module provides functionality for updating years in copyright statements
in already rendered /license headers/.
-}

module Headroom.PostProcess.UpdateCopyright
  ( -- * Data Types
    SelectedAuthors(..)
  , UpdateCopyrightMode(..)
    -- * Header Functions
  , updateCopyright
    -- * Helper Functions
  , updateYears
  )
where

import           Headroom.Data.Has                   ( Has(..) )
import           Headroom.Data.Regex                 ( re
                                                     , replace
                                                     )
import           Headroom.Data.Text                  ( mapLines
                                                     , read
                                                     )
import           Headroom.PostProcess.Types          ( PostProcess(..) )
import           Headroom.Types                      ( CurrentYear(..) )
import           RIO
import qualified RIO.NonEmpty                       as NE
import qualified RIO.Text                           as T


---------------------------------  DATA TYPES  ---------------------------------


-- | Non-empty list of authors for which to update years in their copyrights.
newtype SelectedAuthors = SelectedAuthors (NonEmpty Text) deriving (SelectedAuthors -> SelectedAuthors -> Bool
(SelectedAuthors -> SelectedAuthors -> Bool)
-> (SelectedAuthors -> SelectedAuthors -> Bool)
-> Eq SelectedAuthors
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectedAuthors -> SelectedAuthors -> Bool
$c/= :: SelectedAuthors -> SelectedAuthors -> Bool
== :: SelectedAuthors -> SelectedAuthors -> Bool
$c== :: SelectedAuthors -> SelectedAuthors -> Bool
Eq, Int -> SelectedAuthors -> ShowS
[SelectedAuthors] -> ShowS
SelectedAuthors -> String
(Int -> SelectedAuthors -> ShowS)
-> (SelectedAuthors -> String)
-> ([SelectedAuthors] -> ShowS)
-> Show SelectedAuthors
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectedAuthors] -> ShowS
$cshowList :: [SelectedAuthors] -> ShowS
show :: SelectedAuthors -> String
$cshow :: SelectedAuthors -> String
showsPrec :: Int -> SelectedAuthors -> ShowS
$cshowsPrec :: Int -> SelectedAuthors -> ShowS
Show)


-- | Mode that changes behaviour of the 'updateCopyright' function.
data UpdateCopyrightMode
  = UpdateAllAuthors                      -- ^ updates years in copyrights for all authors
  | UpdateSelectedAuthors SelectedAuthors -- ^ updates years in copyrights only for selected authors
  deriving (UpdateCopyrightMode -> UpdateCopyrightMode -> Bool
(UpdateCopyrightMode -> UpdateCopyrightMode -> Bool)
-> (UpdateCopyrightMode -> UpdateCopyrightMode -> Bool)
-> Eq UpdateCopyrightMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCopyrightMode -> UpdateCopyrightMode -> Bool
$c/= :: UpdateCopyrightMode -> UpdateCopyrightMode -> Bool
== :: UpdateCopyrightMode -> UpdateCopyrightMode -> Bool
$c== :: UpdateCopyrightMode -> UpdateCopyrightMode -> Bool
Eq, Int -> UpdateCopyrightMode -> ShowS
[UpdateCopyrightMode] -> ShowS
UpdateCopyrightMode -> String
(Int -> UpdateCopyrightMode -> ShowS)
-> (UpdateCopyrightMode -> String)
-> ([UpdateCopyrightMode] -> ShowS)
-> Show UpdateCopyrightMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCopyrightMode] -> ShowS
$cshowList :: [UpdateCopyrightMode] -> ShowS
show :: UpdateCopyrightMode -> String
$cshow :: UpdateCopyrightMode -> String
showsPrec :: Int -> UpdateCopyrightMode -> ShowS
$cshowsPrec :: Int -> UpdateCopyrightMode -> ShowS
Show)


------------------------------  PUBLIC FUNCTIONS  ------------------------------


-- | /Post-processor/ that updates years and year ranges in any
-- present copyright statements.
--
-- = Reader Environment Parameters
--   ['CurrentYear'] value of the current year
--   ['UpdateCopyrightMode'] mode specifying the behaviour of the updater
updateCopyright :: (Has CurrentYear env, Has UpdateCopyrightMode env)
                => PostProcess env
updateCopyright :: PostProcess env
updateCopyright = (Text -> Reader env Text) -> PostProcess env
forall env. (Text -> Reader env Text) -> PostProcess env
PostProcess ((Text -> Reader env Text) -> PostProcess env)
-> (Text -> Reader env Text) -> PostProcess env
forall a b. (a -> b) -> a -> b
$ \Text
input -> do
  CurrentYear
currentYear <- ReaderT env Identity CurrentYear
forall a t (m :: * -> *). (Has a t, MonadReader t m) => m a
viewL
  UpdateCopyrightMode
mode        <- ReaderT env Identity UpdateCopyrightMode
forall a t (m :: * -> *). (Has a t, MonadReader t m) => m a
viewL
  Text -> Reader env Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Reader env Text) -> Text -> Reader env Text
forall a b. (a -> b) -> a -> b
$ (Text -> Text) -> Text -> Text
mapLines (UpdateCopyrightMode -> CurrentYear -> Text -> Text
update UpdateCopyrightMode
mode CurrentYear
currentYear) Text
input
 where
  update :: UpdateCopyrightMode -> CurrentYear -> Text -> Text
update UpdateCopyrightMode
mode CurrentYear
year Text
line | UpdateCopyrightMode -> Text -> Bool
shouldUpdate UpdateCopyrightMode
mode Text
line = CurrentYear -> Text -> Text
updateYears CurrentYear
year Text
line
                        | Bool
otherwise              = Text
line
  shouldUpdate :: UpdateCopyrightMode -> Text -> Bool
shouldUpdate UpdateCopyrightMode
UpdateAllAuthors Text
_ = Bool
True
  shouldUpdate (UpdateSelectedAuthors (SelectedAuthors NonEmpty Text
authors)) Text
input =
    (Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Text -> Text -> Bool
`T.isInfixOf` Text
input) (NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty Text
authors)


-- | Updates years and years ranges in given text.
--
-- >>> updateYears (CurrentYear 2020) "Copyright (c) 2020"
-- "Copyright (c) 2020"
--
-- >>> updateYears (CurrentYear 2020) "Copyright (c) 2019"
-- "Copyright (c) 2019-2020"
--
-- >>> updateYears (CurrentYear 2020) "Copyright (c) 2018-2020"
-- "Copyright (c) 2018-2020"
--
-- >>> updateYears (CurrentYear 2020) "Copyright (c) 2018-2019"
-- "Copyright (c) 2018-2020"
updateYears :: CurrentYear -- ^ current year
            -> Text        -- ^ text to update
            -> Text        -- ^ text with updated years
updateYears :: CurrentYear -> Text -> Text
updateYears (CurrentYear Integer
year) = Text -> Text
processYear (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
processRange
 where
  processYear :: Text -> Text
processYear  = Regex -> (Text -> [Text] -> Text) -> Text -> Text
replace [re|(?!\d{4}-)(?<!-)(\d{4})|] Text -> [Text] -> Text
processYear'
  processRange :: Text -> Text
processRange = Regex -> (Text -> [Text] -> Text) -> Text -> Text
replace [re|(\d{4})-(\d{4})|] Text -> [Text] -> Text
processRange'
  replaceYear :: Text -> Text
replaceYear Text
curr | Text -> Maybe Integer
forall a. Read a => Text -> Maybe a
read Text
curr Maybe Integer -> Maybe Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
year = Integer -> Text
forall a. Show a => a -> Text
tshow Integer
year
                   | Bool
otherwise              = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
curr, Text
"-", Integer -> Text
forall a. Show a => a -> Text
tshow Integer
year]
  replaceRange :: Text -> Text -> Text -> Text
replaceRange Text
full Text
fY Text
tY | Text -> Maybe Integer
forall a. Read a => Text -> Maybe a
read Text
tY Maybe Integer -> Maybe Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
year = Text
full
                          | Bool
otherwise            = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
fY, Text
"-", Integer -> Text
forall a. Show a => a -> Text
tshow Integer
year]
  processYear' :: Text -> [Text] -> Text
processYear' Text
_    (Text
curr : [Text]
_) = Text -> Text
replaceYear Text
curr
  processYear' Text
full [Text]
_          = Text
full
  processRange' :: Text -> [Text] -> Text
processRange' Text
full (Text
fromY : Text
toY : [Text]
_) = Text -> Text -> Text -> Text
replaceRange Text
full Text
fromY Text
toY
  processRange' Text
full [Text]
_                 = Text
full