Skip to content
Snippets Groups Projects
Commit bbea9721 authored by Alec Theriault's avatar Alec Theriault Committed by Ben Gamari
Browse files

Division fails fast for `divMod` \w integer-simple

We want to match the behaviour of `Integer` as well as
`Integer`/`Natural` from `integer-gmp`, namely to have

     divMod x 0 = _|_

not

     divMod x 0 = (_|_, _|_)

See #16091 for an example of where this matters.
parent 29ecb520
No related branches found
No related tags found
1 merge request!36Division fails fast for `divMod` \w integer-simple
......@@ -481,22 +481,26 @@ instance Integral Natural where
#else
-- | @since 4.8.0.0
instance Integral Natural where
quot (Natural a) (Natural b) = Natural (quot a b)
{-# INLINE quot #-}
rem (Natural a) (Natural b) = Natural (rem a b)
{-# INLINE rem #-}
div (Natural a) (Natural b) = Natural (div a b)
{-# INLINE div #-}
mod (Natural a) (Natural b) = Natural (mod a b)
{-# INLINE mod #-}
divMod (Natural a) (Natural b) = (Natural q, Natural r)
where (q,r) = divMod a b
{-# INLINE divMod #-}
quotRem (Natural a) (Natural b) = (Natural q, Natural r)
where (q,r) = quotRem a b
{-# INLINE quotRem #-}
toInteger (Natural a) = a
{-# INLINE toInteger #-}
{-# INLINE toInteger #-}
toInteger (Natural a) = a
{-# INLINE quot #-}
Natural a `quot` Natural b = Natural (a `quot` b)
{-# INLINE rem #-}
Natural a `rem` Natural b = Natural (a `rem` b)
{-# INLINE div #-}
Natural a `div` Natural b = Natural (a `div` b)
{-# INLINE mod #-}
Natural a `mod` Natural b = Natural (a `mod` b)
{-# INLINE divMod #-}
Natural a `divMod` Natural b = coerce (a `divMod` b)
{-# INLINE quotRem #-}
Natural a `quotRem` Natural b = coerce (a `quotRem` b)
#endif
--------------------------------------------------------------
......
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