{-# LINE 1 "src/Sound/Pulse/SampleSpec.hsc" #-} {- {-# LINE 2 "src/Sound/Pulse/SampleSpec.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 RecordWildCards #-} {-| Module : Sound.Pulse.SampleSpec Description : provides the time type used for pa_sample_spec. Maintianer : ongy Stability : experimental -} module Sound.Pulse.SampleSpec ( SampleFormat(..) , SampleSpec(..) ) where {-# LINE 35 "src/Sound/Pulse/SampleSpec.hsc" #-} {-# LINE 36 "src/Sound/Pulse/SampleSpec.hsc" #-} import Control.Applicative ((<$>), (<*>)) import Sound.Pulse.Def (SampleFormat(..), sampleFormatFromInt, sampleFormatToInt) import Foreign.Storable (Storable(..)) import Data.Word (Word32, Word8, Word) -- |The pa_sample_spec type for Haskell. data SampleSpec = SampleSpec { ssFormat :: SampleFormat , ssRate :: Word32 , ssChannels :: Word8 } deriving (Eq, Show) instance Storable SampleSpec where sizeOf _ = (12) {-# LINE 52 "src/Sound/Pulse/SampleSpec.hsc" #-} alignment _ = (4) {-# LINE 53 "src/Sound/Pulse/SampleSpec.hsc" #-} peek p = SampleSpec <$> (sampleFormatFromInt <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) p) {-# LINE 55 "src/Sound/Pulse/SampleSpec.hsc" #-} <*> (\hsc_ptr -> peekByteOff hsc_ptr 4) p {-# LINE 56 "src/Sound/Pulse/SampleSpec.hsc" #-} <*> (\hsc_ptr -> peekByteOff hsc_ptr 8) p {-# LINE 57 "src/Sound/Pulse/SampleSpec.hsc" #-} poke p (SampleSpec {..}) = do (\hsc_ptr -> pokeByteOff hsc_ptr 0) p $ sampleFormatToInt ssFormat {-# LINE 59 "src/Sound/Pulse/SampleSpec.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 4) p ssRate {-# LINE 60 "src/Sound/Pulse/SampleSpec.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 8) p ssChannels {-# LINE 61 "src/Sound/Pulse/SampleSpec.hsc" #-}