module FFProbe.Exec (execFFProbe) where
import Control.Exception (IOException, try)
import Data.Bifunctor (first)
import Data.Functor ((<&>))
import System.Process (proc, readCreateProcess)
execFFProbe :: String -> IO (Either String String)
execFFProbe :: String -> IO (Either String String)
execFFProbe String
path = IO String -> IO (Either IOException String)
try_ (CreateProcess -> String -> IO String
readCreateProcess CreateProcess
process String
input) IO (Either IOException String)
-> (Either IOException String -> Either String String)
-> IO (Either String String)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (IOException -> String)
-> Either IOException String -> Either String String
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first IOException -> String
forall a. Show a => a -> String
show
    where
        try_ :: IO String -> IO (Either IOException String)
        try_ :: IO String -> IO (Either IOException String)
try_ = IO String -> IO (Either IOException String)
forall e a. Exception e => IO a -> IO (Either e a)
try
        input :: String
input = String
""
        process :: CreateProcess
process = String -> [String] -> CreateProcess
proc String
"ffprobe" ([String]
ffprobeArgs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
path])
        ffprobeArgs :: [String]
ffprobeArgs =
            [ String
"-v",
              String
"quiet",
              String
"-print_format",
              String
"json",
              String
"-show_format",
              String
"-show_streams",
              String
"-show_chapters"
            ]