diff --git a/app/Main.hs b/app/Main.hs index 9e2c7b3..4dbee8b 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -51,5 +51,5 @@ bootstrap = \case cgoGenMode <- parseGenMode c commandGen CommandGenOptions { .. } Init cioLicenseType cioSourcePaths -> commandInit CommandInitOptions { .. } - Run croSourcePaths croExcludedPaths croTemplateSource croVariables croRunMode croDebug croDryRun + Run croSourcePaths croExcludedPaths croBuiltInTemplates croTemplateRefs croVariables croRunMode croDebug croDryRun -> commandRun CommandRunOptions { .. } diff --git a/src/Headroom/Command.hs b/src/Headroom/Command.hs index ee4c045..87b4621 100644 --- a/src/Headroom/Command.hs +++ b/src/Headroom/Command.hs @@ -23,11 +23,11 @@ where import Headroom.Command.Readers ( licenseReader , licenseTypeReader , regexReader + , templateRefReader ) import Headroom.Command.Types ( Command(..) ) import Headroom.Configuration.Types ( LicenseType , RunMode(..) - , TemplateSource(..) ) import Headroom.Data.EnumExtra ( EnumExtra(..) ) import Headroom.Meta ( buildVersion @@ -98,26 +98,23 @@ runOptions = ) ) <*> optional - ( BuiltInTemplates - <$> option - licenseTypeReader - (long "builtin-templates" <> metavar "TYPE" <> help - ("use built-in templates for license type, available options: " - <> T.unpack (T.toLower (allValuesToText @LicenseType)) - ) - ) - <|> TemplateFiles - <$> some - (strOption - (long "template-path" <> short 't' <> metavar "PATH" <> help - "path to license template file/directory" - ) - ) + (option + licenseTypeReader + (long "builtin-templates" <> metavar "licenseType" <> help + "use built-in templates of selected license type" + ) + ) + <*> many + (option + templateRefReader + (long "source-path" <> short 'e' <> metavar "REGEX" <> help + "path to exclude from source code file paths" + ) ) <*> many (strOption - (long "variable" <> short 'v' <> metavar "KEY=VALUE" <> help - "value for template variable" + (long "template-path" <> short 't' <> metavar "PATH" <> help + "path to template" ) ) <*> optional diff --git a/src/Headroom/Command/Run.hs b/src/Headroom/Command/Run.hs index be07ca4..0b17e51 100644 --- a/src/Headroom/Command/Run.hs +++ b/src/Headroom/Command/Run.hs @@ -28,7 +28,6 @@ responsible for license header management. module Headroom.Command.Run ( commandRun , loadBuiltInTemplates - , loadTemplateFiles , loadTemplateRefs , typeOfTemplate -- * License Header Post-processing @@ -57,7 +56,6 @@ import Headroom.Configuration.Types ( Configuration(..) , LicenseType(..) , PtConfiguration , RunMode(..) - , TemplateSource(..) ) import Headroom.Data.EnumExtra ( EnumExtra(..) ) import Headroom.Data.Has ( Has(..) ) @@ -204,7 +202,7 @@ commandRun opts = bootstrap (env' opts) (croDebug opts) $ do let isCheck = cRunMode == Check warnOnDryRun startTS <- liftIO getPOSIXTime - templates <- loadTemplates @TemplateType + templates <- loadTemplates sourceFiles <- findSourceFiles (M.keys templates) _ <- logInfo "-----" (total, processed) <- processSourceFiles @TemplateType templates sourceFiles @@ -384,38 +382,11 @@ loadTemplateRefs refs = do mapMaybe (L.headMaybe . L.sort) . L.groupBy (\x y -> fst x == fst y) $ rs --- | Loads templates from the given paths. -loadTemplateFiles :: forall a env - . ( Template a - , Has (FileSystem (RIO env)) env - , HasLogFunc env - ) - => [FilePath] - -- ^ paths to template files - -> RIO env (Map FileType TemplateType) - -- ^ map of file types and templates -loadTemplateFiles paths' = do - FileSystem {..} <- viewL - paths <- mconcat <$> mapM (`fsFindFilesByExts` extensions) paths' - logDebug $ "Using template paths: " <> displayShow paths - withTypes <- catMaybes <$> mapM (\p -> fmap (, p) <$> typeOfTemplate p) paths - parsed <- mapM - (\(t, p) -> - (t, ) <$> (fsLoadFile p >>= parseTemplate (Just $ T.pack p) . T.strip) - ) - withTypes - logInfo $ mconcat ["Found ", display $ length parsed, " license templates"] - pure $ M.fromList parsed - where extensions = toList $ templateExtensions @a - - -- | Loads built-in templates, stored in "Headroom.Embedded", for the given -- 'LicenseType'. loadBuiltInTemplates :: (HasLogFunc env) - => LicenseType - -- ^ license type for which to selected templates - -> RIO env (Map FileType TemplateType) - -- ^ map of file types and templates + => LicenseType -- ^ selected license type + -> RIO env (Map FileType TemplateType) -- ^ map of file types and templates loadBuiltInTemplates licenseType = do logInfo $ "Using built-in templates for license: " <> displayShow licenseType parsed <- mapM (\(t, r) -> (t, ) <$> parseTemplate Nothing r) rawTemplates @@ -425,27 +396,26 @@ loadBuiltInTemplates licenseType = do template = licenseTemplate licenseType -loadTemplates :: forall a env - . ( Template a - , Has CtConfiguration env +loadTemplates :: ( Has CtConfiguration env , Has (FileSystem (RIO env)) env + , Has (Network (RIO env)) env , HasLogFunc env ) => RIO env (Map FileType HeaderTemplate) loadTemplates = do Configuration {..} <- viewL @CtConfiguration - templates <- case cTemplateSource of - TemplateFiles paths -> loadTemplateFiles @a paths - BuiltInTemplates licenseType -> loadBuiltInTemplates licenseType - pure $ M.mapWithKey (extractHeaderTemplate cLicenseHeaders) templates + fromRefs <- loadTemplateRefs @TemplateType cTemplateRefs + builtIn <- case cBuiltInTemplates of + Just licenseType -> loadBuiltInTemplates licenseType + _ -> pure M.empty + pure $ M.mapWithKey (extractHeaderTemplate cLicenseHeaders) + (builtIn <> fromRefs) -- | Takes path to the template file and returns detected type of the template. typeOfTemplate :: HasLogFunc env - => FilePath - -- ^ path to the template file - -> RIO env (Maybe FileType) - -- ^ detected template type + => FilePath -- ^ path to the template file + -> RIO env (Maybe FileType) -- ^ detected template type typeOfTemplate path = do let fileType = textToEnum . T.pack . takeBaseName $ path when (isNothing fileType) @@ -495,13 +465,14 @@ optionsToConfiguration :: (Has CommandRunOptions env) => RIO env PtConfiguration optionsToConfiguration = do CommandRunOptions {..} <- viewL variables <- parseVariables croVariables - pure Configuration { cRunMode = maybe mempty pure croRunMode - , cSourcePaths = ifNot null croSourcePaths - , cExcludedPaths = ifNot null croExcludedPaths - , cTemplateSource = maybe mempty pure croTemplateSource - , cVariables = variables - , cLicenseHeaders = mempty - , cHeaderFnConfigs = mempty + pure Configuration { cRunMode = maybe mempty pure croRunMode + , cSourcePaths = ifNot null croSourcePaths + , cExcludedPaths = ifNot null croExcludedPaths + , cBuiltInTemplates = pure croBuiltInTemplates + , cTemplateRefs = croTemplateRefs + , cVariables = variables + , cLicenseHeaders = mempty + , cHeaderFnConfigs = mempty } where ifNot cond value = if cond value then mempty else pure value @@ -525,14 +496,10 @@ postProcessHeader' :: forall a env , Has CtHeaderFnConfigs env , Has CurrentYear env ) - => HeaderSyntax - -- ^ syntax of the license header comments - -> Variables - -- ^ template variables - -> Text - -- ^ rendered /license header/ to post-process - -> RIO env Text - -- ^ post-processed /license header/ + => HeaderSyntax -- ^ syntax of the license header comments + -> Variables -- ^ template variables + -> Text -- ^ /license header/ to post-process + -> RIO env Text -- ^ post-processed /license header/ postProcessHeader' syntax vars rawHeader = do configs <- viewL @CtHeaderFnConfigs year <- viewL diff --git a/src/Headroom/Command/Types.hs b/src/Headroom/Command/Types.hs index 4640afd..f54acb5 100644 --- a/src/Headroom/Command/Types.hs +++ b/src/Headroom/Command/Types.hs @@ -24,55 +24,43 @@ where import Headroom.Configuration.Types ( GenMode , LicenseType , RunMode - , TemplateSource ) import Headroom.Data.Regex ( Regex ) import Headroom.FileType.Types ( FileType ) +import Headroom.Template.TemplateRef ( TemplateRef ) import RIO -- | Application command. data Command - = Run [FilePath] [Regex] (Maybe TemplateSource) [Text] (Maybe RunMode) Bool Bool - -- ^ @run@ command - | Gen Bool (Maybe (LicenseType, FileType)) - -- ^ @gen@ command - | Init LicenseType [FilePath] - -- ^ @init@ command + = Run [FilePath] [Regex] (Maybe LicenseType) [TemplateRef] [Text] (Maybe RunMode) Bool Bool -- ^ @run@ command + | Gen Bool (Maybe (LicenseType, FileType)) -- ^ @gen@ command + | Init LicenseType [FilePath] -- ^ @init@ command deriving (Show) -- | Options for the @gen@ command. newtype CommandGenOptions = CommandGenOptions - { cgoGenMode :: GenMode - -- ^ selected mode + { cgoGenMode :: GenMode -- ^ selected mode } deriving (Show) -- | Options for the @init@ command. data CommandInitOptions = CommandInitOptions - { cioSourcePaths :: [FilePath] - -- ^ paths to source code files - , cioLicenseType :: LicenseType - -- ^ license type + { cioSourcePaths :: [FilePath] -- ^ paths to source code files + , cioLicenseType :: LicenseType -- ^ license type } deriving Show -- | Options for the @run@ command. data CommandRunOptions = CommandRunOptions - { croRunMode :: Maybe RunMode - -- ^ used /Run/ command mode - , croSourcePaths :: [FilePath] - -- ^ source code file paths - , croExcludedPaths :: [Regex] - -- ^ source paths to exclude - , croTemplateSource :: Maybe TemplateSource - -- ^ source of license templates - , croVariables :: [Text] - -- ^ raw variables - , croDebug :: Bool - -- ^ whether to run in debug mode - , croDryRun :: Bool - -- ^ whether to perform dry run + { croRunMode :: Maybe RunMode -- ^ used /Run/ command mode + , croSourcePaths :: [FilePath] -- ^ source code file paths + , croExcludedPaths :: [Regex] -- ^ source paths to exclude + , croBuiltInTemplates :: Maybe LicenseType -- ^ whether to use built-in templates + , croTemplateRefs :: [TemplateRef] -- ^ template references + , croVariables :: [Text] -- ^ raw variables + , croDebug :: Bool -- ^ whether to run in debug mode + , croDryRun :: Bool -- ^ whether to perform dry run } deriving (Eq, Show) diff --git a/src/Headroom/Configuration.hs b/src/Headroom/Configuration.hs index 5924b28..8844595 100644 --- a/src/Headroom/Configuration.hs +++ b/src/Headroom/Configuration.hs @@ -95,13 +95,14 @@ makeConfiguration :: MonadThrow m -> m CtConfiguration -- ^ full 'CtConfiguration' makeConfiguration pt = do - cRunMode <- lastOrError CkRunMode (cRunMode pt) - cSourcePaths <- lastOrError CkSourcePaths (cSourcePaths pt) - cExcludedPaths <- lastOrError CkExcludedPaths (cExcludedPaths pt) - cTemplateSource <- lastOrError CkTemplateSource (cTemplateSource pt) - cLicenseHeaders <- makeHeadersConfig (cLicenseHeaders pt) - cHeaderFnConfigs <- makeHeaderFnConfigs (cHeaderFnConfigs pt) - cVariables <- pure $ cVariables pt + cRunMode <- lastOrError CkRunMode (cRunMode pt) + cSourcePaths <- lastOrError CkSourcePaths (cSourcePaths pt) + cExcludedPaths <- lastOrError CkExcludedPaths (cExcludedPaths pt) + cBuiltInTemplates <- lastOrError CkBuiltInTemplates (cBuiltInTemplates pt) + cTemplateRefs <- pure $ cTemplateRefs pt + cLicenseHeaders <- makeHeadersConfig (cLicenseHeaders pt) + cHeaderFnConfigs <- makeHeaderFnConfigs (cHeaderFnConfigs pt) + cVariables <- pure $ cVariables pt pure Configuration { .. } diff --git a/src/Headroom/Configuration/Types.hs b/src/Headroom/Configuration/Types.hs index 6e8aa27..30f118a 100644 --- a/src/Headroom/Configuration/Types.hs +++ b/src/Headroom/Configuration/Types.hs @@ -67,7 +67,6 @@ module Headroom.Configuration.Types , GenMode(..) , LicenseType(..) , RunMode(..) - , TemplateSource(..) ) where @@ -89,6 +88,7 @@ import Headroom.Data.Regex ( Regex(..) ) import Headroom.Data.Serialization ( aesonOptions ) import Headroom.FileType.Types ( FileType ) import Headroom.Meta ( webDocConfigCurr ) +import Headroom.Template.TemplateRef ( TemplateRef ) import Headroom.Types ( fromHeadroomError , toHeadroomError ) @@ -166,6 +166,13 @@ data LicenseType -- ^ support for /MPL2/ license deriving (Bounded, Enum, EnumExtra, Eq, Ord, Show) +instance FromJSON LicenseType where + parseJSON = \case + String s -> case textToEnum s of + Just licenseType -> pure licenseType + _ -> error $ "Unknown license type: " <> T.unpack s + other -> error $ "Invalid value for run mode: " <> show other + ----------------------------------- RunMode ---------------------------------- -- | Represents what action should the @run@ command perform. @@ -202,17 +209,6 @@ data GenMode deriving (Eq, Show) -------------------------------- TemplateSource ------------------------------- - --- | Source of license templates -data TemplateSource - = TemplateFiles [FilePath] - -- ^ templates are stored as local files - | BuiltInTemplates LicenseType - -- ^ use built-in templates for selected license - deriving (Eq, Show) - - ---------------------------- UpdateCopyrightConfig --------------------------- -- | Main configuration for the "Headroom.HeaderFn.UpdateCopyright" @@ -316,19 +312,19 @@ instance FromJSON PtHeaderFnConfigs where -- | Application configuration. data Configuration (p :: Phase) = Configuration - { cRunMode :: p ::: RunMode + { cRunMode :: p ::: RunMode -- ^ mode of the @run@ command - , cSourcePaths :: p ::: [FilePath] + , cSourcePaths :: p ::: [FilePath] -- ^ paths to source code files - , cExcludedPaths :: p ::: [Regex] + , cExcludedPaths :: p ::: [Regex] -- ^ excluded source paths - , cTemplateSource :: p ::: TemplateSource - -- ^ source of license templates - , cVariables :: Variables + , cBuiltInTemplates :: p ::: Maybe LicenseType + , cTemplateRefs :: [TemplateRef] + , cVariables :: Variables -- ^ variable values for templates - , cLicenseHeaders :: HeadersConfig p + , cLicenseHeaders :: HeadersConfig p -- ^ configuration of license headers - , cHeaderFnConfigs :: HeaderFnConfigs p + , cHeaderFnConfigs :: HeaderFnConfigs p -- ^ configuration of license header functions } @@ -352,15 +348,15 @@ deriving via (Generically PtConfiguration) instance FromJSON PtConfiguration where parseJSON = withObject "PtConfiguration" $ \obj -> do - cRunMode <- Last <$> obj .:? "run-mode" - cSourcePaths <- Last <$> obj .:? "source-paths" - cExcludedPaths <- Last <$> obj .:? "excluded-paths" - cTemplateSource <- Last <$> get TemplateFiles (obj .:? "template-paths") - cVariables <- Variables <$> obj .:? "variables" .!= mempty - cLicenseHeaders <- obj .:? "license-headers" .!= mempty - cHeaderFnConfigs <- obj .:? "post-process" .!= mempty + cRunMode <- Last <$> obj .:? "run-mode" + cSourcePaths <- Last <$> obj .:? "source-paths" + cExcludedPaths <- Last <$> obj .:? "excluded-paths" + cBuiltInTemplates <- Last <$> obj .:? "builtin-templates" + cTemplateRefs <- obj .:? "template-paths" .!= mempty + cVariables <- Variables <$> obj .:? "variables" .!= mempty + cLicenseHeaders <- obj .:? "license-headers" .!= mempty + cHeaderFnConfigs <- obj .:? "post-process" .!= mempty pure Configuration { .. } - where get = fmap . fmap -------------------------------- HeaderConfig -------------------------------- @@ -511,8 +507,8 @@ data ConfigurationKey -- ^ no configuration for @source-paths@ | CkExcludedPaths -- ^ no configuration for @excluded-paths@ - | CkTemplateSource - -- ^ no configuration for template source + | CkBuiltInTemplates + -- ^ no configuration for built in templates | CkVariables -- ^ no configuration for @variables@ | CkEnabled @@ -577,9 +573,9 @@ displayException' = T.unpack . \case CkExcludedPaths -> missingConfig "excluded paths" (Just "excluded-paths") (Just "-e|--excluded-path") - CkTemplateSource -> missingConfig - "template files source" - (Just "template-paths") + CkBuiltInTemplates -> missingConfig + "use of built-in templates" + (Just "builtin-templates") (Just "(-t|--template-path)|--builtin-templates") CkVariables -> missingConfig "template variables" (Just "variables") diff --git a/test/Headroom/Command/RunSpec.hs b/test/Headroom/Command/RunSpec.hs index 7a99f5f..329cdaf 100644 --- a/test/Headroom/Command/RunSpec.hs +++ b/test/Headroom/Command/RunSpec.hs @@ -87,21 +87,6 @@ spec = do M.size <$> runRIO env (loadBuiltInTemplates BSD3) `shouldReturn` 12 - describe "loadTemplateFiles" $ do - it "should load templates from given paths" $ do - let env' = - env - & (envFileSystemL . fsFindFilesByExtsL .~ fsFindFilesByExts') - & (envFileSystemL . fsLoadFileL .~ fsLoadFile') - fsFindFilesByExts' "test-dir" _ = pure ["haskell.mustache"] - fsFindFilesByExts' _ _ = throwString "INVALID CONDITION" - fsLoadFile' "haskell.mustache" = pure "template content" - fsLoadFile' _ = throwString "INVALID CONDITION" - templates <- runRIO env' $ loadTemplateFiles @Mustache ["test-dir"] - M.size templates `shouldBe` 1 - M.member Haskell templates `shouldBe` True - - describe "loadTemplateRefs" $ do it "should load templates from given references" $ do let env' =