{-# LANGUAGE ImportQualifiedPost #-}
module Discord.Voice.Conduit
(
packInt16C
, packInt16CT
, unpackInt16C
, unpackInt16CT
, toMono
)
where
import Conduit
import Data.Bits ( shiftL, shiftR, (.|.) )
import Data.ByteString qualified as B
import Data.Int ( Int16 )
import Data.Word ( Word16, Word8 )
import Discord
packInt16C :: ConduitT B.ByteString Int16 (ResourceT DiscordHandler) ()
packInt16C :: ConduitT ByteString Int16 (ResourceT DiscordHandler) ()
packInt16C = Index ByteString
-> ConduitT ByteString ByteString (ResourceT DiscordHandler) ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq) =>
Index seq -> ConduitT seq seq m ()
chunksOfExactlyCE Index ByteString
2 ConduitT ByteString ByteString (ResourceT DiscordHandler) ()
-> ConduitT ByteString Int16 (ResourceT DiscordHandler) ()
-> ConduitT ByteString Int16 (ResourceT DiscordHandler) ()
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitT ByteString Int16 (ResourceT DiscordHandler) ()
loop
where
loop :: ConduitT ByteString Int16 (ResourceT DiscordHandler) ()
loop = (ByteString
-> ConduitT ByteString Int16 (ResourceT DiscordHandler) ())
-> ConduitT ByteString Int16 (ResourceT DiscordHandler) ()
forall (m :: * -> *) i o r.
Monad m =>
(i -> ConduitT i o m r) -> ConduitT i o m ()
awaitForever ((ByteString
-> ConduitT ByteString Int16 (ResourceT DiscordHandler) ())
-> ConduitT ByteString Int16 (ResourceT DiscordHandler) ())
-> (ByteString
-> ConduitT ByteString Int16 (ResourceT DiscordHandler) ())
-> ConduitT ByteString Int16 (ResourceT DiscordHandler) ()
forall a b. (a -> b) -> a -> b
$ \ByteString
bytes -> do
let [Word8
b1, Word8
b2] = ByteString -> [Word8]
B.unpack ByteString
bytes
Int16 -> ConduitT ByteString Int16 (ResourceT DiscordHandler) ()
forall (m :: * -> *) o i. Monad m => o -> ConduitT i o m ()
yield (Int16 -> ConduitT ByteString Int16 (ResourceT DiscordHandler) ())
-> Int16 -> ConduitT ByteString Int16 (ResourceT DiscordHandler) ()
forall a b. (a -> b) -> a -> b
$ (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Word16 -> Int16
forall a b. (a -> b) -> a -> b
$ (Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
shiftL (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b2 :: Word16) Int
8) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|. (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b1 :: Word16) :: Int16)
unpackInt16C :: ConduitT Int16 B.ByteString (ResourceT DiscordHandler) ()
unpackInt16C :: ConduitT Int16 ByteString (ResourceT DiscordHandler) ()
unpackInt16C = (Int16 -> ConduitT Int16 ByteString (ResourceT DiscordHandler) ())
-> ConduitT Int16 ByteString (ResourceT DiscordHandler) ()
forall (m :: * -> *) i o r.
Monad m =>
(i -> ConduitT i o m r) -> ConduitT i o m ()
awaitForever ((Int16 -> ConduitT Int16 ByteString (ResourceT DiscordHandler) ())
-> ConduitT Int16 ByteString (ResourceT DiscordHandler) ())
-> (Int16
-> ConduitT Int16 ByteString (ResourceT DiscordHandler) ())
-> ConduitT Int16 ByteString (ResourceT DiscordHandler) ()
forall a b. (a -> b) -> a -> b
$ \Int16
i ->
ByteString
-> ConduitT Int16 ByteString (ResourceT DiscordHandler) ()
forall (m :: * -> *) o i. Monad m => o -> ConduitT i o m ()
yield (ByteString
-> ConduitT Int16 ByteString (ResourceT DiscordHandler) ())
-> ByteString
-> ConduitT Int16 ByteString (ResourceT DiscordHandler) ()
forall a b. (a -> b) -> a -> b
$ [Word8] -> ByteString
B.pack
[ Int16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
i :: Word8
, Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Word8) -> Word16 -> Word8
forall a b. (a -> b) -> a -> b
$ Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
shiftR (Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
i :: Word16) Int
8 :: Word8
]
packInt16CT :: ConduitT B.ByteString (Int16, Int16) (ResourceT DiscordHandler) ()
packInt16CT :: ConduitT ByteString (Int16, Int16) (ResourceT DiscordHandler) ()
packInt16CT = Index ByteString
-> ConduitT ByteString ByteString (ResourceT DiscordHandler) ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq) =>
Index seq -> ConduitT seq seq m ()
chunksOfExactlyCE Index ByteString
4 ConduitT ByteString ByteString (ResourceT DiscordHandler) ()
-> ConduitT ByteString (Int16, Int16) (ResourceT DiscordHandler) ()
-> ConduitT ByteString (Int16, Int16) (ResourceT DiscordHandler) ()
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitT ByteString (Int16, Int16) (ResourceT DiscordHandler) ()
loop
where
loop :: ConduitT ByteString (Int16, Int16) (ResourceT DiscordHandler) ()
loop = (ByteString
-> ConduitT
ByteString (Int16, Int16) (ResourceT DiscordHandler) ())
-> ConduitT ByteString (Int16, Int16) (ResourceT DiscordHandler) ()
forall (m :: * -> *) i o r.
Monad m =>
(i -> ConduitT i o m r) -> ConduitT i o m ()
awaitForever ((ByteString
-> ConduitT
ByteString (Int16, Int16) (ResourceT DiscordHandler) ())
-> ConduitT
ByteString (Int16, Int16) (ResourceT DiscordHandler) ())
-> (ByteString
-> ConduitT
ByteString (Int16, Int16) (ResourceT DiscordHandler) ())
-> ConduitT ByteString (Int16, Int16) (ResourceT DiscordHandler) ()
forall a b. (a -> b) -> a -> b
$ \ByteString
bytes -> do
let [Word8
b1, Word8
b2, Word8
b3, Word8
b4] = ByteString -> [Word8]
B.unpack ByteString
bytes
let left :: Int16
left = (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Word16 -> Int16
forall a b. (a -> b) -> a -> b
$ (Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
shiftL (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b2 :: Word16) Int
8) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|. (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b1 :: Word16) :: Int16)
let right :: Int16
right = (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Word16 -> Int16
forall a b. (a -> b) -> a -> b
$ (Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
shiftL (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b4 :: Word16) Int
8) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|. (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b3 :: Word16) :: Int16)
(Int16, Int16)
-> ConduitT ByteString (Int16, Int16) (ResourceT DiscordHandler) ()
forall (m :: * -> *) o i. Monad m => o -> ConduitT i o m ()
yield (Int16
left, Int16
right)
unpackInt16CT :: ConduitT (Int16, Int16) B.ByteString (ResourceT DiscordHandler) ()
unpackInt16CT :: ConduitT (Int16, Int16) ByteString (ResourceT DiscordHandler) ()
unpackInt16CT = ((Int16, Int16)
-> ConduitT
(Int16, Int16) ByteString (ResourceT DiscordHandler) ())
-> ConduitT (Int16, Int16) ByteString (ResourceT DiscordHandler) ()
forall (m :: * -> *) i o r.
Monad m =>
(i -> ConduitT i o m r) -> ConduitT i o m ()
awaitForever (((Int16, Int16)
-> ConduitT
(Int16, Int16) ByteString (ResourceT DiscordHandler) ())
-> ConduitT
(Int16, Int16) ByteString (ResourceT DiscordHandler) ())
-> ((Int16, Int16)
-> ConduitT
(Int16, Int16) ByteString (ResourceT DiscordHandler) ())
-> ConduitT (Int16, Int16) ByteString (ResourceT DiscordHandler) ()
forall a b. (a -> b) -> a -> b
$ \(Int16
l, Int16
r) ->
ByteString
-> ConduitT (Int16, Int16) ByteString (ResourceT DiscordHandler) ()
forall (m :: * -> *) o i. Monad m => o -> ConduitT i o m ()
yield (ByteString
-> ConduitT
(Int16, Int16) ByteString (ResourceT DiscordHandler) ())
-> ByteString
-> ConduitT (Int16, Int16) ByteString (ResourceT DiscordHandler) ()
forall a b. (a -> b) -> a -> b
$ [Word8] -> ByteString
B.pack
[ Int16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
l :: Word8
, Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Word8) -> Word16 -> Word8
forall a b. (a -> b) -> a -> b
$ Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
shiftR (Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
l :: Word16) Int
8 :: Word8
, Int16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
r :: Word8
, Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Word8) -> Word16 -> Word8
forall a b. (a -> b) -> a -> b
$ Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
shiftR (Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
r :: Word16) Int
8 :: Word8
]
toMono :: ConduitT (Int16, Int16) (Int16, Int16) (ResourceT DiscordHandler) ()
toMono :: ConduitT
(Int16, Int16) (Int16, Int16) (ResourceT DiscordHandler) ()
toMono = ((Int16, Int16)
-> ConduitT
(Int16, Int16) (Int16, Int16) (ResourceT DiscordHandler) ())
-> ConduitT
(Int16, Int16) (Int16, Int16) (ResourceT DiscordHandler) ()
forall (m :: * -> *) i o r.
Monad m =>
(i -> ConduitT i o m r) -> ConduitT i o m ()
awaitForever (((Int16, Int16)
-> ConduitT
(Int16, Int16) (Int16, Int16) (ResourceT DiscordHandler) ())
-> ConduitT
(Int16, Int16) (Int16, Int16) (ResourceT DiscordHandler) ())
-> ((Int16, Int16)
-> ConduitT
(Int16, Int16) (Int16, Int16) (ResourceT DiscordHandler) ())
-> ConduitT
(Int16, Int16) (Int16, Int16) (ResourceT DiscordHandler) ()
forall a b. (a -> b) -> a -> b
$ \(Int16
l, Int16
r) -> do
let avg :: Int16
avg = Int16
l Int16 -> Int16 -> Int16
forall a. Integral a => a -> a -> a
`div` Int16
2 Int16 -> Int16 -> Int16
forall a. Num a => a -> a -> a
+ Int16
r Int16 -> Int16 -> Int16
forall a. Integral a => a -> a -> a
`div` Int16
2
(Int16, Int16)
-> ConduitT
(Int16, Int16) (Int16, Int16) (ResourceT DiscordHandler) ()
forall (m :: * -> *) o i. Monad m => o -> ConduitT i o m ()
yield (Int16
avg, Int16
avg)