{-# LINE 1 "src/Sound/Pulse/ChannelPosition.hsc" #-} {- {-# LINE 2 "src/Sound/Pulse/ChannelPosition.hsc" #-} Copyright 2016 Markus Ongyerth This file is part of pulseaudio-hs. Monky is free software: you can redistribute it and/or modify it under the terms of the GNU Lesser General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. Monky is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more details. You should have received a copy of the GNU Lesser General Public License along with pulseaudio-hs. If not, see <http://www.gnu.org/licenses/>. -} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RecordWildCards #-} {-| Module : sound.Pulse.ChannelPosition Description : Provides types for PA_CHANNEL_POSITION and pa_channel_map. Maintianer : ongy Stability : experimental -} module Sound.Pulse.ChannelPosition ( ChannelPosition(..) , ChannelMap(..) ) where {-# LINE 35 "src/Sound/Pulse/ChannelPosition.hsc" #-} {-# LINE 36 "src/Sound/Pulse/ChannelPosition.hsc" #-} import Data.List (genericLength) import Data.Word (Word8, Word) import Foreign.Ptr (plusPtr) -- #{ptr ...} needs this import Foreign.Storable (Storable(..)) import Sound.Pulse.Def (ChannelPosition(..), channelPositionFromInt, channelPositionToInt) -- |The Type for ChannelMaps newtype ChannelMap = ChannelMap [ChannelPosition] deriving (Eq, Show) instance Storable ChannelMap where sizeOf _ = (132) {-# LINE 49 "src/Sound/Pulse/ChannelPosition.hsc" #-} alignment _ = (4) {-# LINE 50 "src/Sound/Pulse/ChannelPosition.hsc" #-} peek p = do size :: Word8 <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p {-# LINE 52 "src/Sound/Pulse/ChannelPosition.hsc" #-} ints <- mapM (peekElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 4) p) . fromIntegral ) [0..size - 1] {-# LINE 53 "src/Sound/Pulse/ChannelPosition.hsc" #-} return . ChannelMap $ map channelPositionFromInt ints poke p (ChannelMap pos) = do (\hsc_ptr -> pokeByteOff hsc_ptr 0) p $ (genericLength pos :: Word8) {-# LINE 56 "src/Sound/Pulse/ChannelPosition.hsc" #-} let indexd = zip [0..] (map channelPositionToInt pos) mapM_ (uncurry (pokeElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 4) p))) indexd {-# LINE 58 "src/Sound/Pulse/ChannelPosition.hsc" #-}