{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
module File
( replace,
convert,
)
where
import Control.Monad.Logger (logInfo)
import Control.Monad.Reader (MonadIO (liftIO), MonadReader (ask))
import Data.Text (Text, pack)
import qualified Data.Text as T (replace)
import Data.Text.IO (readFile, writeFile)
import qualified Environment (T (..))
import Initialiser.Types (Initialiser)
import Prelude hiding (readFile, writeFile)
replace :: FilePath -> Initialiser ()
replace :: FilePath -> Initialiser ()
replace FilePath
p = do
$Int
FilePath
LogLevel
FilePath -> Text
FilePath -> FilePath -> FilePath -> CharPos -> CharPos -> Loc
Text -> Text
Loc -> Text -> LogLevel -> Text -> Initialiser ()
(Text -> Initialiser ())
-> (Text -> Text) -> Text -> Initialiser ()
forall a. a -> a
forall msg.
ToLogStr msg =>
Loc -> Text -> LogLevel -> msg -> Initialiser ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
pack :: FilePath -> Text
id :: forall a. a -> a
. :: forall b c a. (b -> c) -> (a -> b) -> a -> c
monadLoggerLog :: forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
logInfo (Text
"replacing file " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FilePath -> Text
pack (FilePath -> FilePath
forall a. Show a => a -> FilePath
show FilePath
p))
Text
contents <- IO Text -> Initialiser Text
forall a. IO a -> Initialiser a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> Initialiser Text) -> IO Text -> Initialiser Text
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Text
readFile FilePath
p
Text
contents' <- Text -> Initialiser Text
convert Text
contents
IO () -> Initialiser ()
forall a. IO a -> Initialiser a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Initialiser ()) -> IO () -> Initialiser ()
forall a b. (a -> b) -> a -> b
$ FilePath -> Text -> IO ()
writeFile FilePath
p Text
contents'
convert :: Text -> Initialiser Text
convert :: Text -> Initialiser Text
convert Text
contents = do
Environment.T {Year
FilePath
LicenseId
Text
URI
LogLevel
name :: Text
cabalName :: Text
homepage :: URI
author :: Text
maintainer :: Text
licence :: LicenseId
path :: FilePath
year :: Year
verbosity :: LogLevel
name :: T -> Text
cabalName :: T -> Text
homepage :: T -> URI
author :: T -> Text
maintainer :: T -> Text
licence :: T -> LicenseId
path :: T -> FilePath
year :: T -> Year
verbosity :: T -> LogLevel
..} <- Initialiser T
forall r (m :: * -> *). MonadReader r m => m r
ask
Text -> Initialiser Text
forall a. a -> Initialiser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Text -> Initialiser Text)
-> (Text -> Text) -> Text -> Initialiser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"templatise" Text
name
(Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"template-hs" Text
name
(Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"template.hs" Text
name
(Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"initialise" Text
name
(Text -> Initialiser Text) -> Text -> Initialiser Text
forall a b. (a -> b) -> a -> b
$ Text
contents