module Ribosome.App.ProjectPath where import Path (Abs, Dir, Path, Rel, (</>)) import Path.IO (getCurrentDir) import Ribosome.App.Error (RainbowError, ioError) cwdProjectPath :: Members [Stop RainbowError, Embed IO] r => Bool -> Path Rel Dir -> Sem r (Path Abs Dir) cwdProjectPath :: forall (r :: EffectRow). Members '[Stop RainbowError, Embed IO] r => Bool -> Path Rel Dir -> Sem r (Path Abs Dir) cwdProjectPath Bool append Path Rel Dir name = do Path Abs Dir cwd <- (Text -> RainbowError) -> IO (Path Abs Dir) -> Sem r (Path Abs Dir) forall e (r :: EffectRow) a. Members '[Stop e, Embed IO] r => (Text -> e) -> IO a -> Sem r a stopTryIOError Text -> RainbowError err IO (Path Abs Dir) forall (m :: * -> *). MonadIO m => m (Path Abs Dir) getCurrentDir pure (if Bool append then Path Abs Dir cwd Path Abs Dir -> Path Rel Dir -> Path Abs Dir forall b t. Path b Dir -> Path Rel t -> Path b t </> Path Rel Dir name else Path Abs Dir cwd) where err :: Text -> RainbowError err = [Chunk] -> Text -> RainbowError ioError [Item [Chunk] "Could not determine current directory"]