Skip to content

Commit 5354949

Browse files
authored
Add Enum Rational to PlutusTx stdlib. (#7406)
Co-authored-by: Nikolaos Bezirgiannis <[email protected]>
1 parent 62c6d6c commit 5354949

File tree

9 files changed

+219
-53
lines changed

9 files changed

+219
-53
lines changed

plutus-benchmark/cardano-loans/src/CardanoLoans/Validator.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ module CardanoLoans.Validator
4141
tokenAsPubKey,
4242
adaSymbol,
4343
adaToken,
44-
fromGHC,
44+
fromHaskellRatio,
4545
unsafeRatio,
4646
(-),(*),(+),
4747
loanValidatorCode,
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
### Added
2+
3+
- To v3: numerator,denominator,unsafeRatio
4+
5+
### Changed
6+
7+
- In v3: renamed fromGHC/toGHC to fromRatioHaskell/toRatioHaskell

plutus-ledger-api/src/PlutusLedgerApi/Data/V3.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -229,8 +229,11 @@ module PlutusLedgerApi.Data.V3 (
229229
-- *** Ratio
230230
Ratio.Rational,
231231
Ratio.ratio,
232-
Ratio.fromGHC,
233-
Ratio.toGHC,
232+
Ratio.unsafeRatio,
233+
Ratio.numerator,
234+
Ratio.denominator,
235+
Ratio.fromHaskellRatio,
236+
Ratio.toHaskellRatio,
234237

235238
-- *** Association maps
236239
V2.Map,

plutus-ledger-api/src/PlutusLedgerApi/V3.hs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -121,10 +121,12 @@ module PlutusLedgerApi.V3 (
121121
V2.strictUpperBound,
122122

123123
-- *** Ratio
124-
Ratio.Rational,
125124
Ratio.ratio,
126-
Ratio.fromGHC,
127-
Ratio.toGHC,
125+
Ratio.unsafeRatio,
126+
Ratio.numerator,
127+
Ratio.denominator,
128+
Ratio.fromHaskellRatio,
129+
Ratio.toHaskellRatio,
128130

129131
-- *** Association maps
130132
V2.Map,

plutus-tx-plugin/test/StdLib/Spec.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ tests =
5050
[ embed testRatioInterop
5151
, testRatioProperty "round" Ratio.round round
5252
, testRatioProperty "truncate" Ratio.truncate truncate
53-
, testRatioProperty "abs" (fmap Ratio.toGHC Ratio.abs) abs
53+
, testRatioProperty "abs" (fmap Ratio.toHaskellRatio Ratio.abs) abs
5454
, embed $ testPropertyNamed "ord" "testOrd" testOrd
5555
, embed $ testPropertyNamed "divMod" "testDivMod" testDivMod
5656
, embed $ testPropertyNamed "quotRem" "testQuotRem" testQuotRem
@@ -71,7 +71,7 @@ tryHard ~a = reoption <$> (liftIO $ try @SomeException $ evaluate $ force a)
7171

7272
testRatioInterop :: TestTree
7373
testRatioInterop = testCase "ratioInterop" do
74-
runExceptT (runUPlc [getPlcNoAnn roundPlc, snd (Lift.liftProgramDef (Ratio.fromGHC 3.75))])
74+
runExceptT (runUPlc [getPlcNoAnn roundPlc, snd (Lift.liftProgramDef (Ratio.fromHaskellRatio 3.75))])
7575
>>= \case
7676
Left e -> assertFailure (show e)
7777
Right r -> r @?= Core.mkConstant () (4 :: Integer)
@@ -82,7 +82,7 @@ testRatioProperty nm plutusFunc ghcFunc =
8282
embed $ testPropertyNamed nm (fromString nm) $ Hedgehog.property $ do
8383
rat <- Hedgehog.forAll $ Gen.realFrac_ (Range.linearFrac (-10000) 100000)
8484
let ghcResult = ghcFunc rat
85-
plutusResult = plutusFunc $ Ratio.fromGHC rat
85+
plutusResult = plutusFunc $ Ratio.fromHaskellRatio rat
8686
Hedgehog.annotateShow ghcResult
8787
Hedgehog.annotateShow plutusResult
8888
Hedgehog.assert (ghcResult == plutusResult)
@@ -117,7 +117,7 @@ testOrd = Hedgehog.property $ do
117117
n1 <- Hedgehog.forAll $ (%) <$> gen <*> gen'
118118
n2 <- Hedgehog.forAll $ (%) <$> gen <*> gen'
119119
ghcResult <- tryHard $ n1 <= n2
120-
plutusResult <- tryHard $ (PlutusTx.<=) (Ratio.fromGHC n1) (Ratio.fromGHC n2)
120+
plutusResult <- tryHard $ (PlutusTx.<=) (Ratio.fromHaskellRatio n1) (Ratio.fromHaskellRatio n2)
121121
Hedgehog.annotateShow ghcResult
122122
Hedgehog.annotateShow plutusResult
123123
Hedgehog.assert (ghcResult == plutusResult)
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
### Removed
2+
3+
- PlutusTx.Ratio: half
4+
5+
### Added
6+
7+
- Enum Ratio instance that mimicks Haskell's instance
8+
9+
### Changed
10+
11+
- Renamed Ratio's fromGHC/toGHC to fromRatioHaskell/toRatioHaskell

plutus-tx/src/PlutusTx/Ratio.hs

Lines changed: 56 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -31,10 +31,11 @@ module PlutusTx.Ratio (
3131
recip,
3232
abs,
3333
negate,
34-
half,
35-
fromGHC,
36-
toGHC,
3734
gcd,
35+
36+
-- * Conversion from/to Haskell
37+
fromHaskellRatio,
38+
toHaskellRatio,
3839
) where
3940

4041
import PlutusTx.Applicative qualified as P
@@ -49,13 +50,14 @@ import PlutusTx.Maybe qualified as P
4950
import PlutusTx.Numeric qualified as P
5051
import PlutusTx.Ord qualified as P
5152
import PlutusTx.Trace qualified as P
53+
import PlutusTx.Enum
5254

55+
import Data.Ratio qualified as HS
5356
import PlutusTx.Builtins qualified as Builtins
5457

5558
import Control.Monad (guard)
5659
import Data.Aeson (FromJSON (parseJSON), ToJSON (toJSON), object, withObject, (.:))
5760
import GHC.Generics
58-
import GHC.Real qualified as Ratio
5961
import PlutusTx.Blueprint.Class (HasBlueprintSchema (..))
6062
import PlutusTx.Blueprint.Definition (HasBlueprintDefinition (..), HasSchemaDefinition)
6163
import Prelude (Ord (..), Show, (*))
@@ -72,6 +74,8 @@ The following two invariants are maintained:
7274
data Rational = Rational Integer Integer
7375
deriving stock (Haskell.Eq, Show, Generic)
7476

77+
makeLift ''Rational
78+
7579
instance Pretty Rational where
7680
pretty (Rational a b) = "Rational:" <+> pretty a <+> pretty b
7781

@@ -228,12 +232,6 @@ ratio n d
228232
(d `Builtins.quotientInteger` gcd')
229233
{-# INLINEABLE ratio #-}
230234

231-
{-| Converts a 'Rational' to a GHC 'Ratio.Rational', preserving value. Does not
232-
work on-chain.
233-
-}
234-
toGHC :: Rational -> Ratio.Rational
235-
toGHC (Rational n d) = n Ratio.% d
236-
237235
{-| Returns the numerator of its argument.
238236
239237
= Note
@@ -259,20 +257,11 @@ denominator :: Rational -> Integer
259257
denominator (Rational _ d) = d
260258
{-# INLINEABLE denominator #-}
261259

262-
-- | 0.5
263-
half :: Rational
264-
half = Rational 1 2
265-
{-# INLINEABLE half #-}
266-
267260
-- | Converts an 'Integer' into the equivalent 'Rational'.
268261
fromInteger :: Integer -> Rational
269262
fromInteger num = Rational num P.one
270263
{-# INLINEABLE fromInteger #-}
271264

272-
-- | Converts a GHC 'Ratio.Rational', preserving value. Does not work on-chain.
273-
fromGHC :: Ratio.Rational -> Rational
274-
fromGHC r = unsafeRatio (Ratio.numerator r) (Ratio.denominator r)
275-
276265
{-| Produces the additive inverse of its argument.
277266
278267
= Note
@@ -342,6 +331,7 @@ round :: Rational -> Integer
342331
round x =
343332
let (n, r) = properFraction x
344333
m = if r P.< P.zero then n P.- P.one else n P.+ P.one
334+
half = Rational 1 2
345335
flag = abs r P.- half
346336
in if
347337
| flag P.< P.zero -> n
@@ -375,7 +365,53 @@ euclid x y
375365
| P.True = euclid y (x `Builtins.modInteger` y)
376366
{-# INLINEABLE euclid #-}
377367

378-
$(makeLift ''Rational)
368+
instance Enum Rational where
369+
{-# INLINEABLE succ #-}
370+
succ (Rational n d) = Rational (n P.+ d) d
371+
{-# INLINEABLE pred #-}
372+
pred (Rational n d) = Rational (n P.- d) d
373+
{-# INLINEABLE toEnum #-}
374+
toEnum = fromInteger
375+
{-# INLINEABLE fromEnum #-}
376+
fromEnum = truncate
377+
{-# INLINEABLE enumFromTo #-}
378+
enumFromTo x lim
379+
-- See why adding half is needed in the Haskell report: https://www.haskell.org/onlinereport/haskell2010/haskellch6.html
380+
| x > lim P.+ Rational 1 2 = []
381+
| P.True = x : enumFromTo (succ x) lim
382+
{-# INLINEABLE enumFromThenTo #-}
383+
enumFromThenTo x y lim =
384+
if delta >= P.zero
385+
then up_list x
386+
else dn_list x
387+
where
388+
delta = y P.- x
389+
-- denominator of delta cannot be zero because it is constructed from two well-formed ratios. So it is safe to use unsafeRatio
390+
mid = numerator delta `unsafeRatio` (denominator delta P.* 2)
391+
up_list x1 =
392+
-- See why adding mid is needed in the Haskell report: https://www.haskell.org/onlinereport/haskell2010/haskellch6.html
393+
if x1 > lim P.+ mid
394+
then []
395+
else x1 : up_list (x1 P.+ delta)
396+
dn_list x1 =
397+
-- See why adding mid is needed in the Haskell report: https://www.haskell.org/onlinereport/haskell2010/haskellch6.html
398+
if x1 < lim P.+ mid
399+
then []
400+
else x1 : dn_list (x1 P.+ delta)
401+
402+
{-| Converts a GHC 'Ratio.Rational', preserving value.
403+
404+
Note: Does not work on-chain.
405+
-}
406+
fromHaskellRatio :: HS.Rational -> Rational
407+
fromHaskellRatio r = unsafeRatio (HS.numerator r) (HS.denominator r)
408+
409+
{-| Converts a 'Rational' to a GHC 'Ratio.Rational', preserving value.
410+
411+
Note: Does not work on-chain.
412+
-}
413+
toHaskellRatio :: Rational -> HS.Rational
414+
toHaskellRatio (Rational n d) = n HS.% d
379415

380416
{- HLINT ignore -}
381417

0 commit comments

Comments
 (0)