Skip to content

Commit

Permalink
Add a regression test for vincenthz#17
Browse files Browse the repository at this point in the history
  • Loading branch information
enolan committed Jun 7, 2016
1 parent f7eb2c2 commit 693ad8a
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 1 deletion.
1 change: 1 addition & 0 deletions encoding/asn1-encoding.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ Test-Suite tests-asn1-encoding
, mtl
, tasty
, tasty-quickcheck
, tasty-hunit
, asn1-types
, asn1-encoding
, hourglass
Expand Down
16 changes: 15 additions & 1 deletion encoding/tests/Tests.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck
import Test.Tasty

import Control.Applicative
import Data.ASN1.Error
import Data.ASN1.Get (runGet, Result(..))
import Data.ASN1.BitArray
import Data.ASN1.Prim
Expand Down Expand Up @@ -197,10 +200,21 @@ prop_asn1_der_marshalling_id v = (decodeASN1 DER . encodeASN1 DER) v `assertEq`
| got /= expected = error ("got: " ++ show got ++ " expected: " ++ show expected)
| otherwise = True

negativeLengthHdr :: B.ByteString
negativeLengthHdr =
"0\157\&000000000000000000000\252\&0000000\146\&0000000000000000000000000000000000000000000000000\STX\175\&000000000000000000000000000000000000000\222\&00000000"

negativeLengthFails :: TestTree
negativeLengthFails = testCase "negativeLengthFails" $
case decodeASN1' DER negativeLengthHdr of
Left (ParsingHeaderFail _) -> return ()
_ ->
assertFailure "Parsing header with invalid length didn't throw an error"

marshallingTests = testGroup "Marshalling"
[ testProperty "Header" prop_header_marshalling_id
, testProperty "Event" prop_event_marshalling_id
, testProperty "DER" prop_asn1_der_marshalling_id
]

main = defaultMain $ testGroup "asn1-encoding" [marshallingTests]
main = defaultMain $ testGroup "asn1-encoding" [marshallingTests,negativeLengthFails]

0 comments on commit 693ad8a

Please sign in to comment.