Skip to content

Commit

Permalink
Add bangs to tuples instead of their fields alone
Browse files Browse the repository at this point in the history
This commit also adds the '$!' operator where before a tuple section
was applied to a block of code wrapped in parentheses.
  • Loading branch information
rockbmb committed Oct 12, 2017
1 parent f55d60f commit 21312f1
Show file tree
Hide file tree
Showing 3 changed files with 17 additions and 17 deletions.
2 changes: 1 addition & 1 deletion Data/HashMap/Array.hs
Original file line number Diff line number Diff line change
Expand Up @@ -321,7 +321,7 @@ updateWith' ary idx f = update ary idx $! f (index ary idx)
-- inserting it into the array.
updateWithInternal' :: Array e -> Int -> (e -> (Int, e)) -> RunResA e
updateWithInternal' ary idx f =
let (!sz, !e) = f (index ary idx)
let !(!sz, !e) = f (index ary idx)
in RunRes sz (update ary idx e)
{-# INLINE updateWithInternal' #-}

Expand Down
30 changes: 15 additions & 15 deletions Data/HashMap/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -529,15 +529,15 @@ insertInternal k0 v0 m0 = go h0 k0 v0 0 m0
in (1, bitmapIndexedOrFull (b .|. m) ary')
| otherwise =
let !st = A.index ary i
(!sz, !st') = go h k x (s+bitsPerSubkey) st
!(!sz, !st') = go h k x (s+bitsPerSubkey) st
in if st' `ptrEq` st
then (sz, t)
else (sz, BitmapIndexed b (A.update ary i st'))
where m = mask h s
i = sparseIndex b m
go h k x s t@(Full ary) =
let !st = A.index ary i
(!sz, !st') = go h k x (s+bitsPerSubkey) st
!(!sz, !st') = go h k x (s+bitsPerSubkey) st
in if st' `ptrEq` st
then (sz, t)
else (sz, Full (update16 ary i st'))
Expand Down Expand Up @@ -755,8 +755,8 @@ deleteInternal k0 m0 = go h0 k0 0 m0
| b .&. m == 0 = (0, t)
| otherwise =
let !st = A.index ary i
(!sz, !st') = go h k (s+bitsPerSubkey) st
in (sz,) (if st' `ptrEq` st
!(!sz, !st') = go h k (s+bitsPerSubkey) st
in (sz,) $! if st' `ptrEq` st
then t
else case st' of
Empty | A.length ary == 1 -> Empty
Expand All @@ -769,28 +769,28 @@ deleteInternal k0 m0 = go h0 k0 0 m0
where
bIndexed = BitmapIndexed (b .&. complement m) (A.delete ary i)
l | isLeafOrCollision l && A.length ary == 1 -> l
_ -> BitmapIndexed b (A.update ary i st'))
_ -> BitmapIndexed b (A.update ary i st')
where m = mask h s
i = sparseIndex b m
go h k s t@(Full ary) =
let !st = A.index ary i
(!sz, !st') = go h k (s+bitsPerSubkey) st
in (sz,) (if st' `ptrEq` st
!(!sz, !st') = go h k (s+bitsPerSubkey) st
in (sz,) $! if st' `ptrEq` st
then t
else case st' of
Empty ->
let ary' = A.delete ary i
bm = fullNodeMask .&. complement (1 `unsafeShiftL` i)
in BitmapIndexed bm ary'
_ -> Full (A.update ary i st'))
_ -> Full (A.update ary i st')
where i = index h s
go h k _ t@(Collision hy v)
| h == hy = case indexOf k v of
Just i
| A.length v == 2 ->
(-1,) (if i == 0
(-1,) $!if i == 0
then Leaf h (A.index v 1)
else Leaf h (A.index v 0))
else Leaf h (A.index v 0)
| otherwise -> (-1, Collision h (A.delete v i))
Nothing -> (0, t)
| otherwise = (0, t)
Expand Down Expand Up @@ -1010,7 +1010,7 @@ unionWithKeyInternal f hm1 (HashMap siz hm2) = go 0 siz hm1 hm2
leafHashCode _ = error "leafHashCode"

goDifferentHash sz s h1 h2 t1 t2
| m1 == m2 = let (!dsz, !hm) = go sz (s+bitsPerSubkey) t1 t2
| m1 == m2 = let !(!dsz, !hm) = go sz (s+bitsPerSubkey) t1 t2
in (dsz, BitmapIndexed m1 (A.singleton hm))
| m1 < m2 = (sz, BitmapIndexed (m1 .|. m2) (A.pair t1 t2))
| otherwise = (sz, BitmapIndexed (m1 .|. m2) (A.pair t2 t1))
Expand Down Expand Up @@ -1066,7 +1066,7 @@ unionArrayByInternal siz f b1 b2 ary1 ary2 = A.runInternal $ do
| m > b' = return sz
| b' .&. m == 0 = go sz i i1 i2 (m `unsafeShiftL` 1)
| ba .&. m /= 0 = do
let (!dsz, !hm) = f sz (A.index ary1 i1) (A.index ary2 i2)
let !(!dsz, !hm) = f sz (A.index ary1 i1) (A.index ary2 i2)
A.write mary i hm
go dsz (i+1) (i1+1) (i2+1) (m `unsafeShiftL` 1)
| b1 .&. m /= 0 = do
Expand Down Expand Up @@ -1317,9 +1317,9 @@ filterMapAuxInternal onLeaf onColl = go 0
_ -> (siz,) . BitmapIndexed b <$> trim mary 1
_ -> do
ary2 <- trim mary j
return $! (siz,) (if j == maxChildren
then Full ary2
else BitmapIndexed b ary2)
return . (siz,) $! if j == maxChildren
then Full ary2
else BitmapIndexed b ary2
| bi .&. b == 0 = step ary mary b i j (bi `unsafeShiftL` 1) n sz
| otherwise = case go sz (A.index ary i) of
(dsz, Empty) -> step ary mary (b .&. complement bi) (i+1) j
Expand Down
2 changes: 1 addition & 1 deletion Data/HashMap/Strict.hs
Original file line number Diff line number Diff line change
Expand Up @@ -443,7 +443,7 @@ unionWithKeyInternal f hm1 (HashMap siz hm2) = go 0 siz hm1 hm2
leafHashCode _ = error "leafHashCode"

goDifferentHash sz s h1 h2 t1 t2
| m1 == m2 = let (!dsz, !hm) = go sz (s+bitsPerSubkey) t1 t2
| m1 == m2 = let !(!dsz, !hm) = go sz (s+bitsPerSubkey) t1 t2
in (dsz, BitmapIndexed m1 (A.singleton hm))
| m1 < m2 = (sz, BitmapIndexed (m1 .|. m2) (A.pair t1 t2))
| otherwise = (sz, BitmapIndexed (m1 .|. m2) (A.pair t2 t1))
Expand Down

0 comments on commit 21312f1

Please sign in to comment.