[commit: packages/containers] ghc-head: Move the INLINE pragma after the function. (de5b96a)
git at git.haskell.org
git at git.haskell.org
Wed Sep 4 21:24:38 CEST 2013
Repository : ssh://git@git.haskell.org/containers
On branch : ghc-head
Link : http://git.haskell.org/?p=packages/containers.git;a=commit;h=de5b96a6c34caefcce3cf1040106817b824bb456
>---------------------------------------------------------------
commit de5b96a6c34caefcce3cf1040106817b824bb456
Author: Milan Straka <fox at ucw.cz>
Date: Sun Jun 9 11:36:43 2013 +0200
Move the INLINE pragma after the function.
All other INLINEs are after function bodies.
>---------------------------------------------------------------
de5b96a6c34caefcce3cf1040106817b824bb456
Data/IntMap/Base.hs | 2 +-
Data/Map/Base.hs | 2 +-
2 files changed, 2 insertions(+), 2 deletions(-)
diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index 73b05b2..263f539 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -1250,13 +1250,13 @@ mapWithKey f t
--
-- > traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
-- > traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')]) == Nothing
-{-# INLINE traverseWithKey #-}
traverseWithKey :: Applicative t => (Key -> a -> t b) -> IntMap a -> t (IntMap b)
traverseWithKey f = go
where
go Nil = pure Nil
go (Tip k v) = Tip k <$> f k v
go (Bin p m l r) = Bin p m <$> go l <*> go r
+{-# INLINE traverseWithKey #-}
-- | /O(n)/. The function @'mapAccum'@ threads an accumulating
-- argument through the map in ascending order of keys.
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 3e240e8..e44bb9e 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -1654,13 +1654,13 @@ mapWithKey f (Bin sx kx x l r) = Bin sx kx (f kx x) (mapWithKey f l) (mapWithKey
--
-- > traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
-- > traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')]) == Nothing
-{-# INLINE traverseWithKey #-}
traverseWithKey :: Applicative t => (k -> a -> t b) -> Map k a -> t (Map k b)
traverseWithKey f = go
where
go Tip = pure Tip
go (Bin s k v l r)
= flip (Bin s k) <$> go l <*> f k v <*> go r
+{-# INLINE traverseWithKey #-}
-- | /O(n)/. The function 'mapAccum' threads an accumulating
-- argument through the map in ascending order of keys.
More information about the ghc-commits
mailing list