[Git][ghc/ghc][wip/andreask/opt-bindersof] Avoid unknown call, probably
Andreas Klebinger (@AndreasK)
gitlab at gitlab.haskell.org
Sun Aug 14 01:31:15 UTC 2022
Andreas Klebinger pushed to branch wip/andreask/opt-bindersof at Glasgow Haskell Compiler / GHC
Commits:
ccd9cdfe by Andreas Klebinger at 2022-08-14T03:30:55+02:00
Avoid unknown call, probably
- - - - -
1 changed file:
- compiler/GHC/Core.hs
Changes:
=====================================
compiler/GHC/Core.hs
=====================================
@@ -1955,14 +1955,16 @@ bindersOf (Rec pairs) = [binder | (binder, _) <- pairs]
bindersOfBinds :: [Bind b] -> [b]
bindersOfBinds binds = foldr ((++) . bindersOf) [] binds
-{-# INLINABLE foldBindersOfStrict #-}
+{-# INLINE foldBindersOfStrict #-}
foldBindersOfStrict :: (a -> b -> a) -> a -> Bind b -> a
-foldBindersOfStrict f z (NonRec binder _) = f z binder
-foldBindersOfStrict f z (Rec pairs) = foldl' f z $ map fst pairs
+foldBindersOfStrict f = \z bndr ->
+ case bndr of
+ (NonRec binder _) -> f z binder
+ (Rec pairs) -> foldl' f z $ map fst pairs
-{-# INLINABLE foldBindersOfBindsStrict #-}
+{-# INLINE foldBindersOfBindsStrict #-}
foldBindersOfBindsStrict :: (a -> b -> a) -> a -> [Bind b] -> a
-foldBindersOfBindsStrict f z binds = foldl' (foldBindersOfStrict f) z binds
+foldBindersOfBindsStrict f = \z binds -> foldl' (foldBindersOfStrict f) z binds
rhssOfBind :: Bind b -> [Expr b]
rhssOfBind (NonRec _ rhs) = [rhs]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ccd9cdfece6886521cafc1c9fcade0edac7c9108
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ccd9cdfece6886521cafc1c9fcade0edac7c9108
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20220813/a87c5af7/attachment-0001.html>
More information about the ghc-commits
mailing list