{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Headroom.Meta
( TemplateType
, buildVersion
, configBreakingChanges
, configFileName
, productDesc
, productInfo
, productName
, webDoc
, webDocConfigCurr
, webDocMigration
, webRepo
)
where
import Data.Version ( showVersion )
import Headroom.Meta.Version ( Version(..)
, parseVersion
, printVersion
, pvp
)
import Headroom.Template.Mustache ( Mustache )
import Paths_headroom ( version )
import RIO
import RIO.Partial ( fromJust )
import qualified RIO.Text as T
type TemplateType = Mustache
buildVersion :: Version
buildVersion :: Version
buildVersion = Maybe Version -> Version
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Version -> Version)
-> (Version -> Maybe Version) -> Version -> Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Version
parseVersion (Text -> Maybe Version)
-> (Version -> Text) -> Version -> Maybe Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (Version -> String) -> Version -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
showVersion (Version -> Version) -> Version -> Version
forall a b. (a -> b) -> a -> b
$ Version
version
configBreakingChanges :: [Version]
configBreakingChanges :: [Version]
configBreakingChanges = [[pvp|0.4.0.0|]]
configFileName :: IsString a => a
configFileName :: a
configFileName = a
".headroom.yaml"
productDesc :: Text
productDesc :: Text
productDesc = Text
"manage your source code license headers"
productInfo :: Text
productInfo :: Text
productInfo =
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
productName, Text
", v", Version -> Text
printVersion Version
buildVersion, Text
" :: ", Text
webRepo]
productName :: Text
productName :: Text
productName = Text
"headroom"
webDoc :: Version -> Text
webDoc :: Version -> Text
webDoc Version
v = Text
"http://doc.norcane.com/headroom/v" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Version -> Text
printVersion Version
v
webDocConfigCurr :: Text
webDocConfigCurr :: Text
webDocConfigCurr = Version -> Text
webDoc Version
buildVersion Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/documentation/configuration/"
webDocMigration :: Version -> Text
webDocMigration :: Version -> Text
webDocMigration Version
v = Version -> Text
webDoc Version
v Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/migration-guide"
webRepo :: Text
webRepo :: Text
webRepo = Text
"https://github.com/vaclavsvejcar/headroom"