From 64643745fc563d0714078c709526c64dbb45fbc9 Mon Sep 17 00:00:00 2001 From: Harry Garrood Date: Mon, 4 Mar 2019 14:44:53 +0000 Subject: [PATCH] Fix stack overflow in fromFoldable, fixes #3 (#6) I had to rearrange things to remove that `where` clause in the tests because otherwise I'd get a syntax error (still not entirely sure why, but oh well). The test I've added fails on `master` with compiler v0.12.3 and node v8.10.0, but passes with the change to `fromFoldable`. --- src/Foreign/Object.purs | 3 ++- test/Test/Foreign/Object.purs | 23 ++++++++++++++++------- 2 files changed, 18 insertions(+), 8 deletions(-) diff --git a/src/Foreign/Object.purs b/src/Foreign/Object.purs index 0776a64..0ed59d1 100644 --- a/src/Foreign/Object.purs +++ b/src/Foreign/Object.purs @@ -44,6 +44,7 @@ module Foreign.Object import Prelude import Control.Monad.ST (ST) +import Control.Monad.ST as ST import Data.Array as A import Data.Eq (class Eq1) import Data.Foldable (class Foldable, foldl, foldr, for_) @@ -216,7 +217,7 @@ update f k m = alter (maybe Nothing f) k m fromFoldable :: forall f a. Foldable f => f (Tuple String a) -> Object a fromFoldable l = runST do s <- OST.new - for_ (A.fromFoldable l) \(Tuple k v) -> OST.poke k v s + ST.foreach (A.fromFoldable l) \(Tuple k v) -> void $ OST.poke k v s pure s foreign import _lookupST :: forall a r z. Fn4 z (a -> z) String (STObject r a) (ST r z) diff --git a/test/Test/Foreign/Object.purs b/test/Test/Foreign/Object.purs index a6d9336..ff4cbe2 100644 --- a/test/Test/Foreign/Object.purs +++ b/test/Test/Foreign/Object.purs @@ -2,8 +2,6 @@ module Test.Foreign.Object where import Prelude -import Effect (Effect) -import Effect.Console (log) import Control.Monad.Writer (runWriter, tell) import Data.Array as A import Data.Foldable (foldl, foldr) @@ -13,12 +11,16 @@ import Data.List as L import Data.List.NonEmpty as NEL import Data.Maybe (Maybe(..)) import Data.NonEmpty ((:|)) -import Foreign.Object as O -import Foreign.Object.Gen (genForeignObject) import Data.Traversable (sequence, traverse) import Data.TraversableWithIndex (traverseWithIndex) import Data.Tuple (Tuple(..), fst, snd, uncurry) +import Effect (Effect) +import Effect.Console (log) +import Foreign.Object (Object) +import Foreign.Object as O +import Foreign.Object.Gen (genForeignObject) import Partial.Unsafe (unsafePartial) +import Test.Assert (assertEqual) import Test.QuickCheck ((), quickCheck, quickCheck', (===)) import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) import Test.QuickCheck.Gen as Gen @@ -244,7 +246,14 @@ objectTests = do quickCheck \(TestObject m) -> let lhs = go m rhs = go m + go :: O.Object (Array Ordering) -> Array Ordering + go = O.foldMap (const identity) in lhs == rhs ("lhs: " <> show lhs <> ", rhs: " <> show rhs) - where - go :: O.Object (Array Ordering) -> Array Ordering - go = O.foldMap \_ v -> v + + log "fromFoldable stack safety" + do + let entries = 100000 + assertEqual + { expected: entries + , actual: O.size (O.fromFoldable (map (\x -> Tuple (show x) x) (A.range 1 entries))) + }