{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeApplications  #-}

{-|
Module      : Headroom.Embedded.TH
Description : /Template Haskell/ functions for "Headroom.Embedded"
Copyright   : (c) 2019-2021 Vaclav Svejcar
License     : BSD-3-Clause
Maintainer  : vaclav.svejcar@gmail.com
Stability   : experimental
Portability : POSIX

This module contains some /Template Haskell/ powered functions, used by
"Headroom.Embedded" module, that needs to be placed in separated module, due to
/GHC/ stage restriction.
-}

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


-- | Embeds stub configuration file to source code.
embedConfigFile :: Q Exp
embedConfigFile :: Q Exp
embedConfigFile = FilePath -> Q Exp
embedStringFile FilePath
"embedded/config-file.yaml"


-- | Embeds default configuration file to source code.
embedDefaultConfig :: Q Exp
embedDefaultConfig :: Q Exp
embedDefaultConfig = FilePath -> Q Exp
embedStringFile FilePath
"embedded/default-config.yaml"


-- | Embeds /template file/ to the source code.
embedTemplate :: LicenseType
              -- ^ type of the /license/
              -> FileType
              -- ^ type of the source code file
              -> Q Exp
              -- ^ content of the appropriate /template/ file
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 a. Template a => NonEmpty Text
templateExtensions @TemplateType


------------------------------  PRIVATE FUNCTIONS  -----------------------------

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