Skip to content

Commit 177dee2

Browse files
committed
Add Enum Ratio to PlutusTx stdlib.
Remove Ratio: half/toGHC/fromGHC Remove v3 toGHC/fromGHC/Rational
1 parent 8444bd0 commit 177dee2

File tree

9 files changed

+172
-49
lines changed

9 files changed

+172
-49
lines changed

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,6 @@ module CardanoLoans.Validator
4141
tokenAsPubKey,
4242
adaSymbol,
4343
adaToken,
44-
fromGHC,
4544
unsafeRatio,
4645
(-),(*),(+),
4746
loanValidatorCode,
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
### Removed
2+
3+
- From v3: Rational,fromGHC,toGHC
4+
5+
### Added
6+
7+
- To v3: numerator,denominator,unsafeRatio

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -227,10 +227,10 @@ module PlutusLedgerApi.Data.V3 (
227227
V2.strictUpperBound,
228228

229229
-- *** Ratio
230-
Ratio.Rational,
231230
Ratio.ratio,
232-
Ratio.fromGHC,
233-
Ratio.toGHC,
231+
Ratio.unsafeRatio,
232+
Ratio.numerator,
233+
Ratio.denominator,
234234

235235
-- *** Association maps
236236
V2.Map,

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

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -123,8 +123,6 @@ module PlutusLedgerApi.V3 (
123123
-- *** Ratio
124124
Ratio.Rational,
125125
Ratio.ratio,
126-
Ratio.fromGHC,
127-
Ratio.toGHC,
128126

129127
-- *** Association maps
130128
V2.Map,

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

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ import Control.Exception (SomeException, evaluate, try)
1717
import Control.Monad.Except (runExceptT)
1818
import Control.Monad.IO.Class (MonadIO (liftIO))
1919
import Data.Proxy (Proxy (..))
20-
import Data.Ratio ((%))
20+
import Data.Ratio (Ratio,(%), numerator, denominator)
2121
import GHC.Exts (fromString)
2222
import Hedgehog (MonadGen, Property)
2323
import Hedgehog qualified
@@ -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 (\ r -> Ratio.numerator r % Ratio.denominator r) Ratio.abs) abs
5454
, embed $ testPropertyNamed "ord" "testOrd" testOrd
5555
, embed $ testPropertyNamed "divMod" "testDivMod" testDivMod
5656
, embed $ testPropertyNamed "quotRem" "testQuotRem" testQuotRem
@@ -69,9 +69,12 @@ tryHard :: (MonadIO m, NFData a) => a -> m (Maybe a)
6969
-- the body, i.e. outside of the call to 'try', defeating the whole purpose.
7070
tryHard ~a = reoption <$> (liftIO $ try @SomeException $ evaluate $ force a)
7171

72+
fromGHC :: Ratio Integer -> Ratio.Rational
73+
fromGHC r = Ratio.unsafeRatio (numerator r) (denominator r)
74+
7275
testRatioInterop :: TestTree
7376
testRatioInterop = testCase "ratioInterop" do
74-
runExceptT (runUPlc [getPlcNoAnn roundPlc, snd (Lift.liftProgramDef (Ratio.fromGHC 3.75))])
77+
runExceptT (runUPlc [getPlcNoAnn roundPlc, snd (Lift.liftProgramDef (fromGHC 3.75))])
7578
>>= \case
7679
Left e -> assertFailure (show e)
7780
Right r -> r @?= Core.mkConstant () (4 :: Integer)
@@ -82,7 +85,7 @@ testRatioProperty nm plutusFunc ghcFunc =
8285
embed $ testPropertyNamed nm (fromString nm) $ Hedgehog.property $ do
8386
rat <- Hedgehog.forAll $ Gen.realFrac_ (Range.linearFrac (-10000) 100000)
8487
let ghcResult = ghcFunc rat
85-
plutusResult = plutusFunc $ Ratio.fromGHC rat
88+
plutusResult = plutusFunc $ fromGHC rat
8689
Hedgehog.annotateShow ghcResult
8790
Hedgehog.annotateShow plutusResult
8891
Hedgehog.assert (ghcResult == plutusResult)
@@ -117,7 +120,7 @@ testOrd = Hedgehog.property $ do
117120
n1 <- Hedgehog.forAll $ (%) <$> gen <*> gen'
118121
n2 <- Hedgehog.forAll $ (%) <$> gen <*> gen'
119122
ghcResult <- tryHard $ n1 <= n2
120-
plutusResult <- tryHard $ (PlutusTx.<=) (Ratio.fromGHC n1) (Ratio.fromGHC n2)
123+
plutusResult <- tryHard $ (PlutusTx.<=) (fromGHC n1) (fromGHC n2)
121124
Hedgehog.annotateShow ghcResult
122125
Hedgehog.annotateShow plutusResult
123126
Hedgehog.assert (ghcResult == plutusResult)
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
### Removed
2+
3+
- PlutusTx.Ratio: half, toGHC, fromGHC
4+
5+
### Added
6+
7+
- Enum Ratio instance that mimicks GHC instance

plutus-tx/src/PlutusTx/Ratio.hs

Lines changed: 36 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -31,9 +31,6 @@ module PlutusTx.Ratio (
3131
recip,
3232
abs,
3333
negate,
34-
half,
35-
fromGHC,
36-
toGHC,
3734
gcd,
3835
) where
3936

@@ -49,13 +46,13 @@ import PlutusTx.Maybe qualified as P
4946
import PlutusTx.Numeric qualified as P
5047
import PlutusTx.Ord qualified as P
5148
import PlutusTx.Trace qualified as P
49+
import PlutusTx.Enum
5250

5351
import PlutusTx.Builtins qualified as Builtins
5452

5553
import Control.Monad (guard)
5654
import Data.Aeson (FromJSON (parseJSON), ToJSON (toJSON), object, withObject, (.:))
5755
import GHC.Generics
58-
import GHC.Real qualified as Ratio
5956
import PlutusTx.Blueprint.Class (HasBlueprintSchema (..))
6057
import PlutusTx.Blueprint.Definition (HasBlueprintDefinition (..), HasSchemaDefinition)
6158
import Prelude (Ord (..), Show, (*))
@@ -228,12 +225,6 @@ ratio n d
228225
(d `Builtins.quotientInteger` gcd')
229226
{-# INLINEABLE ratio #-}
230227

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-
237228
{-| Returns the numerator of its argument.
238229
239230
= Note
@@ -259,20 +250,11 @@ denominator :: Rational -> Integer
259250
denominator (Rational _ d) = d
260251
{-# INLINEABLE denominator #-}
261252

262-
-- | 0.5
263-
half :: Rational
264-
half = Rational 1 2
265-
{-# INLINEABLE half #-}
266-
267253
-- | Converts an 'Integer' into the equivalent 'Rational'.
268254
fromInteger :: Integer -> Rational
269255
fromInteger num = Rational num P.one
270256
{-# INLINEABLE fromInteger #-}
271257

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-
276258
{-| Produces the additive inverse of its argument.
277259
278260
= Note
@@ -342,6 +324,7 @@ round :: Rational -> Integer
342324
round x =
343325
let (n, r) = properFraction x
344326
m = if r P.< P.zero then n P.- P.one else n P.+ P.one
327+
half = Rational 1 2
345328
flag = abs r P.- half
346329
in if
347330
| flag P.< P.zero -> n
@@ -375,6 +358,40 @@ euclid x y
375358
| P.True = euclid y (x `Builtins.modInteger` y)
376359
{-# INLINEABLE euclid #-}
377360

361+
instance Enum Rational where
362+
{-# INLINEABLE succ #-}
363+
succ (Rational n d) = Rational (n `Builtins.addInteger` d) d
364+
{-# INLINEABLE pred #-}
365+
pred (Rational n d) = Rational (n `Builtins.subtractInteger` d) d
366+
{-# INLINEABLE toEnum #-}
367+
toEnum = fromInteger
368+
{-# INLINEABLE fromEnum #-}
369+
fromEnum = truncate
370+
{-# INLINEABLE enumFromTo #-}
371+
enumFromTo x lim
372+
-- See why adding half is needed in the Haskell report: https://www.haskell.org/onlinereport/haskell2010/haskellch6.html
373+
| x > lim P.+ Rational 1 2 = []
374+
| P.True = x : enumFromTo (succ x) lim
375+
{-# INLINEABLE enumFromThenTo #-}
376+
enumFromThenTo x y lim =
377+
if delta >= P.zero
378+
then up_list x
379+
else dn_list x
380+
where
381+
delta = y P.- x
382+
-- denominator of delta cannot be zero because it is constructed from two well-formed ratios. So it is safe to use unsafeRatio
383+
mid = numerator delta `unsafeRatio` (denominator delta P.* 2)
384+
up_list x1 =
385+
-- See why adding mid is needed in the Haskell report: https://www.haskell.org/onlinereport/haskell2010/haskellch6.html
386+
if x1 > lim P.+ mid
387+
then []
388+
else x1 : up_list (x1 P.+ delta)
389+
dn_list x1 =
390+
-- See why adding mid is needed in the Haskell report: https://www.haskell.org/onlinereport/haskell2010/haskellch6.html
391+
if x1 < lim P.+ mid
392+
then []
393+
else x1 : dn_list (x1 P.+ delta)
394+
378395
$(makeLift ''Rational)
379396

380397
{- HLINT ignore -}

plutus-tx/test/Rational/Laws/Construction.hs

Lines changed: 106 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,24 @@
11
-- editorconfig-checker-disable-file
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE TupleSections #-}
4+
{-# LANGUAGE NoImplicitPrelude #-}
5+
{-# LANGUAGE TypeApplications #-}
46

57
module Rational.Laws.Construction (constructionLaws) where
68

79
import Hedgehog (Gen, Property, assert, cover, property, (===))
810
import Hedgehog.Gen qualified as Gen
911
import PlutusTx.Prelude qualified as Plutus
10-
import PlutusTx.Ratio qualified as Ratio
11-
import Prelude
12-
import Rational.Laws.Helpers (forAllWithPP, genInteger, genIntegerPos, normalAndEquivalentToMaybe,
12+
import PlutusTx.Ratio qualified as P
13+
import PlutusTx.Numeric qualified as P
14+
import PlutusTx.Enum qualified as P
15+
import PlutusTx.List qualified as P
16+
import Prelude hiding (succ, pred)
17+
import Rational.Laws.Helpers (forAllWithPP, genRational, genInteger, genIntegerPos, normalAndEquivalentToMaybe,
1318
testCoverProperty)
1419
import Test.Tasty (TestTree)
1520
import Test.Tasty.Hedgehog (testPropertyNamed)
21+
import Data.Ratio qualified as GHC
1622

1723
constructionLaws :: [TestTree]
1824
constructionLaws =
@@ -37,30 +43,57 @@ constructionLaws =
3743
"denominator (unsafeRatio x y) > 0"
3844
"propUnsafeRatioDenomPos"
3945
propUnsafeRatioDenomPos
40-
]
46+
, testPropertyNamed "succ(r)>r"
47+
"propSuccGt"
48+
propSuccGt
49+
, testPropertyNamed "pred(r)<r"
50+
"propPredLt"
51+
propPredLt
52+
, testPropertyNamed "fromEnum . toEnum n = n"
53+
"propFromToEnumId"
54+
propFromToEnumId
55+
, testPropertyNamed "denominator . toEnum = 1"
56+
"propDenomToEnum"
57+
propDenomToEnum
58+
, testPropertyNamed "n<=m ==> length(enumFromTo n m) = abs(n-m)+1"
59+
"propEnumFromToInteger"
60+
propEnumFromToInteger
61+
, testPropertyNamed "enumFromTo = GHC.enumFromTo"
62+
"propEnumFromToGHC"
63+
propEnumFromToGHC
64+
, testPropertyNamed "x/=y ==> enumFromThenTo x y x = [x]"
65+
"propEnumFromThenToLim"
66+
propEnumFromThenToLim
67+
, testPropertyNamed "x/=y ==> enumFromThenTo = GHC.enumFromThenTo"
68+
"propEnumFromThenToGHC"
69+
propEnumFromThenToGHC
70+
, testPropertyNamed "enumFromTo x y = enumFromThenTo x (x+1) y"
71+
"propEnumFromToThenTo"
72+
propEnumFromToThenTo
73+
]
4174

4275
propZeroDenom :: Property
4376
propZeroDenom = property $ do
4477
x <- forAllWithPP genInteger
45-
Ratio.ratio x Plutus.zero `normalAndEquivalentToMaybe` Nothing
78+
P.ratio x Plutus.zero `normalAndEquivalentToMaybe` Nothing
4679

4780
propOneDenom :: Property
4881
propOneDenom = property $ do
4982
x <- forAllWithPP genInteger
50-
Ratio.ratio x Plutus.one `normalAndEquivalentToMaybe` (Just . Ratio.fromInteger $ x)
83+
P.ratio x Plutus.one `normalAndEquivalentToMaybe` (Just . P.fromInteger $ x)
5184

5285
propRatioSelf :: Property
5386
propRatioSelf = property $ do
5487
x <- forAllWithPP . Gen.filter (/= Plutus.zero) $ genInteger
55-
Ratio.ratio x x `normalAndEquivalentToMaybe` Just Plutus.one
88+
P.ratio x x `normalAndEquivalentToMaybe` Just Plutus.one
5689

5790
propRatioSign :: Property
5891
propRatioSign = property $ do
5992
(n, d) <- forAllWithPP go
6093
cover 30 "zero numerator" $ n == 0
6194
cover 30 "same signs" $ signum n == signum d
6295
cover 30 "different signs" $ (signum n /= signum d) && n /= 0
63-
let r = Ratio.ratio n d
96+
let r = P.ratio n d
6497
let signIndicator = Plutus.compare <$> r <*> pure Plutus.zero
6598
case (signum n, signum d) of
6699
(0, _) -> signIndicator === Just Plutus.EQ
@@ -89,31 +122,88 @@ propConstructionAgreement :: Property
89122
propConstructionAgreement = property $ do
90123
n <- forAllWithPP genInteger
91124
d <- forAllWithPP . Gen.filter (/= Plutus.zero) $ genInteger
92-
Ratio.ratio n d `normalAndEquivalentToMaybe` (Just . Ratio.unsafeRatio n $ d)
125+
P.ratio n d `normalAndEquivalentToMaybe` (Just . P.unsafeRatio n $ d)
93126

94127
propFromIntegerNum :: Property
95128
propFromIntegerNum = property $ do
96129
x <- forAllWithPP genInteger
97-
let r = Ratio.fromInteger x
98-
Ratio.numerator r === x
130+
let r = P.fromInteger x
131+
P.numerator r === x
99132

100133
propFromIntegerDen :: Property
101134
propFromIntegerDen = property $ do
102135
x <- forAllWithPP genInteger
103-
let r = Ratio.fromInteger x
104-
Ratio.denominator r === Plutus.one
136+
let r = P.fromInteger x
137+
P.denominator r === Plutus.one
105138

106139
propRatioScale :: Property
107140
propRatioScale = property $ do
108141
x <- forAllWithPP genInteger
109142
y <- forAllWithPP genInteger
110143
z <- forAllWithPP . Gen.filter (/= Plutus.zero) $ genInteger
111-
let lhs = Ratio.ratio x y
112-
let rhs = Ratio.ratio (x Plutus.* z) (y Plutus.* z)
144+
let lhs = P.ratio x y
145+
let rhs = P.ratio (x Plutus.* z) (y Plutus.* z)
113146
lhs `normalAndEquivalentToMaybe` rhs
114147

115148
propUnsafeRatioDenomPos :: Property
116149
propUnsafeRatioDenomPos = property $ do
117150
n <- forAllWithPP genInteger
118151
d <- forAllWithPP $ Gen.filter (/= Plutus.zero) genInteger
119-
assert $ Ratio.denominator (Ratio.unsafeRatio n d) > 0
152+
assert $ P.denominator (P.unsafeRatio n d) > 0
153+
154+
propSuccGt :: Property
155+
propSuccGt = property $ do
156+
n <- forAllWithPP genRational
157+
assert $ P.succ n > n
158+
159+
propPredLt :: Property
160+
propPredLt = property $ do
161+
n <- forAllWithPP genRational
162+
assert $ P.pred n < n
163+
164+
propDenomToEnum :: Property
165+
propDenomToEnum = property $ do
166+
n <- forAllWithPP genInteger
167+
P.denominator (P.toEnum n) === 1
168+
169+
propFromToEnumId :: Property
170+
propFromToEnumId = property $ do
171+
n <- forAllWithPP genInteger
172+
P.fromEnum @P.Rational (P.toEnum n) === n
173+
174+
propEnumFromToInteger :: Property
175+
propEnumFromToInteger = property $ do
176+
n <- forAllWithPP genInteger
177+
m <- forAllWithPP $ Gen.filter (>=n) genInteger
178+
P.length(P.enumFromTo @P.Rational (P.toEnum n) (P.toEnum m)) === abs (n - m) + 1
179+
180+
propEnumFromThenToLim :: Property
181+
propEnumFromThenToLim = property $ do
182+
x <- forAllWithPP genRational
183+
y <- forAllWithPP $ Gen.filter (/=x) genRational
184+
P.enumFromThenTo x y x === [x]
185+
186+
propEnumFromToGHC :: Property
187+
propEnumFromToGHC = property $ do
188+
x <- forAllWithPP genRational
189+
y <- forAllWithPP genRational
190+
fmap toGHC (P.enumFromTo x y) === enumFromTo (toGHC x) (toGHC y)
191+
192+
propEnumFromThenToGHC :: Property
193+
propEnumFromThenToGHC = property $ do
194+
x <- forAllWithPP genRational
195+
y <- forAllWithPP $ Gen.filter (/=x) genRational
196+
z <- forAllWithPP genRational
197+
fmap toGHC (P.enumFromThenTo x y z) === enumFromThenTo (toGHC x) (toGHC y) (toGHC z)
198+
199+
propEnumFromToThenTo :: Property
200+
propEnumFromToThenTo = property $ do
201+
x <- forAllWithPP genRational
202+
y <- forAllWithPP genRational
203+
P.enumFromTo x y === P.enumFromThenTo x (x P.+ Plutus.one) y
204+
205+
{-| Converts a 'Rational' to a GHC 'Rational', preserving value. Does not
206+
work on-chain.
207+
-}
208+
toGHC :: P.Rational -> Rational
209+
toGHC r = P.numerator r GHC.% P.denominator r

0 commit comments

Comments
 (0)