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, )


{- |
Sox determines the output format
from the filename extension or from 'Option.format'.
Make sure that you provide one of them.

> :load Sound.Sox.Write Sound.Sox.Signal.List
>
> simple Sound.Sox.Signal.List.put Option.none "test.aiff" 11025 (take 100 $ iterate (1000+) (0::Data.Int.Int16))
-}
simple ::
   (Frame.C y) =>
   (IO.Handle -> sig y -> IO ())
      {- ^ Writer routine -
           e.g. 'Sound.Sox.Signal.List.put'
           or 'Data.StorableVector.hPut' -} ->
   Option.T ->
   FilePath ->
   Int
      {- ^ sample rate -} ->
   sig y ->
   IO ExitCode
simple :: forall y (sig :: * -> *).
C y =>
(Handle -> sig y -> IO ())
-> T -> FilePath -> Int -> sig y -> IO ExitCode
simple Handle -> sig y -> IO ()
write T
opts =
   forall y (sig :: * -> *).
C y =>
(Handle -> sig y -> IO ())
-> T -> T -> FilePath -> Int -> sig y -> IO ExitCode
extended Handle -> sig y -> IO ()
write T
Option.none T
opts

extended ::
   (Frame.C y) =>
   (IO.Handle -> sig y -> IO ())
      {- ^ Writer routine -
           e.g. 'Sound.Sox.Signal.List.put'
           or 'Data.StorableVector.hPut' -} ->
   Option.T
      {- ^ source options, usually none -} ->
   Option.T
      {- ^ target options -} ->
   FilePath ->
   Int
      {- ^ sample rate -} ->
   sig y ->
   IO ExitCode
extended :: forall y (sig :: * -> *).
C y =>
(Handle -> sig y -> IO ())
-> T -> T -> FilePath -> Int -> sig y -> IO ExitCode
extended Handle -> sig y -> IO ()
write T
srcOpts T
dstOpts FilePath
fileName Int
sampleRate sig y
signal =
   forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
      (forall y (sig :: * -> *).
C y =>
T -> T -> FilePath -> Int -> sig y -> IO Handle
open T
srcOpts T
dstOpts FilePath
fileName Int
sampleRate sig y
signal)
      Handle -> IO ()
close
      (\(Handle
input,Handle
_,Handle
_,ProcessHandle
proc) ->
         IO ()
catchCtrlC forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
         Handle -> sig y -> IO ()
write Handle
input sig y
signal forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
         forall (m :: * -> *) a. Monad m => a -> m a
return ProcessHandle
proc)
   -- get exit code, e.g. when options were wrong
   forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ProcessHandle -> IO ExitCode
Proc.waitForProcess

{- |
The traversable functor @f@ might be 'Maybe' or '[]'.
It allows you to write to many files simultaneously
and returns the exit codes of all writing processes.
-}
manyExtended ::
   (Frame.C y, Trav.Traversable f) =>
   (f IO.Handle -> sig y -> IO ())
      {- ^ Writer routine -
           e.g. 'Sound.Sox.Signal.List.put'
           or 'Data.StorableVector.hPut' -} ->
   Option.T
      {- ^ source options, usually none -} ->
   Option.T
      {- ^ target options -} ->
   f FilePath ->
   Int
      {- ^ sample rate -} ->
   sig y ->
   IO (f ExitCode)
manyExtended :: forall y (f :: * -> *) (sig :: * -> *).
(C y, Traversable f) =>
(f Handle -> sig y -> IO ())
-> T -> T -> f FilePath -> Int -> sig y -> IO (f ExitCode)
manyExtended f Handle -> sig y -> IO ()
write T
srcOpts T
dstOpts f FilePath
fileNames Int
sampleRate sig y
signal =
   forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
      (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Trav.traverse
         (\FilePath
fileName -> forall y (sig :: * -> *).
C y =>
T -> T -> FilePath -> Int -> sig y -> IO Handle
open T
srcOpts T
dstOpts FilePath
fileName Int
sampleRate sig y
signal)
         f FilePath
fileNames)
      (forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
Fold.traverse_ Handle -> IO ()
close)
      (\f Handle
handles ->
         IO ()
catchCtrlC forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
         f Handle -> sig y -> IO ()
write (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Handle
input,Handle
_,Handle
_,ProcessHandle
_) -> Handle
input) f Handle
handles) sig y
signal forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
         forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Handle
_,Handle
_,Handle
_,ProcessHandle
proc) -> ProcessHandle
proc) f Handle
handles))
   -- get exit code, e.g. when options were wrong
   forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Trav.traverse ProcessHandle -> IO ExitCode
Proc.waitForProcess


type Handle = (IO.Handle, IO.Handle, IO.Handle, Proc.ProcessHandle)

open ::
   (Frame.C y) =>
   Option.T
      {- ^ source options, usually none -} ->
   Option.T
      {- ^ target options -} ->
   FilePath ->
   Int
      {- ^ sample rate -} ->
   sig y ->
   IO Handle
open :: forall y (sig :: * -> *).
C y =>
T -> T -> FilePath -> Int -> sig y -> IO Handle
open T
srcOpts T
dstOpts FilePath
fileName Int
sampleRate sig y
signal =
   FilePath
-> [FilePath]
-> Maybe FilePath
-> Maybe [(FilePath, FilePath)]
-> IO Handle
Proc.runInteractiveProcess FilePath
"sox"
      (T -> [FilePath]
Args.decons forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$
       T -> T
OptPriv.toArguments
         (forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$
          T
srcOpts forall a. a -> [a] -> [a]
:
          Int -> T
Option.numberOfChannels
             (forall y a (sig :: * -> *). (y -> a) -> sig y -> a
Frame.withSignal forall y. C y => y -> Int
Frame.numberOfChannels sig y
signal) forall a. a -> [a] -> [a]
:
          Int -> T
Option.sampleRate Int
sampleRate forall a. a -> [a] -> [a]
:
          T -> T
Option.format (forall y a (sig :: * -> *). (y -> a) -> sig y -> a
Frame.withSignal forall y. C y => y -> T
Frame.format sig y
signal) forall a. a -> [a] -> [a]
:
          []) forall a. a -> [a] -> [a]
:
       T
Args.pipe forall a. a -> [a] -> [a]
:
       T -> T
OptPriv.toArguments T
dstOpts forall a. a -> [a] -> [a]
:
       FilePath -> T
Args.fileName FilePath
fileName forall a. a -> [a] -> [a]
:
       [])
      forall a. Maybe a
Nothing forall a. Maybe a
Nothing

close :: Handle -> IO ()
close :: Handle -> IO ()
close (Handle
input,Handle
output,Handle
err,ProcessHandle
_proc) =
   forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Handle -> IO ()
IO.hClose [Handle
input, Handle
output, Handle
err]