{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Headroom.Configuration.Types
(
ConfigurationError(..)
, ConfigurationKey(..)
, Phase(..)
, (:::)
, Configuration(..)
, CtConfiguration
, PtConfiguration
, HeadersConfig(..)
, CtHeadersConfig
, PtHeadersConfig
, HeaderConfig(..)
, CtHeaderConfig
, PtHeaderConfig
, CtUpdateCopyrightConfig
, PtUpdateCopyrightConfig
, UpdateCopyrightConfig(..)
, CtHeaderFnConfig
, PtHeaderFnConfig
, HeaderFnConfig(..)
, CtHeaderFnConfigs
, PtHeaderFnConfigs
, HeaderFnConfigs(..)
, HeaderSyntax(..)
, GenMode(..)
, LicenseType(..)
, RunMode(..)
, TemplateSource(..)
)
where
import Control.Exception ( throw )
import Data.Aeson ( FromJSON(..)
, Value(String)
, genericParseJSON
, withObject
, (.!=)
, (.:?)
)
import Data.Monoid ( Last(..) )
import Headroom.Data.EnumExtra ( EnumExtra(..) )
import Headroom.Data.Regex ( Regex(..) )
import Headroom.FileType.Types ( FileType )
import Headroom.Serialization ( aesonOptions )
import Headroom.Types ( fromHeadroomError
, toHeadroomError
)
import Headroom.Variables.Types ( Variables(..) )
import RIO
import qualified RIO.Text as T
data Phase
= Partial
| Complete
type family (p :: Phase) ::: a where
'Partial ::: a = Last a
'Complete ::: a = a
data HeaderSyntax
= BlockComment Text Text
| LineComment Text
deriving (Eq, Show)
data BlockComment' = BlockComment'
{ bcStartsWith :: Text
, bcEndsWith :: Text
}
deriving (Eq, Generic, Show)
instance FromJSON BlockComment' where
parseJSON = genericParseJSON aesonOptions
newtype LineComment' = LineComment'
{ lcPrefixedBy :: Text
}
deriving (Eq, Generic, Show)
instance FromJSON LineComment' where
parseJSON = genericParseJSON aesonOptions
data LicenseType
= Apache2
| BSD3
| GPL2
| GPL3
| MIT
| MPL2
deriving (Bounded, Enum, EnumExtra, Eq, Ord, Show)
data RunMode
= Add
| Check
| Drop
| Replace
deriving (Eq, Show)
instance FromJSON RunMode where
parseJSON = \case
String s -> case T.toLower s of
"add" -> pure Add
"check" -> pure Check
"drop" -> pure Drop
"replace" -> pure Replace
_ -> error $ "Unknown run mode: " <> T.unpack s
other -> error $ "Invalid value for run mode: " <> show other
data GenMode
= GenConfigFile
| GenLicense (LicenseType, FileType)
deriving (Eq, Show)
data TemplateSource
= TemplateFiles [FilePath]
| BuiltInTemplates LicenseType
deriving (Eq, Show)
data UpdateCopyrightConfig (p :: Phase) = UpdateCopyrightConfig
{ uccSelectedAuthors :: p ::: Maybe (NonEmpty Text)
}
type CtUpdateCopyrightConfig = UpdateCopyrightConfig 'Complete
type PtUpdateCopyrightConfig = UpdateCopyrightConfig 'Partial
deriving instance Eq CtUpdateCopyrightConfig
deriving instance Eq PtUpdateCopyrightConfig
deriving instance Show CtUpdateCopyrightConfig
deriving instance Show PtUpdateCopyrightConfig
instance FromJSON PtUpdateCopyrightConfig where
parseJSON = withObject "PtUpdateCopyrightConfig" $ \obj -> do
uccSelectedAuthors <- Last <$> obj .:? "selected-authors-only"
pure UpdateCopyrightConfig { .. }
instance Semigroup PtUpdateCopyrightConfig where
x <> y = UpdateCopyrightConfig
{ uccSelectedAuthors = uccSelectedAuthors x <> uccSelectedAuthors y
}
instance Monoid PtUpdateCopyrightConfig where
mempty = UpdateCopyrightConfig mempty
data HeaderFnConfig (p :: Phase) c = HeaderFnConfig
{ hfcEnabled :: p ::: Bool
, hfcConfig :: c p
}
type CtHeaderFnConfig c = HeaderFnConfig 'Complete c
type PtHeaderFnConfig c = HeaderFnConfig 'Partial c
deriving instance (Eq (c 'Complete)) => Eq (CtHeaderFnConfig c)
deriving instance (Eq (c 'Partial)) => Eq (PtHeaderFnConfig c)
deriving instance (Show (c 'Complete)) => Show (CtHeaderFnConfig c)
deriving instance (Show (c 'Partial)) => Show (PtHeaderFnConfig c)
instance Semigroup (c 'Partial) => Semigroup (PtHeaderFnConfig c) where
x <> y = HeaderFnConfig { hfcEnabled = hfcEnabled x <> hfcEnabled y
, hfcConfig = hfcConfig x <> hfcConfig y
}
instance Monoid (c 'Partial) => Monoid (PtHeaderFnConfig c) where
mempty = HeaderFnConfig mempty mempty
instance (FromJSON (c 'Partial), Monoid (c 'Partial)) => FromJSON (PtHeaderFnConfig c) where
parseJSON = withObject "PtHeaderFnConfig" $ \obj -> do
hfcEnabled <- Last <$> obj .:? "enabled"
hfcConfig <- obj .:? "config" .!= mempty
pure HeaderFnConfig { .. }
data HeaderFnConfigs (p :: Phase) = HeaderFnConfigs
{ hfcsUpdateCopyright :: HeaderFnConfig p UpdateCopyrightConfig
}
type CtHeaderFnConfigs = HeaderFnConfigs 'Complete
type PtHeaderFnConfigs = HeaderFnConfigs 'Partial
deriving instance Eq CtHeaderFnConfigs
deriving instance Eq PtHeaderFnConfigs
deriving instance Show CtHeaderFnConfigs
deriving instance Show PtHeaderFnConfigs
instance Semigroup PtHeaderFnConfigs where
x <> y = HeaderFnConfigs
{ hfcsUpdateCopyright = hfcsUpdateCopyright x <> hfcsUpdateCopyright y
}
instance Monoid PtHeaderFnConfigs where
mempty = HeaderFnConfigs mempty
instance FromJSON PtHeaderFnConfigs where
parseJSON = withObject "PtHeaderFnConfigs" $ \obj -> do
hfcsUpdateCopyright <- obj .:? "update-copyright" .!= mempty
pure HeaderFnConfigs { .. }
data Configuration (p :: Phase) = Configuration
{ cRunMode :: p ::: RunMode
, cSourcePaths :: p ::: [FilePath]
, cExcludedPaths :: p ::: [Regex]
, cTemplateSource :: p ::: TemplateSource
, cVariables :: Variables
, cLicenseHeaders :: HeadersConfig p
, cHeaderFnConfigs :: HeaderFnConfigs p
}
type CtConfiguration = Configuration 'Complete
type PtConfiguration = Configuration 'Partial
deriving instance Eq CtConfiguration
deriving instance Eq PtConfiguration
deriving instance Show CtConfiguration
deriving instance Show 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 <- fmap Variables (obj .:? "variables" .!= mempty)
cLicenseHeaders <- obj .:? "license-headers" .!= mempty
cHeaderFnConfigs <- obj .:? "post-process" .!= mempty
pure Configuration { .. }
where get = fmap . fmap
instance Semigroup PtConfiguration where
x <> y = Configuration
{ cRunMode = cRunMode x <> cRunMode y
, cSourcePaths = cSourcePaths x <> cSourcePaths y
, cExcludedPaths = cExcludedPaths x <> cExcludedPaths y
, cTemplateSource = cTemplateSource x <> cTemplateSource y
, cVariables = cVariables x <> cVariables y
, cLicenseHeaders = cLicenseHeaders x <> cLicenseHeaders y
, cHeaderFnConfigs = cHeaderFnConfigs x <> cHeaderFnConfigs y
}
instance Monoid PtConfiguration where
mempty = Configuration mempty mempty mempty mempty mempty mempty mempty
data HeaderConfig (p :: Phase) = HeaderConfig
{ hcFileExtensions :: p ::: [Text]
, hcMarginAfter :: p ::: Int
, hcMarginBefore :: p ::: Int
, hcPutAfter :: p ::: [Regex]
, hcPutBefore :: p ::: [Regex]
, hcHeaderSyntax :: p ::: HeaderSyntax
}
type CtHeaderConfig = HeaderConfig 'Complete
type PtHeaderConfig = HeaderConfig 'Partial
deriving instance Eq CtHeaderConfig
deriving instance Eq PtHeaderConfig
deriving instance Show CtHeaderConfig
deriving instance Show PtHeaderConfig
instance FromJSON PtHeaderConfig where
parseJSON = withObject "PartialHeaderConfig" $ \obj -> do
hcFileExtensions <- Last <$> obj .:? "file-extensions"
hcMarginAfter <- Last <$> obj .:? "margin-after"
hcMarginBefore <- Last <$> obj .:? "margin-before"
hcPutAfter <- Last <$> obj .:? "put-after"
hcPutBefore <- Last <$> obj .:? "put-before"
blockComment <- obj .:? "block-comment"
lineComment <- obj .:? "line-comment"
hcHeaderSyntax <- pure . Last $ headerSyntax blockComment lineComment
pure HeaderConfig { .. }
where
headerSyntax (Just (BlockComment' s e)) Nothing = Just $ BlockComment s e
headerSyntax Nothing (Just (LineComment' p)) = Just $ LineComment p
headerSyntax Nothing Nothing = Nothing
headerSyntax _ _ = throw MixedHeaderSyntax
instance Monoid PtHeaderConfig where
mempty = HeaderConfig mempty mempty mempty mempty mempty mempty
instance Semigroup PtHeaderConfig where
x <> y = HeaderConfig
{ hcFileExtensions = hcFileExtensions x <> hcFileExtensions y
, hcMarginAfter = hcMarginAfter x <> hcMarginAfter y
, hcMarginBefore = hcMarginBefore x <> hcMarginBefore y
, hcPutAfter = hcPutAfter x <> hcPutAfter y
, hcPutBefore = hcPutBefore x <> hcPutBefore y
, hcHeaderSyntax = hcHeaderSyntax x <> hcHeaderSyntax y
}
data HeadersConfig (p :: Phase) = HeadersConfig
{ hscC :: HeaderConfig p
, hscCpp :: HeaderConfig p
, hscCss :: HeaderConfig p
, hscHaskell :: HeaderConfig p
, hscHtml :: HeaderConfig p
, hscJava :: HeaderConfig p
, hscJs :: HeaderConfig p
, hscPureScript :: HeaderConfig p
, hscRust :: HeaderConfig p
, hscScala :: HeaderConfig p
, hscShell :: HeaderConfig p
}
type CtHeadersConfig = HeadersConfig 'Complete
type PtHeadersConfig = HeadersConfig 'Partial
deriving instance Eq CtHeadersConfig
deriving instance Eq PtHeadersConfig
deriving instance Show CtHeadersConfig
deriving instance Show PtHeadersConfig
instance FromJSON PtHeadersConfig where
parseJSON = withObject "PartialHeadersConfig" $ \obj -> do
hscC <- obj .:? "c" .!= mempty
hscCpp <- obj .:? "cpp" .!= mempty
hscCss <- obj .:? "css" .!= mempty
hscHaskell <- obj .:? "haskell" .!= mempty
hscHtml <- obj .:? "html" .!= mempty
hscJava <- obj .:? "java" .!= mempty
hscJs <- obj .:? "js" .!= mempty
hscPureScript <- obj .:? "purescript" .!= mempty
hscRust <- obj .:? "rust" .!= mempty
hscScala <- obj .:? "scala" .!= mempty
hscShell <- obj .:? "shell" .!= mempty
pure HeadersConfig { .. }
instance Semigroup PtHeadersConfig where
x <> y = HeadersConfig { hscC = hscC x <> hscC y
, hscCpp = hscCpp x <> hscCpp y
, hscCss = hscCss x <> hscCss y
, hscHaskell = hscHaskell x <> hscHaskell y
, hscHtml = hscHtml x <> hscHtml y
, hscJava = hscJava x <> hscJava y
, hscJs = hscJs x <> hscJs y
, hscPureScript = hscPureScript x <> hscPureScript y
, hscRust = hscRust x <> hscRust y
, hscScala = hscScala x <> hscScala y
, hscShell = hscShell x <> hscShell y
}
instance Monoid PtHeadersConfig where
mempty = HeadersConfig mempty
mempty
mempty
mempty
mempty
mempty
mempty
mempty
mempty
mempty
mempty
data ConfigurationKey
= CkFileExtensions FileType
| CkHeaderSyntax FileType
| CkMarginAfter FileType
| CkMarginBefore FileType
| CkPutAfter FileType
| CkPutBefore FileType
| CkRunMode
| CkSourcePaths
| CkExcludedPaths
| CkTemplateSource
| CkVariables
| CkEnabled
deriving (Eq, Show)
data ConfigurationError
= MissingConfiguration ConfigurationKey
| MixedHeaderSyntax
deriving (Eq, Show, Typeable)
instance Exception ConfigurationError where
displayException = displayException'
toException = toHeadroomError
fromException = fromHeadroomError
displayException' :: ConfigurationError -> String
displayException' = T.unpack . \case
MissingConfiguration key -> case key of
CkFileExtensions fileType -> missingConfig
(withFT "file-extensions" fileType)
(Just "file-extensions")
Nothing
CkHeaderSyntax fileType -> missingConfig
(withFT "comment-syntax" fileType)
(Just "block-comment|line-comment")
Nothing
CkMarginAfter fileType -> missingConfig (withFT "margin-after" fileType)
(Just "margin-after")
Nothing
CkMarginBefore fileType -> missingConfig
(withFT "margin-before" fileType)
(Just "margin-before")
Nothing
CkPutAfter fileType ->
missingConfig (withFT "put-after" fileType) (Just "put-after") Nothing
CkPutBefore fileType ->
missingConfig (withFT "put-before" fileType) (Just "put-before") Nothing
CkRunMode -> missingConfig
"mode of the run command"
(Just "run-mode")
(Just
"(-a|--add-headers)|(-c|--check-header)|(-d|--drop-header)|(-r|--replace-headers)"
)
CkSourcePaths -> missingConfig "paths to source code files"
(Just "source-paths")
(Just "-s|--source-path")
CkExcludedPaths -> missingConfig "excluded paths"
(Just "excluded-paths")
(Just "-e|--excluded-path")
CkTemplateSource -> missingConfig
"template files source"
(Just "template-paths")
(Just "(-t|--template-path)|--builtin-templates")
CkVariables -> missingConfig "template variables"
(Just "variables")
(Just "-v|--variable")
CkEnabled -> missingConfig "enabled" (Just "enabled") Nothing
MixedHeaderSyntax -> mixedHeaderSyntax
where
withFT msg fileType = msg <> " (" <> T.pack (show fileType) <> ")"
mixedHeaderSyntax = mconcat
[ "Invalid configuration, combining 'block-comment' with 'line-comment' "
, "is not allowed. Either use 'block-comment' to define multi-line "
, "comment header, or 'line-comment' to define header composed of "
, "multiple single-line comments."
]
missingConfig :: Text -> Maybe Text -> Maybe Text -> Text
missingConfig desc yaml cli = mconcat
[ "Missing configuration for '"
, desc
, "' ("
, options
, "). See official documentation for more details."
]
where
cliText = fmap (\c -> "command line option '" <> c <> "'") cli
yamlText = fmap (\y -> "YAML option '" <> y <> "'") yaml
options = T.intercalate " or " . catMaybes $ [cliText, yamlText]