module Sound.Frame.Stereo (
T, left, right, cons, map,
Channel(..), select,
interleave, sequence, liftApplicative,
) where
import qualified Sound.Frame as Frame
import qualified Data.Traversable as Trav
import qualified Data.Foldable as Fold
import Control.Applicative (Applicative, pure, (<*>), liftA2, )
import Control.Monad (liftM2, )
import Foreign.Storable (Storable (..), )
import Foreign.Ptr (Ptr, castPtr, )
import Test.QuickCheck (Arbitrary(arbitrary), )
import Prelude hiding (Either(Left, Right), map, sequence, )
data T a = Cons {left, right :: !a}
deriving (Eq)
instance Show a => Show (T a) where
showsPrec p x =
showParen (p >= 10)
(showString "Stereo.cons " . showsPrec 11 (left x) .
showString " " . showsPrec 11 (right x))
instance (Arbitrary a) => Arbitrary (T a) where
arbitrary = liftM2 cons arbitrary arbitrary
cons :: a -> a -> T a
cons = Cons
map :: (a -> b) -> T a -> T b
map f (Cons l r) = Cons (f l) (f r)
data Channel = Left | Right
select :: T a -> Channel -> a
select x c =
case c of
Left -> left x
Right -> right x
interleave :: (T a, T b) -> T (a,b)
interleave = uncurry (liftA2 (,))
sequence :: (Functor f) => f (T a) -> T (f a)
sequence x = cons (fmap left x) (fmap right x)
liftApplicative ::
(Applicative f) =>
(f a -> f b) -> f (T a) -> f (T b)
liftApplicative proc =
Trav.sequenceA . fmap proc . sequence
instance Functor T where
fmap = map
instance Applicative T where
pure a = Cons a a
Cons fl fr <*> Cons l r = Cons (fl l) (fr r)
instance Fold.Foldable T where
foldMap = Trav.foldMapDefault
instance Trav.Traversable T where
sequenceA ~(Cons l r) = liftA2 Cons l r
castToElemPtr :: Ptr (T a) -> Ptr a
castToElemPtr = castPtr
instance (Storable a) => Storable (T a) where
sizeOf ~(Cons l r) =
sizeOf l + mod ( sizeOf l) (alignment r) + sizeOf r
alignment ~(Cons l _) = alignment l
poke p (Cons l r) =
let q = castToElemPtr p
in poke q l >> pokeElemOff q 1 r
peek p =
let q = castToElemPtr p
in liftM2 Cons
(peek q) (peekElemOff q 1)
instance Frame.C a => Frame.C (T a) where
numberOfChannels y = 2 * Frame.numberOfChannels (left y)
sizeOfElement = Frame.sizeOfElement . left