aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rwxr-xr-xmarkdown2pdf12
-rw-r--r--src/markdown2pdf.hs9
2 files changed, 3 insertions, 18 deletions
diff --git a/markdown2pdf b/markdown2pdf
index ab0f3ae78..faeafc174 100755
--- a/markdown2pdf
+++ b/markdown2pdf
@@ -125,16 +125,6 @@ fi
done
) || exit $?
-is_target_exists=
-if [ -f "$destname" ]; then
- is_target_exists=1
- mv "$destname" "$destname~"
-fi
-
mv -f $THIS_TEMPDIR/$texname.pdf "$destname"
-errn "Created $destname"
-[ -z "$is_target_exists" ] || {
- errn " (previous file has been backed up as $destname~)"
-}
-err .
+err "Created $destname"
diff --git a/src/markdown2pdf.hs b/src/markdown2pdf.hs
index 038549180..79cd09a2d 100644
--- a/src/markdown2pdf.hs
+++ b/src/markdown2pdf.hs
@@ -3,7 +3,7 @@ module Main where
import Data.List (isInfixOf, intercalate, isPrefixOf)
import Data.Maybe (isNothing)
-import Control.Monad (when, unless, guard)
+import Control.Monad (unless, guard)
import Control.Exception (tryJust, bracket)
import System.IO (stderr)
@@ -129,13 +129,8 @@ saveStdin file = do
saveOutput :: FilePath -> FilePath -> IO ()
saveOutput input output = do
- outputExist <- doesFileExist output
- when outputExist $ do
- let output' = output ++ "~"
- renameFile output output'
- putStrLn $! "Created backup file " ++ output'
copyFile input output
- putStrLn $! "Created " ++ output
+ hPutStrLn stderr $! "Created " ++ output
main :: IO ()
main = bracket