Skip to content

Commit

Permalink
[#66] Switch to new TemplateRef logic
Browse files Browse the repository at this point in the history
  • Loading branch information
vaclavsvejcar committed Apr 11, 2021
1 parent 11ab0af commit 0a7d3ac
Show file tree
Hide file tree
Showing 7 changed files with 93 additions and 159 deletions.
2 changes: 1 addition & 1 deletion app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 { .. }
33 changes: 15 additions & 18 deletions src/Headroom/Command.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
83 changes: 25 additions & 58 deletions src/Headroom/Command/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,6 @@ responsible for license header management.
module Headroom.Command.Run
( commandRun
, loadBuiltInTemplates
, loadTemplateFiles
, loadTemplateRefs
, typeOfTemplate
-- * License Header Post-processing
Expand Down Expand Up @@ -57,7 +56,6 @@ import Headroom.Configuration.Types ( Configuration(..)
, LicenseType(..)
, PtConfiguration
, RunMode(..)
, TemplateSource(..)
)
import Headroom.Data.EnumExtra ( EnumExtra(..) )
import Headroom.Data.Has ( Has(..) )
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand All @@ -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)
Expand Down Expand Up @@ -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

Expand All @@ -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
Expand Down
42 changes: 15 additions & 27 deletions src/Headroom/Command/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
15 changes: 8 additions & 7 deletions src/Headroom/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 { .. }


Expand Down
Loading

0 comments on commit 0a7d3ac

Please sign in to comment.