Skip to content

Commit

Permalink
add DecoderSpec
Browse files Browse the repository at this point in the history
  • Loading branch information
sigrdrifa committed Dec 26, 2023
1 parent be5eb90 commit c7b4e9e
Show file tree
Hide file tree
Showing 4 changed files with 16 additions and 21 deletions.
20 changes: 15 additions & 5 deletions test/DecodeSpec.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,13 @@
module DecodeSpec where
import Test.Hspec (Spec, shouldBe, describe, context, it)
import Data.Word (Word64)
import Stego.Common (StegoParams(StegoParams), EncodingType (LsbEncoding))
import Stego.Decode.Decoder (newDecoder)

import Command.DecodeCmd (doDecodeFramesWithDecoder)
import Data.Text.Encoding (encodeUtf8)
import Data.Int (Int16)
import qualified Data.Text as T
import Data.Text.Encoding (encodeUtf8)
import Data.Word (Word64)
import Stego.Common (EncodingType(LsbEncoding), StegoParams(StegoParams))
import Stego.Decode.Decoder (newDecoder, DecoderResult (SkippedFrame))
import Test.Hspec (Spec, context, describe, it, shouldBe)

spec :: Spec
spec = do
Expand All @@ -18,3 +20,11 @@ spec = do
decoder <- newDecoder stegoParams
result <- doDecodeFramesWithDecoder decoder []
result `shouldBe` []
context "when passing it frames that are below the cutoff threshold" $
it "should return an encode result that skipped all frames" $ do
let rawSamples :: [Int16] = [0 | i <- [0 .. 128]]
let frame = (0, rawSamples)
let frames = [frame]
decoder <- newDecoder stegoParams
result <- doDecodeFramesWithDecoder decoder frames
result `shouldBe` [SkippedFrame frame]
15 changes: 0 additions & 15 deletions test/EncodeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,18 +57,3 @@ spec =
encoder <- newEncoder stegoParams
result <- doEncodeFramesWithEncoder encoder frames
result `shouldBe` [SkippedFrame frame]
context "when passing it frames from the sample1.wav testfile" $
it "should return an encode result that verified 7 of the frames" $ do
let inputFile = "test/corpus/sample1.wav"
audio <- runExceptT (waveAudioFromFile inputFile)
case audio of
Left err -> err `shouldSatisfy` (not . null)
Right wa -> do
let frames = audioFrames wa
encoder <- newEncoder stegoParams
result <- doEncodeFramesWithEncoder encoder frames
let (DRS total verified unverified skipped) = getResultStats result
total `shouldBe` 18
verified `shouldBe` 7
unverified `shouldBe` 0
skipped `shouldBe` 11
2 changes: 1 addition & 1 deletion test/RealTimeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ spec =
describe "encoding and decoding with the real-time flag set" $ do
context "when passing it an encode command targeting the sample1.wav test file" $
it "should successfully decode the first time within the time window, and then fail the second time" $ do
let inputFile = "test/corpus/sample1.wav"
let inputFile = "test/corpus/sample1_rt.wav"
let outputFile = "test/output/sample1_rt_out.wav"
let secret = "21ø!2312422mmsfiuetest#@@1@sasf//"
let encodeCmd = Encode secret 5 inputFile outputFile
Expand Down
Binary file not shown.

0 comments on commit c7b4e9e

Please sign in to comment.