module Sound.Sox.Write 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 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 write opts =
   extended write Option.none 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 write srcOpts dstOpts fileName sampleRate stream =
   bracket
      (Proc.runInteractiveProcess "sox"
          (Args.decons $ mconcat $
           OptPriv.toArguments
             (mconcat $
              srcOpts :
              Option.numberOfChannels
                 (Frame.withSignal Frame.numberOfChannels stream) :
              Option.sampleRate sampleRate :
              Option.format (Frame.withSignal Frame.format stream) :
              []) :
           Args.pipe :
           OptPriv.toArguments dstOpts :
           Args.fileName fileName :
           [])
          Nothing Nothing)
      (\(input,output,err,_proc) ->
          mapM_ IO.hClose [input, output, err])
      (\(input,_,_,proc) ->
         catchCtrlC >>
         write input stream >>
         return proc)
   -- get exit code, e.g. when options were wrong
   >>= Proc.waitForProcess