Skip to content

Commit bcd94a5

Browse files
author
Evgenii Akentev
authored
[PlutuxTx.Ratio]: Use reduce in recip (fix IntersectMBO#3897). (IntersectMBO#3932)
1 parent cc20eb1 commit bcd94a5

File tree

2 files changed

+12
-2
lines changed

2 files changed

+12
-2
lines changed

plutus-tx/src/PlutusTx/Ratio.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -192,7 +192,8 @@ x % y = reduce (x P.* signum y) (abs y)
192192

193193
-- | Reciprocal fraction
194194
recip :: Ratio Integer -> Ratio Integer
195-
recip (x :% y) = ((y P.* signum x) :% abs x)
195+
recip (x :% y) = reduce n d
196+
where (n :% d) = ((y P.* signum x) :% abs x)
196197

197198
-- | Convert an 'Interger' to a 'Rational'
198199
fromInteger :: Integer -> Ratio Integer

plutus-tx/test/Spec.hs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ module Main(main) where
66
import qualified Codec.CBOR.FlatTerm as FlatTerm
77
import Codec.Serialise (deserialiseOrFail, serialise)
88
import qualified Codec.Serialise as Serialise
9+
import Control.Exception (ErrorCall, catch)
910
import qualified Data.ByteString as BS
1011
import Data.Either (isLeft)
1112
import Hedgehog (MonadGen, Property, PropertyT, annotateShow, assert, forAll, property, tripping)
@@ -19,7 +20,7 @@ import PlutusTx.Ratio (Rational, denominator, numerator, recip, (
1920
import PlutusTx.Sqrt (Sqrt (..), isqrt, rsqrt)
2021
import Prelude hiding (Rational, negate, recip)
2122
import Test.Tasty
22-
import Test.Tasty.HUnit (testCase, (@?=))
23+
import Test.Tasty.HUnit (Assertion, testCase, (@?=))
2324
import Test.Tasty.Hedgehog (testProperty)
2425

2526
main :: IO ()
@@ -167,8 +168,16 @@ ratioTests = testGroup "Ratio"
167168
[ testProperty "reciprocal ordering 1" reciprocalOrdering1
168169
, testProperty "reciprocal ordering 2" reciprocalOrdering2
169170
, testProperty "reciprocal ordering 3" reciprocalOrdering3
171+
, testCase "recip 0 % 2 fails" reciprocalFailsZeroNumerator
170172
]
171173

174+
-- We check that 'recip' throws an exception if the numerator is zero
175+
reciprocalFailsZeroNumerator :: Assertion
176+
reciprocalFailsZeroNumerator = do
177+
res <- catch (pure $! recip $ 0 % 2) $ \(_ :: ErrorCall) -> pure $ 1 % 1
178+
-- the result should be 1 % 1 if there was an exception
179+
res @?= (1 % 1)
180+
172181
genPositiveRational :: Monad m => PropertyT m Rational
173182
genPositiveRational = do
174183
a <- forAll . Gen.integral $ Range.linear 1 100000

0 commit comments

Comments
 (0)