Skip to content

Commit

Permalink
Fix stack overflow in fromFoldable, fixes #3 (#6)
Browse files Browse the repository at this point in the history
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`.
  • Loading branch information
hdgarrood authored Mar 4, 2019
1 parent 993b44a commit 6464374
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 8 deletions.
3 changes: 2 additions & 1 deletion src/Foreign/Object.purs
Original file line number Diff line number Diff line change
Expand Up @@ -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_)
Expand Down Expand Up @@ -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)
Expand Down
23 changes: 16 additions & 7 deletions test/Test/Foreign/Object.purs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand All @@ -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
Expand Down Expand Up @@ -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)))
}

0 comments on commit 6464374

Please sign in to comment.