Skip to content

Commit 478a22a

Browse files
authored
Merge pull request #7 from yutotakano/add-detailed-docs
Add module-level docs to files and add all function Haddocks
2 parents 51495fe + 5aa9e20 commit 478a22a

File tree

6 files changed

+263
-92
lines changed

6 files changed

+263
-92
lines changed

src/Codec/Audio/Opus/Decoder.hs

Lines changed: 27 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
{-# LANGUAGE FlexibleContexts #-}
2-
2+
-- | This module contains the high-level API for decoding Opus audio.
33
module Codec.Audio.Opus.Decoder
44
( -- * Decoder
55
Decoder, OpusException(..)
@@ -22,11 +22,12 @@ import qualified Data.ByteString as BS
2222
import qualified Data.ByteString.Lazy as BL
2323
import Foreign
2424

25-
-- | Decoder State
25+
-- | Decoder. Internally, it holds a pointer to the libopus decoder state and
26+
-- a pointer to the (potential) last Opus error code.
2627
newtype Decoder = Decoder (ForeignPtr DecoderT, ForeignPtr ErrorCode)
2728
deriving (Eq, Ord, Show)
2829

29-
-- | allocates and initializes a decoder state.
30+
-- | Allocates and initializes a decoder.
3031
opusDecoderCreate :: (HasDecoderConfig cfg, MonadIO m) => cfg -> m Decoder
3132
opusDecoderCreate cfg = liftIO $ do
3233
let cs = if isStereo then 2 else 1
@@ -38,14 +39,16 @@ opusDecoderCreate cfg = liftIO $ do
3839
let enc = Decoder (d', err)
3940
opusLastError enc >>= maybe (pure enc) throwM
4041

41-
42-
4342
-- | Decode an Opus frame.
4443
opusDecode
4544
:: (HasDecoderStreamConfig cfg, MonadIO m)
46-
=> Decoder -- ^ 'Decoder' state
47-
-> cfg -- ^ max data bytes
48-
-> ByteString -- ^ input signal (interleaved if 2 channels)
45+
=> Decoder
46+
-- ^ 'Decoder' state
47+
-> cfg
48+
-- ^ The stream configuration that specifies the frame size, whether FEC is
49+
-- enabled, and the decoder configuration (sampling rate, channels).
50+
-> ByteString
51+
-- ^ Input signal (interleaved if 2 channels)
4952
-> m ByteString
5053
opusDecode d cfg i =
5154
let fs = cfg ^. deStreamFrameSize
@@ -70,36 +73,43 @@ opusDecode d cfg i =
7073
-- but CStringLen expects a CChar which is Int8
7174
BS.packCStringLen $ (castPtr os, (fromIntegral l) * 2 * chans)
7275

76+
-- | Decode an Opus frame, returning a lazy 'BL.ByteString'.
7377
opusDecodeLazy :: (HasDecoderStreamConfig cfg, MonadIO m)
74-
=> Decoder -- ^ 'Decoder' state
78+
=> Decoder
79+
-- ^ 'Decoder' state
7580
-> cfg
76-
-> ByteString -- ^ input signal (interleaved if 2 channels)
81+
-- ^ The stream configuration that specifies the frame size, whether FEC is
82+
-- enabled, and the decoder configuration (sampling rate, channels).
83+
-> ByteString
84+
-- ^ Input signal (interleaved if 2 channels)
7785
-> m BL.ByteString
7886
opusDecodeLazy d cfg = fmap BL.fromStrict . opusDecode d cfg
7987

88+
-- | For use with 'ResourceT' or any other monad that implements 'MonadResource'.
89+
-- Safely allocate a 'Decoder' that will be freed upon exiting the monad, an
90+
-- exception, or an explicit call to 'Control.Monad.Trans.Resource.release'.
8091
withOpusDecoder :: (HasDecoderConfig cfg) => MonadResource m
8192
=> cfg
8293
-> (Decoder -> IO ())
8394
-> m Decoder
8495
withOpusDecoder cfg a =
8596
snd <$> allocate (opusDecoderCreate cfg) a
8697

87-
88-
-- | Frees an 'Decoder'. Is normaly called automaticly
89-
-- when 'Decoder' gets out of scope
98+
-- | Frees an 'Decoder'.
9099
opusDecoderDestroy :: MonadIO m => Decoder -> m ()
91100
opusDecoderDestroy (Decoder (d, err)) = liftIO $
92101
finalizeForeignPtr d >> finalizeForeignPtr err
93102

94-
95-
-- | get last error from decoder
103+
-- | Get the last error from decoder.
96104
opusLastError :: MonadIO m => Decoder -> m (Maybe OpusException)
97105
opusLastError (Decoder (_, fp)) =
98106
liftIO $ (^? _ErrorCodeException) <$> withForeignPtr fp peek
99107

108+
-- | An 'DecoderAction' is an IO action that uses a 'DecoderT' for its operation.
100109
type DecoderAction a = Ptr DecoderT -> IO a
101110

102-
-- | Run an 'DecoderAction'.
111+
-- | Run a 'DecoderAction' using a 'Decoder', returning either 'OpusException'
112+
-- for errors or the result of the action.
103113
withDecoder' :: MonadIO m =>
104114
Decoder -> DecoderAction a -> m (Either OpusException a)
105115
withDecoder' e@(Decoder (fp_a, _)) m = liftIO $
@@ -108,7 +118,7 @@ withDecoder' e@(Decoder (fp_a, _)) m = liftIO $
108118
le <- opusLastError e
109119
pure $ maybe (Right r) Left le
110120

111-
-- | Run an 'DecoderAction'. Might throw an 'OpusException'
121+
-- | Run a 'DecoderAction'. Might throw an 'OpusException' if the action fails.
112122
runDecoderAction :: (MonadIO m, MonadThrow m) =>
113123
Decoder -> DecoderAction a -> m a
114124
runDecoderAction d m = withDecoder' d m >>= either throwM pure

src/Codec/Audio/Opus/Decoder/Conduit.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
-- | Conduit interface for decoding audio data with Opus.
12
module Codec.Audio.Opus.Decoder.Conduit
23
( decoderC, decoderLazyC
34
, decoderSink
@@ -11,21 +12,26 @@ import qualified Data.ByteString.Lazy as BL
1112
import Data.Conduit.Combinators
1213
import Prelude (($))
1314

15+
-- | Decode audio data with Opus.
1416
decoderC :: (HasDecoderStreamConfig cfg, MonadResource m) =>
1517
cfg -> ConduitT ByteString ByteString m ()
1618
decoderC cfg = withDecoder (cfg ^. deStreamDecoderConfig) $
1719
\d -> mapM (opusDecode d cfg)
1820

21+
-- | Decode lazy bytestring audio data with Opus.
1922
decoderLazyC :: (HasDecoderStreamConfig cfg, MonadResource m) =>
2023
cfg -> ConduitT ByteString BL.ByteString m ()
2124
decoderLazyC cfg = withDecoder (cfg ^. deStreamDecoderConfig) $
2225
\d -> mapM (opusDecodeLazy d cfg)
2326

27+
-- | A sink to decode audio data with Opus and return a lazy bytestring of the
28+
-- whole stream.
2429
decoderSink :: (HasDecoderStreamConfig cfg, MonadResource m) =>
2530
cfg -> ConduitT ByteString o m BL.ByteString
2631
decoderSink cfg = withDecoder (cfg ^. deStreamDecoderConfig) $
2732
\d -> foldMapM (opusDecodeLazy d cfg)
2833

34+
-- | Run a conduit that uses a decoder with the given configuration.
2935
withDecoder :: (HasDecoderConfig cfg, MonadResource m) =>
3036
cfg -> (Decoder -> ConduitT i o m r) -> ConduitT i o m r
3137
withDecoder cfg = bracketP (opusDecoderCreate cfg) opusDecoderDestroy

src/Codec/Audio/Opus/Encoder.hs

Lines changed: 28 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
{-# LANGUAGE FlexibleContexts #-}
2-
2+
-- | This module contains the high-level API for encoding Opus audio.
33
module Codec.Audio.Opus.Encoder
44
( -- * Encoder
55
Encoder, OpusException(..)
@@ -22,11 +22,12 @@ import qualified Data.ByteString as BS
2222
import qualified Data.ByteString.Lazy as BL
2323
import Foreign
2424

25-
-- | Encoder State
25+
-- | Encoder. Internally, it holds a pointer to the libopus encoder state and
26+
-- a pointer to the (potential) last Opus error code.
2627
newtype Encoder = Encoder (ForeignPtr EncoderT, ForeignPtr ErrorCode)
2728
deriving (Eq, Ord, Show)
2829

29-
-- | allocates and initializes an encoder state.
30+
-- | Allocates and initializes an encoder.
3031
opusEncoderCreate :: (HasEncoderConfig cfg, MonadIO m) => cfg -> m Encoder
3132
opusEncoderCreate cfg = liftIO $ do
3233
let cs = if isStereo then 2 else 1
@@ -39,14 +40,16 @@ opusEncoderCreate cfg = liftIO $ do
3940
let enc = Encoder (e', err)
4041
opusLastError enc >>= maybe (pure enc) throwM
4142

42-
43-
4443
-- | Encode an Opus frame.
4544
opusEncode
4645
:: (HasStreamConfig cfg, MonadIO m)
47-
=> Encoder -- ^ 'Encoder' state
48-
-> cfg -- ^ max data bytes
49-
-> ByteString -- ^ input signal (interleaved if 2 channels)
46+
=> Encoder
47+
-- ^ 'Encoder' state
48+
-> cfg
49+
-- ^ The stream configuration that specifies the frame size, the output size,
50+
-- and the encoder configuration (sampling rate, channels, coding mode).
51+
-> ByteString
52+
-- ^ Input signal (interleaved if 2 channels)
5053
-> m ByteString
5154
opusEncode e cfg i =
5255
let fs = cfg ^. streamFrameSize
@@ -62,13 +65,22 @@ opusEncode e cfg i =
6265
if l < 0 then throwM OpusInvalidPacket else
6366
BS.packCStringLen ol
6467

68+
-- | Encode an Opus frame. Returns a lazy 'BL.ByteString'.
6569
opusEncodeLazy :: (HasStreamConfig cfg, MonadIO m)
66-
=> Encoder -- ^ 'Encoder' state
70+
=> Encoder
71+
-- ^ 'Encoder' state
6772
-> cfg
68-
-> ByteString -- ^ input signal (interleaved if 2 channels)
73+
-- ^ The stream configuration that specifies the frame size, the output size,
74+
-- and the encoder configuration (sampling rate, channels, coding mode).
75+
-> ByteString
76+
-- ^ Input signal (interleaved if 2 channels)
6977
-> m BL.ByteString
7078
opusEncodeLazy e cfg = fmap BL.fromStrict . opusEncode e cfg
7179

80+
81+
-- | For use with 'ResourceT' or any other monad that implements 'MonadResource'.
82+
-- Safely allocate an 'Encoder' that will be freed upon exiting the monad, an
83+
-- exception, or an explicit call to 'Control.Monad.Trans.Resource.release'.
7284
withOpusEncoder :: (HasEncoderConfig cfg) => MonadResource m
7385
=> cfg
7486
-> (Encoder -> IO ())
@@ -77,21 +89,22 @@ withOpusEncoder cfg a =
7789
snd <$> allocate (opusEncoderCreate cfg) a
7890

7991

80-
-- | Frees an 'Encoder'. Is normaly called automaticly
81-
-- when 'Encoder' gets out of scope
92+
-- | Frees an 'Encoder'.
8293
opusEncoderDestroy :: MonadIO m => Encoder -> m ()
8394
opusEncoderDestroy (Encoder (e, err)) = liftIO $
8495
finalizeForeignPtr e >> finalizeForeignPtr err
8596

8697

87-
-- | get last error from encoder
98+
-- | Get the last error from the encoder.
8899
opusLastError :: MonadIO m => Encoder -> m (Maybe OpusException)
89100
opusLastError (Encoder (_, fp)) =
90101
liftIO $ (^? _ErrorCodeException) <$> withForeignPtr fp peek
91102

103+
-- | An 'EncoderAction' is an IO action that uses a 'EncoderT' for its operation.
92104
type EncoderAction a = Ptr EncoderT -> IO a
93105

94-
-- | Run an 'EncoderAction'.
106+
-- | Run an 'EncoderAction' using an 'Encoder', returning either 'OpusException'
107+
-- for errors or the result of the action.
95108
withEncoder' :: MonadIO m =>
96109
Encoder -> EncoderAction a -> m (Either OpusException a)
97110
withEncoder' e@(Encoder (fp_a, _)) m = liftIO $
@@ -100,7 +113,7 @@ withEncoder' e@(Encoder (fp_a, _)) m = liftIO $
100113
le <- opusLastError e
101114
pure $ maybe (Right r) Left le
102115

103-
-- | Run an 'EncoderAction'. Might throw an 'OpusException'
116+
-- | Run an 'EncoderAction'. Might throw an 'OpusException' if the action fails.
104117
runEncoderAction :: (MonadIO m, MonadThrow m) =>
105118
Encoder -> EncoderAction a -> m a
106119
runEncoderAction e m = withEncoder' e m >>= either throwM pure

src/Codec/Audio/Opus/Encoder/Conduit.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
-- | Conduit interface for encoding audio data with Opus.
12
module Codec.Audio.Opus.Encoder.Conduit
23
( encoderC, encoderLazyC
34
, encoderSink
@@ -11,21 +12,26 @@ import qualified Data.ByteString.Lazy as BL
1112
import Data.Conduit.Combinators
1213
import Prelude (($))
1314

15+
-- | Encode audio data with Opus.
1416
encoderC :: (HasStreamConfig cfg, MonadResource m) =>
1517
cfg -> ConduitT ByteString ByteString m ()
1618
encoderC cfg = withEncoder (cfg ^. streamConfig) $
1719
\e -> mapM (opusEncode e cfg)
1820

21+
-- | Encode lazy bytestring audio data with Opus.
1922
encoderLazyC :: (HasStreamConfig cfg, MonadResource m) =>
2023
cfg -> ConduitT ByteString BL.ByteString m ()
2124
encoderLazyC cfg = withEncoder (cfg ^. streamConfig) $
2225
\e -> mapM (opusEncodeLazy e cfg)
2326

27+
-- | A sink to encode audio data with Opus and return a lazy bytestring of the
28+
-- whole stream.
2429
encoderSink :: (HasStreamConfig cfg, MonadResource m) =>
2530
cfg -> ConduitT ByteString o m BL.ByteString
2631
encoderSink cfg = withEncoder (cfg ^. streamConfig) $
2732
\e -> foldMapM (opusEncodeLazy e cfg)
2833

34+
-- | Run a conduit that uses an encoder with the given configuration.
2935
withEncoder :: (HasEncoderConfig cfg, MonadResource m) =>
3036
cfg -> (Encoder -> ConduitT i o m r) -> ConduitT i o m r
3137
withEncoder cfg = bracketP (opusEncoderCreate cfg) opusEncoderDestroy

0 commit comments

Comments
 (0)