{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Headroom.Command.Gen
( commandGen
, parseGenMode
)
where
import Data.String.Interpolate ( iii )
import Headroom.Command.Types ( Command(..)
, CommandGenOptions(..)
)
import Headroom.Command.Utils ( bootstrap )
import Headroom.Configuration.Enrich ( Enrich(..)
, replaceEmptyValue
, withText
)
import Headroom.Configuration.Types ( GenMode(..) )
import Headroom.Data.Lens ( suffixLensesFor )
import Headroom.Embedded ( configFileStub
, licenseTemplate
)
import Headroom.Meta ( buildVersion )
import Headroom.Meta.Version ( printVersion )
import Headroom.Types ( fromHeadroomError
, toHeadroomError
)
import Prelude ( putStrLn )
import RIO
import qualified RIO.Text as T
data Env = Env
{ Env -> LogFunc
envLogFunc :: !LogFunc
, Env -> CommandGenOptions
envGenOptions :: !CommandGenOptions
}
suffixLensesFor ["envLogFunc"] ''Env
instance HasLogFunc Env where
logFuncL :: (LogFunc -> f LogFunc) -> Env -> f Env
logFuncL = (LogFunc -> f LogFunc) -> Env -> f Env
Lens' Env LogFunc
envLogFuncL
env' :: CommandGenOptions -> LogFunc -> IO Env
env' :: CommandGenOptions -> LogFunc -> IO Env
env' CommandGenOptions
opts LogFunc
logFunc = Env -> IO Env
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Env -> IO Env) -> Env -> IO Env
forall a b. (a -> b) -> a -> b
$ Env :: LogFunc -> CommandGenOptions -> Env
Env { envLogFunc :: LogFunc
envLogFunc = LogFunc
logFunc, envGenOptions :: CommandGenOptions
envGenOptions = CommandGenOptions
opts }
parseGenMode :: MonadThrow m
=> Command
-> m GenMode
parseGenMode :: Command -> m GenMode
parseGenMode = \case
Gen Bool
True Maybe (LicenseType, FileType)
Nothing -> GenMode -> m GenMode
forall (f :: * -> *) a. Applicative f => a -> f a
pure GenMode
GenConfigFile
Gen Bool
False (Just (LicenseType, FileType)
license) -> GenMode -> m GenMode
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenMode -> m GenMode) -> GenMode -> m GenMode
forall a b. (a -> b) -> a -> b
$ (LicenseType, FileType) -> GenMode
GenLicense (LicenseType, FileType)
license
Command
_ -> CommandGenError -> m GenMode
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM CommandGenError
NoGenModeSelected
commandGen :: CommandGenOptions
-> IO ()
commandGen :: CommandGenOptions -> IO ()
commandGen CommandGenOptions
opts = (LogFunc -> IO Env) -> Bool -> RIO Env () -> IO ()
forall env a. (LogFunc -> IO env) -> Bool -> RIO env a -> IO a
bootstrap (CommandGenOptions -> LogFunc -> IO Env
env' CommandGenOptions
opts) Bool
False (RIO Env () -> IO ()) -> RIO Env () -> IO ()
forall a b. (a -> b) -> a -> b
$ case CommandGenOptions -> GenMode
cgoGenMode CommandGenOptions
opts of
GenMode
GenConfigFile -> IO () -> RIO Env ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ()
printConfigFile
GenLicense (LicenseType
lType, FileType
fType) -> IO () -> RIO Env ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> RIO Env ()) -> (String -> IO ()) -> String -> RIO Env ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ()
putStrLn (String -> RIO Env ()) -> String -> RIO Env ()
forall a b. (a -> b) -> a -> b
$ LicenseType -> FileType -> String
forall a. IsString a => LicenseType -> FileType -> a
licenseTemplate LicenseType
lType FileType
fType
printConfigFile :: IO ()
printConfigFile :: IO ()
printConfigFile = String -> IO ()
putStrLn (String -> IO ()) -> (Text -> String) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Enrich -> Text -> Text
enrich Enrich
modify Text
forall a. IsString a => a
configFileStub
where
modify :: Enrich
modify = Text -> (Text -> (ValueType, Text)) -> Enrich
replaceEmptyValue Text
"version" ((Text -> (ValueType, Text)) -> Enrich)
-> (Text -> (ValueType, Text)) -> Enrich
forall a b. (a -> b) -> a -> b
$ Text -> Text -> (ValueType, Text)
withText Text
ver
ver :: Text
ver = Version -> Text
printVersion Version
buildVersion
data CommandGenError = NoGenModeSelected
deriving (CommandGenError -> CommandGenError -> Bool
(CommandGenError -> CommandGenError -> Bool)
-> (CommandGenError -> CommandGenError -> Bool)
-> Eq CommandGenError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandGenError -> CommandGenError -> Bool
$c/= :: CommandGenError -> CommandGenError -> Bool
== :: CommandGenError -> CommandGenError -> Bool
$c== :: CommandGenError -> CommandGenError -> Bool
Eq, Int -> CommandGenError -> ShowS
[CommandGenError] -> ShowS
CommandGenError -> String
(Int -> CommandGenError -> ShowS)
-> (CommandGenError -> String)
-> ([CommandGenError] -> ShowS)
-> Show CommandGenError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandGenError] -> ShowS
$cshowList :: [CommandGenError] -> ShowS
show :: CommandGenError -> String
$cshow :: CommandGenError -> String
showsPrec :: Int -> CommandGenError -> ShowS
$cshowsPrec :: Int -> CommandGenError -> ShowS
Show)
instance Exception CommandGenError where
displayException :: CommandGenError -> String
displayException = CommandGenError -> String
displayException'
toException :: CommandGenError -> SomeException
toException = CommandGenError -> SomeException
forall e. Exception e => e -> SomeException
toHeadroomError
fromException :: SomeException -> Maybe CommandGenError
fromException = SomeException -> Maybe CommandGenError
forall e. Exception e => SomeException -> Maybe e
fromHeadroomError
displayException' :: CommandGenError -> String
displayException' :: CommandGenError -> String
displayException' = \case
CommandGenError
NoGenModeSelected -> [iii|
Please select at least one option what to generate
(see --help for details)
|]