Gabriella439 / turtle

Shell programming, Haskell style

Geek Repo:Geek Repo

Github PK Tool:Github PK Tool

script repeating output of command run with proc to stdout

iko-deleted opened this issue · comments

i've just started using turtle and i've made this script to count the number of lines in an ebook:

#!/usr/bin/env stack
-- stack script --resolver=lts-16.27 --package turtle --package protolude --package text
{-# LANGUAGE OverloadedStrings, NoImplicitPrelude, TypeApplications, LambdaCase #-}

module Main where

import Protolude hiding (FilePath)
import Data.Maybe (fromJust)
import Turtle

tempFileLocation = "/tmp/pdf_counter_tmp.pdf"

checkPrograms :: Shell ()
checkPrograms = do
    let programs :: IsString s => [s]
        programs = ["ebook-convert", "pdfinfo"]
    locations <- traverse which programs
    when (any isNothing locations) $ do
        print $ "you need to have all these programs on your PATH: " ++ show (programs :: [Text])
        exit (ExitFailure 1)

isSuccess ExitSuccess = True
isSuccess (ExitFailure _) = False

textPath path = toText path & \case
    Left t -> do
        case textToLine t of
            Just t -> echo ("invalid filepath: " <> t)
            Nothing -> echo "filepath contains a newline in it"
        return t
    Right t -> return t

convertFile :: FilePath -> Shell Bool
convertFile path = do
    pathT <- textPath path
    exitCode <-
        if hasExtension path "pdf"
            then proc "cp" [pathT, tempFileLocation] empty
            else proc "ebook-convert" [pathT, tempFileLocation, "--paper-size", "letter"] empty
    return $ isSuccess exitCode

pagesPattern :: Pattern Integer
pagesPattern = prefix "Pages:" *> space *> decimal

countPages :: FilePath -> Shell Integer
countPages path = do
    conversionSuccessful <- convertFile path
    guard conversionSuccessful
    info <- inproc "pdfinfo" [tempFileLocation] empty
    select $ match pagesPattern $ lineToText info

countDirectory :: FilePath -> Shell (Integer, FilePath)
countDirectory dir = do
    file <- lsif (fmap isRegularFile . stat) dir
    count <- countPages file
    return (count, fromJust $ stripPrefix dir file)

main :: IO ()
main = do
    sh checkPrograms
    path <- getArgs >>= \case
            [path] ->
                return $ decodeString path
            _ -> do
                putStrLn ("this program expects exactly one argument of a file or directory" :: Text) :: IO ()
                exitFailure
    isDir <- isDirectory <$> stat path
    if isDir
        then view $ countDirectory path
        else view $ countPages path

i would expect this, when run on a file, to simply print the number of lines in that file

instead, when run on a non-pdf file it returns that and also prints the entire ebook-convert output:

colby@desktop ~/c/p/src> ./Main.hs ~/Documents/books/short/anonymous-desert.epub 
1% Converting input to HTML...
InputFormatPlugin: EPUB Input running
on /home/colby/Documents/books/short/anonymous-desert.epub
Parsing all content...
34% Running transforms on e-book...
Merging user specified metadata...
Detecting structure...
Flattening CSS and remapping font sizes...
Source base font size is 12.00000pt
Removing fake margins...
Cleaning up manifest...
Trimming unused files from manifest...
Creating PDF Output...
67% Running PDF Output plugin
68% Parsed all content for markup transformation
70% Completed markup transformation
90% Rendered all HTML as PDF
91% Added links to PDF content
100% Updated metadata in PDF
PDF output written to /tmp/pdf_counter_tmp.pdf
Output saved to   /tmp/pdf_counter_tmp.pdf
111

it's possible that this is just some weird ebook-convert behavior, i haven't really looked into it all that much

a more minimal version of the script:

#!/usr/bin/env stack
-- stack script --resolver=lts-16.27 --package turtle --package protolude --package text
{-# LANGUAGE OverloadedStrings, NoImplicitPrelude, LambdaCase #-}

module Main where

import Protolude hiding (FilePath)
import Turtle

textPath path = toText path & \case
    Left t -> do
        case textToLine t of
            Just t -> echo ("invalid filepath: " <> t)
            Nothing -> echo "filepath contains a newline in it"
        return t
    Right t -> return t

main :: IO ()
main = do
    [file] <- map decodeString <$> getArgs
    fileT <- textPath file
    view (proc "ebook-convert" [fileT, "/tmp/pdf_counter_tmp.pdf", "--paper-size", "letter"] empty)

@ikea-shark-official: inproc does not capture stderr, so it will forward anything that the subprocess emits to stderr to the console. If you use inprocWithErr then it will capture both stdout and stderr.