Skip to content

Commit 441b849

Browse files
authored
PLT-1611: Fix Interval for discrete intervals (#5190)
* PLT-1611: Fix Interval for discrete intervals `Interval` was not in a good place. It violated a bunch of laws. The first thing this PR does is add a bunch more tests: - Generic tests for the typeclasses that `Interval` has instances of. - Some specific tests that test that finite intervals behave the same as sets of consecutive numbers. The latter gives us a "semantic" test that lets us check whether our operations on intervals are doing the right thing with respect to a model - in this case the model is the set of values that fall into the inteval. Then we need to actually fix `Interval`. The most straightforward solution I could see is just to restrict most of its operations to intervals on enumerable types. That lets us turn non-inclusive bounds into inclusive bounds, which simplifies things a lot. Without that information, we can't easily even tell if e.g. an interval is empty or not. Arguably we should just have never had non-inclusive bounds in the first place and it's unnecessary generality. However, I think changing that now would be more disruptive than it is worth. Fixes #5185 * Review comments * Add tests for closed boolean intervals
1 parent bb6e4ff commit 441b849

File tree

10 files changed

+477
-75
lines changed

10 files changed

+477
-75
lines changed
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
### Fixed
2+
3+
- Fixed numerous bugs in the behaviour of `Interval`s with open endpoints.

plutus-ledger-api/plutus-ledger-api.cabal

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -138,17 +138,17 @@ test-suite plutus-ledger-api-test
138138

139139
build-depends:
140140
, barbies
141-
, base >=4.9 && <5
141+
, base >=4.9 && <5
142142
, bytestring
143143
, containers
144144
, extra
145145
, hedgehog
146146
, lens
147147
, mtl
148148
, nothunks
149-
, plutus-core ^>=1.2
150-
, plutus-ledger-api ^>=1.2
151-
, plutus-ledger-api-testlib ^>=1.2
149+
, plutus-core ^>=1.2
150+
, plutus-ledger-api:{plutus-ledger-api, plutus-ledger-api-testlib} ^>=1.2
151+
, plutus-tx:plutus-tx-testlib ^>=1.2
152152
, tasty
153153
, tasty-hedgehog
154154
, tasty-hunit

plutus-ledger-api/src/PlutusLedgerApi/V1/Interval.hs

Lines changed: 138 additions & 51 deletions
Original file line numberDiff line numberDiff line change
@@ -41,21 +41,29 @@ import Prelude qualified as Haskell
4141
import Prettyprinter (Pretty (pretty), comma, (<+>))
4242

4343
import PlutusTx qualified
44+
import PlutusTx.Eq as PlutusTx
4445
import PlutusTx.Lift (makeLift)
46+
import PlutusTx.Ord as PlutusTx
4547
import PlutusTx.Prelude
4648

49+
-- See Note [Enumerable Intervals]
4750
{- | An interval of @a@s.
4851
4952
The interval may be either closed or open at either end, meaning
5053
that the endpoints may or may not be included in the interval.
5154
5255
The interval can also be unbounded on either side.
5356
54-
The 'Haskell.Eq'uality of two intervals is specified as the canonical, structural equality and not
55-
the equality of the elements of their two underlying sets; the same holds for 'Haskell.Ord'.
57+
The 'Eq' instance gives equality of the intervals, not structural equality.
58+
There is no 'Ord' instance, but 'contains' gives a partial order.
59+
60+
Note that some of the functions on `Interval` rely on `Enum` in order to
61+
handle non-inclusive endpoints. For this reason, it may not be safe to
62+
use `Interval`s with non-inclusive endpoints on types whose `Enum`
63+
instances have partial methods.
5664
-}
5765
data Interval a = Interval { ivFrom :: LowerBound a, ivTo :: UpperBound a }
58-
deriving stock (Haskell.Eq, Haskell.Ord, Haskell.Show, Generic)
66+
deriving stock (Haskell.Show, Generic)
5967
deriving anyclass (NFData)
6068

6169
instance Functor Interval where
@@ -66,7 +74,7 @@ instance Pretty a => Pretty (Interval a) where
6674

6775
-- | A set extended with a positive and negative infinity.
6876
data Extended a = NegInf | Finite a | PosInf
69-
deriving stock (Haskell.Eq, Haskell.Ord, Haskell.Show, Generic)
77+
deriving stock (Haskell.Show, Generic)
7078
deriving anyclass (NFData)
7179

7280
instance Functor Extended where
@@ -79,14 +87,30 @@ instance Pretty a => Pretty (Extended a) where
7987
pretty PosInf = pretty "+∞"
8088
pretty (Finite a) = pretty a
8189

90+
-- See Note [Enumerable Intervals]
8291
-- | Whether a bound is inclusive or not.
8392
type Closure = Bool
8493

8594
-- | The upper bound of an interval.
8695
data UpperBound a = UpperBound (Extended a) Closure
87-
deriving stock (Haskell.Eq, Haskell.Ord, Haskell.Show, Generic)
96+
deriving stock (Haskell.Show, Generic)
8897
deriving anyclass (NFData)
8998

99+
-- | For an enumerable type, turn an upper bound into a single inclusive
100+
-- bounding value.
101+
--
102+
-- Since the type is enumerable, non-inclusive bounds are equivalent
103+
-- to inclusive bounds on the predecessor.
104+
--
105+
-- See Note [Enumerable Intervals]
106+
inclusiveUpperBound :: Enum a => UpperBound a -> Extended a
107+
-- already inclusive
108+
inclusiveUpperBound (UpperBound v True) = v
109+
-- take pred
110+
inclusiveUpperBound (UpperBound (Finite x) False) = Finite $ pred x
111+
-- an infinity: inclusive/non-inclusive makes no difference
112+
inclusiveUpperBound (UpperBound v False) = v
113+
90114
instance Functor UpperBound where
91115
fmap f (UpperBound e c) = UpperBound (f <$> e) c
92116

@@ -98,9 +122,24 @@ instance Pretty a => Pretty (UpperBound a) where
98122

99123
-- | The lower bound of an interval.
100124
data LowerBound a = LowerBound (Extended a) Closure
101-
deriving stock (Haskell.Eq, Haskell.Ord, Haskell.Show, Generic)
125+
deriving stock (Haskell.Show, Generic)
102126
deriving anyclass (NFData)
103127

128+
-- | For an enumerable type, turn an lower bound into a single inclusive
129+
-- bounding value.
130+
--
131+
-- Since the type is enumerable, non-inclusive bounds are equivalent
132+
-- to inclusive bounds on the successor.
133+
--
134+
-- See Note [Enumerable Intervals]
135+
inclusiveLowerBound :: Enum a => LowerBound a -> Extended a
136+
-- already inclusive
137+
inclusiveLowerBound (LowerBound v True) = v
138+
-- take succ
139+
inclusiveLowerBound (LowerBound (Finite x) False) = Finite $ succ x
140+
-- an infinity: inclusive/non-inclusive makes no difference
141+
inclusiveLowerBound (LowerBound v False) = v
142+
104143
instance Functor LowerBound where
105144
fmap f (LowerBound e c) = LowerBound (f <$> e) c
106145

@@ -127,6 +166,9 @@ instance Eq a => Eq (Extended a) where
127166
Finite l == Finite r = l == r
128167
_ == _ = False
129168

169+
instance Eq a => Haskell.Eq (Extended a) where
170+
(==) = (PlutusTx.==)
171+
130172
instance Ord a => Ord (Extended a) where
131173
{-# INLINABLE compare #-}
132174
NegInf `compare` NegInf = EQ
@@ -137,31 +179,40 @@ instance Ord a => Ord (Extended a) where
137179
PosInf `compare` _ = GT
138180
Finite l `compare` Finite r = l `compare` r
139181

140-
instance Eq a => Eq (UpperBound a) where
182+
instance Ord a => Haskell.Ord (Extended a) where
183+
compare = PlutusTx.compare
184+
185+
-- See Note [Enumerable Intervals]
186+
instance (Enum a, Eq a) => Eq (UpperBound a) where
141187
{-# INLINABLE (==) #-}
142-
UpperBound v1 in1 == UpperBound v2 in2 = v1 == v2 && in1 == in2
188+
b1 == b2 = inclusiveUpperBound b1 == inclusiveUpperBound b2
143189

144-
instance Ord a => Ord (UpperBound a) where
190+
instance (Enum a, Eq a) => Haskell.Eq (UpperBound a) where
191+
(==) = (PlutusTx.==)
192+
193+
-- See Note [Enumerable Intervals]
194+
instance (Enum a, Ord a) => Ord (UpperBound a) where
145195
{-# INLINABLE compare #-}
146-
UpperBound v1 in1 `compare` UpperBound v2 in2 = case v1 `compare` v2 of
147-
LT -> LT
148-
GT -> GT
149-
-- A closed upper bound is bigger than an open upper bound. This corresponds
150-
-- to the normal order on Bool.
151-
EQ -> in1 `compare` in2
152-
153-
instance Eq a => Eq (LowerBound a) where
196+
b1 `compare` b2 = inclusiveUpperBound b1 `compare` inclusiveUpperBound b2
197+
198+
instance (Enum a, Ord a) => Haskell.Ord (UpperBound a) where
199+
compare = PlutusTx.compare
200+
201+
-- See Note [Enumerable Intervals]
202+
instance (Enum a, Eq a) => Eq (LowerBound a) where
154203
{-# INLINABLE (==) #-}
155-
LowerBound v1 in1 == LowerBound v2 in2 = v1 == v2 && in1 == in2
204+
b1 == b2 = inclusiveLowerBound b1 == inclusiveLowerBound b2
156205

157-
instance Ord a => Ord (LowerBound a) where
206+
instance (Enum a, Eq a) => Haskell.Eq (LowerBound a) where
207+
(==) = (PlutusTx.==)
208+
209+
-- See Note [Enumerable Intervals]
210+
instance (Enum a, Ord a) => Ord (LowerBound a) where
158211
{-# INLINABLE compare #-}
159-
LowerBound v1 in1 `compare` LowerBound v2 in2 = case v1 `compare` v2 of
160-
LT -> LT
161-
GT -> GT
162-
-- An open lower bound is bigger than a closed lower bound. This corresponds
163-
-- to the *reverse* of the normal order on Bool.
164-
EQ -> in2 `compare` in1
212+
b1 `compare` b2 = inclusiveLowerBound b1 `compare` inclusiveLowerBound b2
213+
214+
instance (Enum a, Ord a) => Haskell.Ord (LowerBound a) where
215+
compare = PlutusTx.compare
165216

166217
{-# INLINABLE strictUpperBound #-}
167218
{- | Construct a strict upper bound from a value.
@@ -195,25 +246,38 @@ The resulting bound includes all values that are equal or smaller than the input
195246
upperBound :: a -> UpperBound a
196247
upperBound a = UpperBound (Finite a) True
197248

198-
instance Ord a => JoinSemiLattice (Interval a) where
249+
-- See Note [Enumerable Intervals]
250+
instance (Enum a, Ord a) => JoinSemiLattice (Interval a) where
199251
{-# INLINABLE (\/) #-}
200252
(\/) = hull
201253

202-
instance Ord a => BoundedJoinSemiLattice (Interval a) where
254+
-- See Note [Enumerable Intervals]
255+
instance (Enum a, Ord a) => BoundedJoinSemiLattice (Interval a) where
203256
{-# INLINABLE bottom #-}
204257
bottom = never
205258

206-
instance Ord a => MeetSemiLattice (Interval a) where
259+
-- See Note [Enumerable Intervals]
260+
instance (Enum a, Ord a) => MeetSemiLattice (Interval a) where
207261
{-# INLINABLE (/\) #-}
208262
(/\) = intersection
209263

210-
instance Ord a => BoundedMeetSemiLattice (Interval a) where
264+
-- See Note [Enumerable Intervals]
265+
instance (Enum a, Ord a) => BoundedMeetSemiLattice (Interval a) where
211266
{-# INLINABLE top #-}
212267
top = always
213268

214-
instance Eq a => Eq (Interval a) where
269+
-- See Note [Enumerable Intervals]
270+
instance (Enum a, Ord a) => Eq (Interval a) where
215271
{-# INLINABLE (==) #-}
216-
l == r = ivFrom l == ivFrom r && ivTo l == ivTo r
272+
-- Degenerate case: both the intervals are empty.
273+
-- There can be many empty intervals, so we check for this case
274+
-- explicitly
275+
iv1 == iv2 | isEmpty iv1 && isEmpty iv2 = True
276+
(Interval lb1 ub1) == (Interval lb2 ub2) = lb1 == lb2 && ub1 == ub2
277+
278+
instance (Enum a, Ord a) => Haskell.Eq (Interval a) where
279+
{-# INLINABLE (==) #-}
280+
(==) = (PlutusTx.==)
217281

218282
{-# INLINABLE interval #-}
219283
-- | @interval a b@ includes all values that are greater than or equal to @a@
@@ -255,7 +319,7 @@ never = Interval (LowerBound PosInf True) (UpperBound NegInf True)
255319

256320
{-# INLINABLE member #-}
257321
-- | Check whether a value is in an interval.
258-
member :: Ord a => a -> Interval a -> Bool
322+
member :: (Enum a, Ord a) => a -> Interval a -> Bool
259323
member a i = i `contains` singleton a
260324

261325
{-# INLINABLE overlaps #-}
@@ -267,46 +331,69 @@ overlaps l r = not $ isEmpty (l `intersection` r)
267331
{-# INLINABLE intersection #-}
268332
-- | 'intersection a b' is the largest interval that is contained in 'a' and in
269333
-- 'b', if it exists.
270-
intersection :: Ord a => Interval a -> Interval a -> Interval a
334+
intersection :: (Enum a, Ord a) => Interval a -> Interval a -> Interval a
271335
intersection (Interval l1 h1) (Interval l2 h2) = Interval (max l1 l2) (min h1 h2)
272336

273337
{-# INLINABLE hull #-}
274338
-- | 'hull a b' is the smallest interval containing 'a' and 'b'.
275-
hull :: Ord a => Interval a -> Interval a -> Interval a
339+
hull :: (Enum a, Ord a) => Interval a -> Interval a -> Interval a
276340
hull (Interval l1 h1) (Interval l2 h2) = Interval (min l1 l2) (max h1 h2)
277341

278342
{-# INLINABLE contains #-}
279343
{- | @a `contains` b@ is true if the 'Interval' @b@ is entirely contained in
280344
@a@. That is, @a `contains` b@ if for every entry @s@, if @member s b@ then
281345
@member s a@.
282346
-}
283-
contains :: Ord a => Interval a -> Interval a -> Bool
347+
contains :: (Enum a, Ord a) => Interval a -> Interval a -> Bool
348+
-- Everything contains the empty interval
349+
contains _ i2 | isEmpty i2 = True
350+
-- Nothing is contained in the empty interval (except the empty interval,
351+
-- which is already handled)
352+
contains i1 _ | isEmpty i1 = False
353+
-- Otherwise we check the endpoints. This doesn't work for empty intervals,
354+
-- hence the cases above.
284355
contains (Interval l1 h1) (Interval l2 h2) = l1 <= l2 && h2 <= h1
285356

286357
{-# INLINABLE isEmpty #-}
287-
{- | Check if an 'Interval' is empty.
288-
289-
There can be many empty intervals, given a set of values.
290-
Two 'Interval's being empty does not imply that they are `Haskell.Eq`ual to each other.
291-
-}
358+
{- | Check if an 'Interval' is empty. -}
292359
isEmpty :: (Enum a, Ord a) => Interval a -> Bool
293-
isEmpty (Interval (LowerBound v1 in1) (UpperBound v2 in2)) = case v1 `compare` v2 of
294-
LT -> if openInterval then checkEnds v1 v2 else False
360+
isEmpty (Interval lb ub) = case inclusiveLowerBound lb `compare` inclusiveUpperBound ub of
361+
-- We have at least two possible values, the lower bound and the upper bound
362+
LT -> False
363+
-- We have one possible value, the lower bound/upper bound
364+
EQ -> False
365+
-- We have no possible values
295366
GT -> True
296-
EQ -> not (in1 && in2)
297-
where
298-
openInterval = in1 == False && in2 == False
299-
-- | We check two finite ends to figure out if there are elements between them.
300-
-- If there are no elements then the interval is empty (#3467).
301-
checkEnds (Finite v1') (Finite v2') = succ v1' == v2'
302-
checkEnds _ _ = False
303367

304368
{-# INLINABLE before #-}
305369
-- | Check if a value is earlier than the beginning of an 'Interval'.
306-
before :: Ord a => a -> Interval a -> Bool
370+
before :: (Enum a, Ord a) => a -> Interval a -> Bool
307371
before h (Interval f _) = lowerBound h < f
308372

309373
{-# INLINABLE after #-}
310374
-- | Check if a value is later than the end of an 'Interval'.
311-
after :: Ord a => a -> Interval a -> Bool
375+
after :: (Enum a , Ord a) => a -> Interval a -> Bool
312376
after h (Interval _ t) = upperBound h > t
377+
378+
{- Note [Enumerable Intervals]
379+
The 'Interval' type is set up to handle open intervals, where we have non-inclusive
380+
bounds. These are only meaningful for orders where there do not exist (computable)
381+
joins and meets over all elements greater or less than an element.
382+
383+
If those do exist, we can eliminate non-inclusive bounds in favour of inclusive bounds.
384+
For example, in the integers, (x, y) is equivalent to [x+1, y-1], because
385+
x+1 = sup { z | z > x} and y-1 = inf { z | z < y }.
386+
387+
Checking equality, containment etc. of intervals with non-inclusive bounds is
388+
tricky. For example, to know if (x, y) is empty, we need to know if there is a
389+
value between x and y. We don't have a typeclass for that!
390+
391+
In practice, most of the intervals we care about are enumerable (have 'Enum'
392+
instances). We assume that `pred` and `succ` calculate the infima/suprema described
393+
above, and so we can turn non-inclusive bounds into inclusive bounds, which
394+
makes things much easier. The downside is that some of the `Enum` instances have
395+
partial implementations, which means that, e.g. `isEmpty (False, True]` will
396+
throw.
397+
398+
The upshot of this is that many functions in this module require 'Enum'.
399+
-}

0 commit comments

Comments
 (0)