module Ribosome.App.TemplateTree where import qualified Data.Text.IO as Text import Path (Abs, Dir, File, Path, Rel, parent, reldir, toFilePath, (</>)) import Path.IO (createDirIfMissing, doesFileExist) import Ribosome.App.Data (Global (..)) import Ribosome.App.Data.TemplateTree (TemplateTree (TDir, TFile)) import Ribosome.App.Error (RainbowError, ioError) import Ribosome.App.UserInput (cmdColor, infoMessage, pathChunk) warnExists :: Members [Stop RainbowError, Embed IO] r => Path Rel File -> Sem r () warnExists :: forall (r :: EffectRow). Members '[Stop RainbowError, Embed IO] r => Path Rel File -> Sem r () warnExists Path Rel File file = [Chunk] -> Sem r () forall (r :: EffectRow). Members '[Stop RainbowError, Embed IO] r => [Chunk] -> Sem r () infoMessage [ Item [Chunk] "⚠️ Not overwriting ", Path Rel File -> Chunk forall b t. Path b t -> Chunk pathChunk Path Rel File file, Item [Chunk] " without ", Chunk -> Chunk cmdColor Chunk "--force" ] writeTemplate :: Members [Stop RainbowError, Embed IO] r => Global -> Path Abs File -> Path Rel File -> Text -> Sem r () writeTemplate :: forall (r :: EffectRow). Members '[Stop RainbowError, Embed IO] r => Global -> Path Abs File -> Path Rel File -> Text -> Sem r () writeTemplate Global {Bool $sel:force:Global :: Global -> Bool $sel:quiet:Global :: Global -> Bool force :: Bool quiet :: Bool ..} Path Abs File path Path Rel File relPath Text content = do (Text -> RainbowError) -> IO () -> Sem r () forall e (r :: EffectRow) a. Members '[Stop e, Embed IO] r => (Text -> e) -> IO a -> Sem r a stopTryIOError Text -> RainbowError dirError (Bool -> Path Abs Dir -> IO () forall (m :: * -> *) b. MonadIO m => Bool -> Path b Dir -> m () createDirIfMissing Bool True Path Abs Dir dir) Bool exists <- IO Bool -> Sem r Bool forall (m :: * -> *) (r :: EffectRow) a. Member (Embed m) r => m a -> Sem r a embed (Path Abs File -> IO Bool forall (m :: * -> *) b. MonadIO m => Path b File -> m Bool doesFileExist Path Abs File path) if Bool exists Bool -> Bool -> Bool && Bool -> Bool not Bool force then Bool -> Sem r () -> Sem r () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless Bool quiet (Path Rel File -> Sem r () forall (r :: EffectRow). Members '[Stop RainbowError, Embed IO] r => Path Rel File -> Sem r () warnExists Path Rel File relPath) else (Text -> RainbowError) -> IO () -> Sem r () forall e (r :: EffectRow) a. Members '[Stop e, Embed IO] r => (Text -> e) -> IO a -> Sem r a stopTryIOError Text -> RainbowError writeError (FilePath -> Text -> IO () Text.writeFile (Path Abs File -> FilePath forall b t. Path b t -> FilePath toFilePath Path Abs File path) Text content) where writeError :: Text -> RainbowError writeError Text msg = [Chunk] -> Text -> RainbowError ioError [Item [Chunk] "Failed to write ", Path Abs File -> Chunk forall b t. Path b t -> Chunk pathChunk Path Abs File path] Text msg dirError :: Text -> RainbowError dirError = [Chunk] -> Text -> RainbowError ioError [Item [Chunk] "Failed to create directory ", Path Abs Dir -> Chunk forall b t. Path b t -> Chunk pathChunk Path Abs Dir dir] dir :: Path Abs Dir dir = Path Abs File -> Path Abs Dir forall b t. Path b t -> Path b Dir parent Path Abs File path writeTemplateTree :: Members [Stop RainbowError, Embed IO] r => Global -> Path Abs Dir -> TemplateTree -> Sem r () writeTemplateTree :: forall (r :: EffectRow). Members '[Stop RainbowError, Embed IO] r => Global -> Path Abs Dir -> TemplateTree -> Sem r () writeTemplateTree Global global Path Abs Dir root = Path Rel Dir -> TemplateTree -> Sem r () spin [reldir|.|] where spin :: Path Rel Dir -> TemplateTree -> Sem r () spin Path Rel Dir current = \case TDir Path Rel Dir sub [TemplateTree] nodes -> (TemplateTree -> Sem r ()) -> [TemplateTree] -> Sem r () forall (t :: * -> *) (f :: * -> *) a b. (Foldable t, Applicative f) => (a -> f b) -> t a -> f () traverse_ (Path Rel Dir -> TemplateTree -> Sem r () spin (Path Rel Dir current Path Rel Dir -> Path Rel Dir -> Path Rel Dir forall b t. Path b Dir -> Path Rel t -> Path b t </> Path Rel Dir sub)) [TemplateTree] nodes TFile Path Rel File name Text content -> let file :: Path Rel File file = Path Rel Dir current Path Rel Dir -> Path Rel File -> Path Rel File forall b t. Path b Dir -> Path Rel t -> Path b t </> Path Rel File name in Global -> Path Abs File -> Path Rel File -> Text -> Sem r () forall (r :: EffectRow). Members '[Stop RainbowError, Embed IO] r => Global -> Path Abs File -> Path Rel File -> Text -> Sem r () writeTemplate Global global (Path Abs Dir root Path Abs Dir -> Path Rel File -> Path Abs File forall b t. Path b Dir -> Path Rel t -> Path b t </> Path Rel File file) Path Rel File file Text content