[Haskell-cafe] SOX - play simple

Antoine Latter aslatter at gmail.com
Thu Nov 29 14:11:39 CET 2012


The example is assuming you have an import statement like this:

import qualified Sound.Sox.Option.Format as Option

On Wed, Nov 28, 2012 at 8:48 AM, Gary Klindt <gary.klindt at googlemail.com> wrote:
> Dear Cafe,
>
> after installing the Sox library
> (cabal install sox)
> I wanted to let run a minimal example from
> http://hackage.haskell.org/packages/archive/sox/0.2.2.2/doc/html/Sound-Sox-Play.html
>
>
> module Main where
>
> import Sound.Sox.Play
> import Sound.Sox.Signal.List
> --import Sound.Sox.Option.Format
>
> import Data.Int
>
> main = do
>     simple Sound.Sox.Signal.List.put
>            Option.none
>            11025
>            (iterate (1000+) (0::Data.Int.Int16))
>
> in this version, I get the error:
>  Not in scope: `Option.none'
>
> So, I imported Sound.Sox.Option.Format, because there is a none with the
> right type. I also changed Option.none to none.
>
> Then the program compiles and I get the runtime error:
> fd:4: hClose: resource vanished (Broken pipe)
>
>
> What is wrong here?
>
> I appreciate your help!
>
> Best regards, Gary
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list