Skip to content
Snippets Groups Projects
Commit 59321879 authored by Sylvain Henry's avatar Sylvain Henry Committed by Marge Bot
Browse files

Add quotRem rules (#22152)

  case quotRemInt# x y of
     (# q, _ #) -> body
  ====>
   case quotInt# x y of
     q -> body

  case quotRemInt# x y of
     (# _, r #) -> body
  ====>
   case remInt# x y of
     r -> body
parent 690d0225
No related branches found
No related tags found
No related merge requests found
......@@ -27,6 +27,7 @@ module GHC.Core.Opt.ConstantFold
( primOpRules
, builtinRules
, caseRules
, caseRules2
)
where
......@@ -3192,6 +3193,61 @@ caseRules _ (App (App (Var f) (Type ty)) v) -- dataToTag x
caseRules _ _ = Nothing
-- | Case rules
--
-- It's important that occurence info are present, hence the use of In* types.
caseRules2
:: InExpr -- ^ Scutinee
-> InId -- ^ Case-binder
-> [InAlt] -- ^ Alternatives in standard (increasing) order
-> Maybe (InExpr, InId, [InAlt])
caseRules2 scrut bndr alts
-- case quotRem# x y of
-- (# q, _ #) -> body
-- ====>
-- case quot# x y of
-- q -> body
--
-- case quotRem# x y of
-- (# _, r #) -> body
-- ====>
-- case rem# x y of
-- r -> body
| BinOpApp x op y <- scrut
, Just (quot,rem) <- is_any_quot_rem op
, [Alt (DataAlt _) [q,r] body] <- alts
, isDeadBinder bndr
, dead_q <- isDeadBinder q
, dead_r <- isDeadBinder r
, dead_q || dead_r
= if
| dead_q -> Just $ (BinOpApp x rem y, r, [Alt DEFAULT [] body])
| dead_r -> Just $ (BinOpApp x quot y, q, [Alt DEFAULT [] body])
| otherwise -> Nothing
| otherwise
= Nothing
-- | If the given primop is a quotRem, return the corresponding (quot,rem).
is_any_quot_rem :: PrimOp -> Maybe (PrimOp, PrimOp)
is_any_quot_rem = \case
IntQuotRemOp -> Just (IntQuotOp , IntRemOp)
Int8QuotRemOp -> Just (Int8QuotOp, Int8RemOp)
Int16QuotRemOp -> Just (Int16QuotOp, Int16RemOp)
Int32QuotRemOp -> Just (Int32QuotOp, Int32RemOp)
-- Int64QuotRemOp doesn't exist (yet)
WordQuotRemOp -> Just (WordQuotOp, WordRemOp)
Word8QuotRemOp -> Just (Word8QuotOp, Word8RemOp)
Word16QuotRemOp -> Just (Word16QuotOp, Word16RemOp)
Word32QuotRemOp -> Just (Word32QuotOp, Word32RemOp)
-- Word64QuotRemOp doesn't exist (yet)
_ -> Nothing
tx_lit_con :: Platform -> (Integer -> Integer) -> AltCon -> Maybe AltCon
tx_lit_con _ _ DEFAULT = Just DEFAULT
tx_lit_con platform adjust (LitAlt l) = Just $ LitAlt (mapLitValue platform adjust l)
......
......@@ -19,6 +19,7 @@ import GHC.Driver.Flags
import GHC.Core
import GHC.Core.Opt.Simplify.Monad
import GHC.Core.Opt.ConstantFold
import GHC.Core.Type hiding ( substTy, substTyVar, extendTvSubst, extendCvSubst )
import GHC.Core.TyCo.Compare( eqType )
import GHC.Core.Opt.Simplify.Env
......@@ -3039,6 +3040,14 @@ rebuildCase env scrut case_bndr alts@[Alt _ bndrs rhs] cont
; case mb_rule of
Just (env', rule_rhs, cont') -> simplExprF env' rule_rhs cont'
Nothing -> reallyRebuildCase env scrut case_bndr alts cont }
--------------------------------------------------
-- 3. Primop-related case-rules
--------------------------------------------------
|Just (scrut', case_bndr', alts') <- caseRules2 scrut case_bndr alts
= reallyRebuildCase env scrut' case_bndr' alts' cont
where
all_dead_bndrs = all isDeadBinder bndrs -- bndrs are [InId]
is_plain_seq = all_dead_bndrs && isDeadBinder case_bndr -- Evaluation *only* for effect
......
{-# OPTIONS_GHC -O2 -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques #-}
module T22152 (toHours) where
{-# INLINE toHoursMinutesSeconds #-}
toHoursMinutesSeconds :: Int -> (Int, Int, Int)
toHoursMinutesSeconds t = (h, m', s)
where
(h, m') = m `quotRem` 60
(m, s) = toMinutesSeconds t
toMinutesSeconds :: Int -> (Int, Int)
toMinutesSeconds t = t `quotRem` 60
toHours t = h
where
(h, _, _) = toHoursMinutesSeconds t
==================== Tidy Core ====================
Result size of Tidy Core
= {terms: 11, types: 5, coercions: 0, joins: 0/0}
toHours
= \ t -> case t of { I# x -> I# (quotInt# (quotInt# x 60#) 60#) }
......@@ -6,3 +6,4 @@ test('LevAddrToAny', normal, compile, [''])
test('UnliftedMutVar_Comp', normal, compile, [''])
test('UnliftedStableName', normal, compile, [''])
test('KeepAliveWrapper', normal, compile, ['-O'])
test('T22152', normal, compile, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment