{- This data type can be used as sample type for stereo signals. -} module Sound.Sox.Frame.Stereo (T, left, right, cons, ) where import qualified Sound.Sox.Frame as Frame import Control.Monad (liftM2, ) import Foreign.Storable (Storable (..), ) import qualified Sound.Sox.StorableUtility as Store data T a = Cons {left, right :: !a} {-# INLINE cons #-} cons :: a -> a -> T a cons = Cons instance Functor T where {-# INLINE fmap #-} fmap f (Cons l r) = Cons (f l) (f r) -- cf. StorableInstances instance (Storable a) => Storable (T a) where sizeOf y = Store.sizeOfArray 2 $ left y alignment y = alignment $ left y peek ptr = Store.run ptr $ liftM2 Cons Store.peekNext Store.peekNext poke ptr (Cons l r) = Store.run ptr $ do Store.pokeNext l Store.pokeNext r instance Frame.C a => Frame.C (T a) where numberOfChannels y = 2 * Frame.numberOfChannels (left y) format y = Frame.format (left y)