Skip to content

Commit

Permalink
fixup! fixup! [#39] String interpolation in coffer output messages
Browse files Browse the repository at this point in the history
  • Loading branch information
DK318 committed May 5, 2022
1 parent db28412 commit ce9d09a
Showing 1 changed file with 21 additions and 19 deletions.
40 changes: 21 additions & 19 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,26 +7,27 @@ module Main where
import Backend
import Backend.Commands as Commands
import Backend.Interpreter
import Control.Lens
import Control.Monad (forM_, when)
import Data.Text (pack)
import Data.Text.IO qualified as TIO
import Fmt
import Options.Applicative (execParser)
import Polysemy
import Polysemy.Error (Error, errorToIOFinal)
import System.Exit (die, exitFailure)
import Toml qualified

import CLI.Parser
import CLI.PrettyPrint
import CLI.Types
import Coffer.Directory qualified as Dir
import Coffer.Path (EntryPath, Path, QualifiedPath(qpPath))
import Config (Config(..), configCodec)
import Control.Lens
import Control.Monad (forM, forM_, when)
import Data.Maybe (fromMaybe)
import Data.Text (pack)
import Data.Text.IO qualified as TIO
import Entry qualified as E
import Error
import Fmt
import Options.Applicative (execParser)
import Polysemy
import Polysemy.Error (Error, errorToIOFinal)
import System.Environment (lookupEnv)
import System.Exit (die, exitFailure)
import Toml qualified
import Text.Interpolation.Nyan

runBackendIO
Expand Down Expand Up @@ -138,7 +139,7 @@ main = do
CPRMissingEntryName -> printError
"The destination path is not a valid entry path. Please specify the new name of the entry."
CPRCreateErrors errors -> do
errorMsgs <- buildErrorMessages errors
let errorMsgs = buildErrorMessages errors
printError [int|s|
The following entries cannot be renamed:

Expand All @@ -157,7 +158,7 @@ main = do
CPRMissingEntryName -> printError
"The destination path is not a valid entry path. Please specify the new name of the entry."
CPRCreateErrors errors -> do
errorMsgs <- buildErrorMessages errors
let errorMsgs = buildErrorMessages errors
printError [int|s|
The following entries cannot be copied:

Expand Down Expand Up @@ -228,10 +229,11 @@ main = do
CEDestinationIsDirectory entryPath -> entryPath
CEEntryAlreadyExists entryPath -> entryPath

buildErrorMessages :: [(QualifiedPath EntryPath, CreateError)] -> Sem r [Builder]
buildErrorMessages errors = do
forM errors \(from, err) -> do
let entryPath = getEntryFromCreateError err
let header = [int|s|'#{from}' to '#{entryPath}':|]
let errorMsg = createErrorToBuilder err
pure $ unlinesF @_ @Builder $ header : [indentF 2 errorMsg]
buildErrorMessages :: [(QualifiedPath EntryPath, CreateError)] -> [Builder]
buildErrorMessages =
fmap \(from, err) ->
let
entryPath = getEntryFromCreateError err
header = [int|s|'#{from}' to '#{entryPath}':|]
errorMsg = createErrorToBuilder err
in unlinesF @_ @Builder $ header : [indentF 2 errorMsg]

0 comments on commit ce9d09a

Please sign in to comment.