@@ -3702,23 +3702,8 @@ foldlFB = foldlWithKey
3702
3702
-- > valid (fromAscList [(5,"a"), (3,"b"), (5,"b")]) == False
3703
3703
3704
3704
fromAscList :: Eq k => [(k ,a )] -> Map k a
3705
- fromAscList xs
3706
- = fromDistinctAscList (combineEq xs)
3707
- where
3708
- -- [combineEq f xs] combines equal elements with function [f] in an ordered list [xs]
3709
- combineEq xs'
3710
- = case xs' of
3711
- [] -> []
3712
- [x] -> [x]
3713
- (x: xx) -> combineEq' x xx
3714
-
3715
- combineEq' z [] = [z]
3716
- combineEq' z@ (kz,_) (x@ (kx,xx): xs')
3717
- | kx== kz = combineEq' (kx,xx) xs'
3718
- | otherwise = z: combineEq' x xs'
3719
- #if __GLASGOW_HASKELL__
3720
- {-# INLINABLE fromAscList #-}
3721
- #endif
3705
+ fromAscList xs = fromAscListWithKey (\ _ x _ -> x) xs
3706
+ {-# INLINE fromAscList #-} -- INLINE for fusion
3722
3707
3723
3708
-- | \(O(n)\). Build a map from a descending list in linear time.
3724
3709
-- /The precondition (input list is descending) is not checked./
@@ -3731,22 +3716,8 @@ fromAscList xs
3731
3716
-- @since 0.5.8
3732
3717
3733
3718
fromDescList :: Eq k => [(k ,a )] -> Map k a
3734
- fromDescList xs = fromDistinctDescList (combineEq xs)
3735
- where
3736
- -- [combineEq f xs] combines equal elements with function [f] in an ordered list [xs]
3737
- combineEq xs'
3738
- = case xs' of
3739
- [] -> []
3740
- [x] -> [x]
3741
- (x: xx) -> combineEq' x xx
3742
-
3743
- combineEq' z [] = [z]
3744
- combineEq' z@ (kz,_) (x@ (kx,xx): xs')
3745
- | kx== kz = combineEq' (kx,xx) xs'
3746
- | otherwise = z: combineEq' x xs'
3747
- #if __GLASGOW_HASKELL__
3748
- {-# INLINABLE fromDescList #-}
3749
- #endif
3719
+ fromDescList xs = fromDescListWithKey (\ _ x _ -> x) xs
3720
+ {-# INLINE fromDescList #-} -- INLINE for fusion
3750
3721
3751
3722
-- | \(O(n)\). Build a map from an ascending list in linear time with a combining function for equal keys.
3752
3723
-- /The precondition (input list is ascending) is not checked./
@@ -3758,9 +3729,7 @@ fromDescList xs = fromDistinctDescList (combineEq xs)
3758
3729
fromAscListWith :: Eq k => (a -> a -> a ) -> [(k ,a )] -> Map k a
3759
3730
fromAscListWith f xs
3760
3731
= fromAscListWithKey (\ _ x y -> f x y) xs
3761
- #if __GLASGOW_HASKELL__
3762
- {-# INLINABLE fromAscListWith #-}
3763
- #endif
3732
+ {-# INLINE fromAscListWith #-} -- INLINE for fusion
3764
3733
3765
3734
-- | \(O(n)\). Build a map from a descending list in linear time with a combining function for equal keys.
3766
3735
-- /The precondition (input list is descending) is not checked./
@@ -3776,9 +3745,7 @@ fromAscListWith f xs
3776
3745
fromDescListWith :: Eq k => (a -> a -> a ) -> [(k ,a )] -> Map k a
3777
3746
fromDescListWith f xs
3778
3747
= fromDescListWithKey (\ _ x y -> f x y) xs
3779
- #if __GLASGOW_HASKELL__
3780
- {-# INLINABLE fromDescListWith #-}
3781
- #endif
3748
+ {-# INLINE fromDescListWith #-} -- INLINE for fusion
3782
3749
3783
3750
-- | \(O(n)\). Build a map from an ascending list in linear time with a
3784
3751
-- combining function for equal keys.
@@ -3792,23 +3759,15 @@ fromDescListWith f xs
3792
3759
-- Also see the performance note on 'fromListWith'.
3793
3760
3794
3761
fromAscListWithKey :: Eq k => (k -> a -> a -> a ) -> [(k ,a )] -> Map k a
3795
- fromAscListWithKey f xs
3796
- = fromDistinctAscList (combineEq f xs)
3762
+ fromAscListWithKey f xs = ascLinkAll (Foldable. foldl' next Nada xs)
3797
3763
where
3798
- -- [combineEq f xs] combines equal elements with function [f] in an ordered list [xs]
3799
- combineEq _ xs'
3800
- = case xs' of
3801
- [] -> []
3802
- [x] -> [x]
3803
- (x: xx) -> combineEq' x xx
3804
-
3805
- combineEq' z [] = [z]
3806
- combineEq' z@ (kz,zz) (x@ (kx,xx): xs')
3807
- | kx== kz = let yy = f kx xx zz in combineEq' (kx,yy) xs'
3808
- | otherwise = z: combineEq' x xs'
3809
- #if __GLASGOW_HASKELL__
3810
- {-# INLINABLE fromAscListWithKey #-}
3811
- #endif
3764
+ next stk (! ky, y) = case stk of
3765
+ Push kx x l stk'
3766
+ | ky == kx -> Push ky (f ky y x) l stk'
3767
+ | Tip <- l -> ascLinkTop stk' 1 (singleton kx x) ky y
3768
+ | otherwise -> Push ky y Tip stk
3769
+ Nada -> Push ky y Tip stk
3770
+ {-# INLINE fromAscListWithKey #-} -- INLINE for fusion
3812
3771
3813
3772
-- | \(O(n)\). Build a map from a descending list in linear time with a
3814
3773
-- combining function for equal keys.
@@ -3822,23 +3781,15 @@ fromAscListWithKey f xs
3822
3781
-- Also see the performance note on 'fromListWith'.
3823
3782
3824
3783
fromDescListWithKey :: Eq k => (k -> a -> a -> a ) -> [(k ,a )] -> Map k a
3825
- fromDescListWithKey f xs
3826
- = fromDistinctDescList (combineEq f xs)
3784
+ fromDescListWithKey f xs = descLinkAll (Foldable. foldl' next Nada xs)
3827
3785
where
3828
- -- [combineEq f xs] combines equal elements with function [f] in an ordered list [xs]
3829
- combineEq _ xs'
3830
- = case xs' of
3831
- [] -> []
3832
- [x] -> [x]
3833
- (x: xx) -> combineEq' x xx
3834
-
3835
- combineEq' z [] = [z]
3836
- combineEq' z@ (kz,zz) (x@ (kx,xx): xs')
3837
- | kx== kz = let yy = f kx xx zz in combineEq' (kx,yy) xs'
3838
- | otherwise = z: combineEq' x xs'
3839
- #if __GLASGOW_HASKELL__
3840
- {-# INLINABLE fromDescListWithKey #-}
3841
- #endif
3786
+ next stk (! ky, y) = case stk of
3787
+ Push kx x r stk'
3788
+ | ky == kx -> Push ky (f ky y x) r stk'
3789
+ | Tip <- r -> descLinkTop ky y 1 (singleton kx x) stk'
3790
+ | otherwise -> Push ky y Tip stk
3791
+ Nada -> Push ky y Tip stk
3792
+ {-# INLINE fromDescListWithKey #-} -- INLINE for fusion
3842
3793
3843
3794
3844
3795
-- | \(O(n)\). Build a map from an ascending list of distinct elements in linear time.
@@ -3850,7 +3801,7 @@ fromDescListWithKey f xs
3850
3801
3851
3802
-- See Note [fromDistinctAscList implementation] in Data.Set.Internal.
3852
3803
fromDistinctAscList :: [(k ,a )] -> Map k a
3853
- fromDistinctAscList = ascLinkAll . Foldable. foldl' next Nada
3804
+ fromDistinctAscList xs = ascLinkAll ( Foldable. foldl' next Nada xs)
3854
3805
where
3855
3806
next :: Stack k a -> (k , a ) -> Stack k a
3856
3807
next (Push kx x Tip stk) (! ky, y) = ascLinkTop stk 1 (singleton kx x) ky y
@@ -3879,7 +3830,7 @@ ascLinkAll stk = foldl'Stack (\r kx x l -> link kx x l r) Tip stk
3879
3830
3880
3831
-- See Note [fromDistinctAscList implementation] in Data.Set.Internal.
3881
3832
fromDistinctDescList :: [(k ,a )] -> Map k a
3882
- fromDistinctDescList = descLinkAll . Foldable. foldl' next Nada
3833
+ fromDistinctDescList xs = descLinkAll ( Foldable. foldl' next Nada xs)
3883
3834
where
3884
3835
next :: Stack k a -> (k , a ) -> Stack k a
3885
3836
next (Push ky y Tip stk) (! kx, x) = descLinkTop kx x 1 (singleton ky y) stk
0 commit comments