module Sound.Sox.Write (simple, extended, manyExtended, ) where
import qualified Sound.Sox.Frame as Frame
import Sound.Sox.System (catchCtrlC, )
import qualified Sound.Sox.Option.Format as Option
import qualified Sound.Sox.Private.Option as OptPriv
import qualified Sound.Sox.Private.Arguments as Args
import Data.Monoid (mconcat, )
import qualified Data.Traversable as Trav
import qualified Data.Foldable as Fold
import qualified System.Process as Proc
import qualified System.IO as IO
import Control.Exception (bracket, )
import System.Exit (ExitCode, )
simple ::
(Frame.C y) =>
(IO.Handle -> sig y -> IO ())
->
Option.T ->
FilePath ->
Int
->
sig y ->
IO ExitCode
simple write opts =
extended write Option.none opts
extended ::
(Frame.C y) =>
(IO.Handle -> sig y -> IO ())
->
Option.T
->
Option.T
->
FilePath ->
Int
->
sig y ->
IO ExitCode
extended write srcOpts dstOpts fileName sampleRate signal =
bracket
(open srcOpts dstOpts fileName sampleRate signal)
close
(\(input,_,_,proc) ->
catchCtrlC >>
write input signal >>
return proc)
>>= Proc.waitForProcess
manyExtended ::
(Frame.C y, Trav.Traversable f) =>
(f IO.Handle -> sig y -> IO ())
->
Option.T
->
Option.T
->
f FilePath ->
Int
->
sig y ->
IO (f ExitCode)
manyExtended write srcOpts dstOpts fileNames sampleRate signal =
bracket
(Trav.traverse
(\fileName -> open srcOpts dstOpts fileName sampleRate signal)
fileNames)
(Fold.traverse_ close)
(\handles ->
catchCtrlC >>
write (fmap (\(input,_,_,_) -> input) handles) signal >>
return (fmap (\(_,_,_,proc) -> proc) handles))
>>= Trav.traverse Proc.waitForProcess
type Handle = (IO.Handle, IO.Handle, IO.Handle, Proc.ProcessHandle)
open ::
(Frame.C y) =>
Option.T
->
Option.T
->
FilePath ->
Int
->
sig y ->
IO Handle
open srcOpts dstOpts fileName sampleRate signal =
Proc.runInteractiveProcess "sox"
(Args.decons $ mconcat $
OptPriv.toArguments
(mconcat $
srcOpts :
Option.numberOfChannels
(Frame.withSignal Frame.numberOfChannels signal) :
Option.sampleRate sampleRate :
Option.format (Frame.withSignal Frame.format signal) :
[]) :
Args.pipe :
OptPriv.toArguments dstOpts :
Args.fileName fileName :
[])
Nothing Nothing
close :: Handle -> IO ()
close (input,output,err,_proc) =
mapM_ IO.hClose [input, output, err]