Skip to content

Commit 446f7df

Browse files
fixed infinite loop caused by incorrect defintion of SomeJSRuntimeException
1 parent b5c8458 commit 446f7df

File tree

3 files changed

+15
-6
lines changed

3 files changed

+15
-6
lines changed

quickjs-hs.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
cabal-version: 1.12
22
name: quickjs-hs
3-
version: 0.1.2.2
3+
version: 0.1.2.3
44
homepage: https://github.com/goodlyrottenapple/quickjs-hs#readme
55
bug-reports: https://github.com/goodlyrottenapple/quickjs-hs/issues
66
author: Sam Balco

src/Quickjs/Error.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -18,10 +18,7 @@ data SomeJSRuntimeException = forall e . Exception e => SomeJSRuntimeException e
1818
instance Show SomeJSRuntimeException where
1919
show (SomeJSRuntimeException e) = show e
2020

21-
instance Exception SomeJSRuntimeException where
22-
toException = jsRuntimeExceptionToException
23-
fromException = jsRuntimeExceptionFromException
24-
21+
instance Exception SomeJSRuntimeException
2522

2623
jsRuntimeExceptionToException :: Exception e => e -> SomeException
2724
jsRuntimeExceptionToException = toException . SomeJSRuntimeException

test/Spec.hs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
2+
{-# LANGUAGE LambdaCase #-}
13
{-# LANGUAGE OverloadedStrings #-}
24

35
module Main where
@@ -10,18 +12,27 @@ import qualified Test.QuickCheck as QC
1012
import qualified Test.QuickCheck.Monadic as QC
1113
import Data.Aeson (Value(..))
1214
import Control.Monad.IO.Class (liftIO)
13-
import Control.Monad.Catch (SomeException, MonadCatch(..))
15+
import Control.Monad.Catch (try, SomeException, MonadCatch(..))
1416
import Data.Text (pack)
1517
import qualified Data.HashMap.Strict as HM
1618
import qualified Data.Vector as V
1719
import Quickjs
20+
import Test.HUnit (assertFailure)
21+
import Quickjs.Error (SomeJSRuntimeException)
1822

1923

2024
eval_1_plus_2 :: Assertion
2125
eval_1_plus_2 = quickjsMultithreaded $ do
2226
v <- eval "1 + 2;"
2327
liftIO $ v @?= Number 3
2428

29+
30+
eval_throw :: Assertion
31+
eval_throw = quickjsMultithreaded $
32+
try (eval "throw 'Error'") >>= \case
33+
Left (_ :: SomeJSRuntimeException) -> return ()
34+
Right _ -> liftIO $ assertFailure "should fail with an Exception..."
35+
2536
genText = do
2637
k <- QC.choose (0,200)
2738
pack <$> QC.vectorOf k (QC.oneof $ map pure $ ['0'..'~'])
@@ -63,6 +74,7 @@ tests =
6374
testGroup "Quickjs"
6475
[ testCase "empty quickjs call" (quickjsMultithreaded $ pure ())
6576
, testCase "eval '1 + 2;'" eval_1_plus_2
77+
, testCase "eval throw" eval_throw
6678
, testProperty "marshalling Value to JSValue and back" marshall_to_from_JSValue
6779
]
6880

0 commit comments

Comments
 (0)