{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeApplications #-}
module Headroom.Embedded.TH
( embedConfigFile
, embedDefaultConfig
, embedTemplate
)
where
import Data.FileEmbed ( embedStringFile )
import Headroom.Configuration.Types ( LicenseType(..) )
import Headroom.Data.EnumExtra ( EnumExtra(..) )
import Headroom.FileType.Types ( FileType(..) )
import Headroom.Meta ( TemplateType )
import Headroom.Template ( Template(..) )
import Language.Haskell.TH.Syntax ( Exp
, Q
)
import RIO
import qualified RIO.NonEmpty as NE
import qualified RIO.Text as T
embedConfigFile :: Q Exp
embedConfigFile :: Q Exp
embedConfigFile = FilePath -> Q Exp
embedStringFile FilePath
"embedded/config-file.yaml"
embedDefaultConfig :: Q Exp
embedDefaultConfig :: Q Exp
embedDefaultConfig = FilePath -> Q Exp
embedStringFile FilePath
"embedded/default-config.yaml"
embedTemplate :: LicenseType
-> FileType
-> Q Exp
embedTemplate :: LicenseType -> FileType -> Q Exp
embedTemplate LicenseType
lt FileType
ft = (FilePath -> Q Exp
embedStringFile (FilePath -> Q Exp)
-> ([FilePath] -> FilePath) -> [FilePath] -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat)
[FilePath
"embedded/license/", LicenseType -> FilePath
forall a. EnumExtra a => a -> FilePath
toStringLC LicenseType
lt, FilePath
"/", FileType -> FilePath
forall a. EnumExtra a => a -> FilePath
toStringLC FileType
ft, FilePath
".", FilePath
ext]
where ext :: FilePath
ext = Text -> FilePath
T.unpack (Text -> FilePath)
-> (NonEmpty Text -> Text) -> NonEmpty Text -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Text -> Text
forall a. NonEmpty a -> a
NE.head (NonEmpty Text -> FilePath) -> NonEmpty Text -> FilePath
forall a b. (a -> b) -> a -> b
$ Template TemplateType => NonEmpty Text
forall t. Template t => NonEmpty Text
templateExtensions @TemplateType
toStringLC :: EnumExtra a => a -> String
toStringLC :: a -> FilePath
toStringLC = Text -> FilePath
T.unpack (Text -> FilePath) -> (a -> Text) -> a -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. EnumExtra a => a -> Text
enumToText