• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

input-output-hk / constrained-generators / 407

20 Nov 2025 12:46PM UTC coverage: 76.922% (-0.4%) from 77.308%
407

push

github

web-flow
initial stab at speeding up maps with more optimistic first assumption (#58)

12 of 13 new or added lines in 3 files covered. (92.31%)

45 existing lines in 5 files now uncovered.

3923 of 5100 relevant lines covered (76.92%)

1.45 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

75.42
/src/Constrained/NumOrd.hs
1
{-# LANGUAGE AllowAmbiguousTypes #-}
2
{-# LANGUAGE ConstraintKinds #-}
3
{-# LANGUAGE CPP #-}
4
{-# LANGUAGE DataKinds #-}
5
{-# LANGUAGE DefaultSignatures #-}
6
{-# LANGUAGE DerivingVia #-}
7
{-# LANGUAGE FlexibleContexts #-}
8
{-# LANGUAGE FlexibleInstances #-}
9
{-# LANGUAGE GADTs #-}
10
{-# LANGUAGE LambdaCase #-}
11
{-# LANGUAGE PatternSynonyms #-}
12
{-# LANGUAGE ScopedTypeVariables #-}
13
{-# LANGUAGE StandaloneDeriving #-}
14
{-# LANGUAGE TypeApplications #-}
15
{-# LANGUAGE TypeFamilies #-}
16
{-# LANGUAGE TypeOperators #-}
17
{-# LANGUAGE UndecidableInstances #-}
18
{-# LANGUAGE UndecidableSuperClasses #-}
19
{-# LANGUAGE ViewPatterns #-}
20
-- Random Natural, Arbitrary Natural, Uniform Natural
21
{-# OPTIONS_GHC -Wno-orphans #-}
22

23
-- | Everything we need to deal with numbers and comparisons between them
24
module Constrained.NumOrd (
25
  NumSpec (..),
26
  (>.),
27
  (<.),
28
  (-.),
29
  (>=.),
30
  (<=.),
31
  (+.),
32
  (*.),
33
  negate_,
34
  cardinality,
35
  caseBoolSpec,
36
  addSpecInt,
37
  emptyNumSpec,
38
  cardinalNumSpec,
39
  combineNumSpec,
40
  genFromNumSpec,
41
  shrinkWithNumSpec,
42
  fixupWithTypeSpec,
43
  conformsToNumSpec,
44
  toPredsNumSpec,
45
  OrdLike (..),
46
  MaybeBounded (..),
47
  NumLike (..),
48
  HasDivision (..),
49
  Numeric,
50
  Number,
51
  nubOrd,
52
  IntW (..),
53
  OrdW (..),
54
) where
55

56
import Constrained.AbstractSyntax
57
import Constrained.Base
58
import Constrained.Conformance
59
import Constrained.Core (Value (..), unionWithMaybe)
60
import Constrained.FunctionSymbol
61
import Constrained.GenT
62
import Constrained.Generic
63
import Constrained.List
64
import Constrained.PrettyUtils
65
import Control.Applicative ((<|>))
66
import Control.Arrow (first)
67
import Data.Foldable
68
import Data.Kind
69
import Data.List (nub)
70
import Data.List.NonEmpty (NonEmpty ((:|)))
71
import qualified Data.List.NonEmpty as NE
72
import Data.Maybe
73
import qualified Data.Set as Set
74
import Data.Typeable (typeOf)
75
import Data.Word
76
import GHC.Int
77
import GHC.Natural
78
import GHC.Real
79
import System.Random.Stateful (Random (..), Uniform (..))
80
import Test.QuickCheck (Arbitrary (arbitrary, shrink), choose, frequency)
81

82
-- | Witnesses for comparison operations (<=. and <. and <=. and >=.) on numbers
83
-- The other operations are defined in terms of these.
84
data OrdW (dom :: [Type]) (rng :: Type) where
85
  LessOrEqualW :: OrdLike a => OrdW '[a, a] Bool
86
  LessW :: OrdLike a => OrdW '[a, a] Bool
87
  GreaterOrEqualW :: OrdLike a => OrdW '[a, a] Bool
88
  GreaterW :: OrdLike a => OrdW '[a, a] Bool
89

90
deriving instance Eq (OrdW ds r)
×
91

92
instance Show (OrdW ds r) where
×
93
  show LessOrEqualW = "<=."
2✔
94
  show LessW = "<."
2✔
95
  show GreaterOrEqualW = ">=."
×
96
  show GreaterW = ">."
2✔
97

98
instance Semantics OrdW where
99
  semantics LessOrEqualW = (<=)
2✔
100
  semantics LessW = (<)
2✔
101
  semantics GreaterW = (>)
2✔
102
  semantics GreaterOrEqualW = (>=)
2✔
103

104
instance Syntax OrdW where
2✔
105
  isInfix _ = True
2✔
106

107
-- =============================================
108
-- OrdLike. Ord for Numbers in the Logic
109
-- =============================================
110

111
-- | Ancillary things we need to be able to implement `Logic` instances for
112
-- `OrdW` that make sense for a given type we are comparing things on.
113
class (Ord a, HasSpec a) => OrdLike a where
114
  leqSpec :: a -> Specification a
115
  default leqSpec ::
116
    ( GenericRequires a
117
    , OrdLike (SimpleRep a)
118
    ) =>
119
    a ->
120
    Specification a
121
  leqSpec = fromSimpleRepSpec . leqSpec . toSimpleRep
×
122

123
  ltSpec :: a -> Specification a
124
  default ltSpec ::
125
    ( OrdLike (SimpleRep a)
126
    , GenericRequires a
127
    ) =>
128
    a ->
129
    Specification a
130
  ltSpec = fromSimpleRepSpec . ltSpec . toSimpleRep
×
131

132
  geqSpec :: a -> Specification a
133
  default geqSpec ::
134
    ( OrdLike (SimpleRep a)
135
    , GenericRequires a
136
    ) =>
137
    a ->
138
    Specification a
139
  geqSpec = fromSimpleRepSpec . geqSpec . toSimpleRep
×
140

141
  gtSpec :: a -> Specification a
142
  default gtSpec ::
143
    ( OrdLike (SimpleRep a)
144
    , GenericRequires a
145
    ) =>
146
    a ->
147
    Specification a
148
  gtSpec = fromSimpleRepSpec . gtSpec . toSimpleRep
×
149

150
-- | This instance should be general enough for every type of Number that has a NumSpec as its TypeSpec
151
instance {-# OVERLAPPABLE #-} (Ord a, HasSpec a, MaybeBounded a, Num a, TypeSpec a ~ NumSpec a) => OrdLike a where
152
  leqSpec l = typeSpec $ NumSpecInterval Nothing (Just l)
2✔
153
  ltSpec l
2✔
154
    | Just b <- lowerBound
2✔
155
    , l == b =
1✔
156
        ErrorSpec (pure ("ltSpec @" ++ show (typeOf l) ++ " " ++ show l))
×
157
    | otherwise = typeSpec $ NumSpecInterval Nothing (Just (l - 1))
1✔
158
  geqSpec l = typeSpec $ NumSpecInterval (Just l) Nothing
2✔
159
  gtSpec l
2✔
160
    | Just b <- upperBound
2✔
161
    , l == b =
1✔
162
        ErrorSpec (pure ("gtSpec @" ++ show (typeOf l) ++ " " ++ show l))
×
163
    | otherwise = typeSpec $ NumSpecInterval (Just (l + 1)) Nothing
1✔
164

165
-- ========================================================================
166
-- helper functions for the TypeSpec for Numbers
167
-- ========================================================================
168

169
-- | Helper class for talking about things that _might_ be `Bounded`
170
class MaybeBounded a where
171
  lowerBound :: Maybe a
172
  upperBound :: Maybe a
173

174
  default lowerBound :: Bounded a => Maybe a
175
  lowerBound = Just minBound
2✔
176

177
  default upperBound :: Bounded a => Maybe a
178
  upperBound = Just maxBound
2✔
179

180
newtype Unbounded a = Unbounded a
181

182
instance MaybeBounded (Unbounded a) where
183
  lowerBound = Nothing
2✔
184
  upperBound = Nothing
2✔
185

186
instance MaybeBounded Int
2✔
187

188
instance MaybeBounded Int64
2✔
189

190
instance MaybeBounded Int32
2✔
191

192
instance MaybeBounded Int16
2✔
193

194
instance MaybeBounded Int8
2✔
195

196
instance MaybeBounded Word64
2✔
197

198
instance MaybeBounded Word32
2✔
199

200
instance MaybeBounded Word16
2✔
201

202
instance MaybeBounded Word8
2✔
203

204
deriving via Unbounded Integer instance MaybeBounded Integer
2✔
205

206
deriving via Unbounded (Ratio Integer) instance MaybeBounded (Ratio Integer)
×
207

208
deriving via Unbounded Float instance MaybeBounded Float
2✔
209

210
deriving via Unbounded Double instance MaybeBounded Double
2✔
211

212
instance MaybeBounded Natural where
213
  lowerBound = Just 0
2✔
214
  upperBound = Nothing
2✔
215

216
-- ===================================================================
217
-- The TypeSpec for numbers
218
-- ===================================================================
219

220
-- | t`TypeSpec` for numbers - represented as a single interval
221
data NumSpec n = NumSpecInterval (Maybe n) (Maybe n)
222

223
instance Ord n => Eq (NumSpec n) where
×
224
  NumSpecInterval ml mh == NumSpecInterval ml' mh'
2✔
225
    | isEmpty ml mh = isEmpty ml' mh'
2✔
226
    | isEmpty ml' mh' = isEmpty ml mh
1✔
227
    | otherwise = ml == ml' && mh == mh'
1✔
228
    where
229
      isEmpty (Just a) (Just b) = a > b
2✔
230
      isEmpty _ _ = False
2✔
231

232
instance Show n => Show (NumSpec n) where
×
233
  show (NumSpecInterval ml mu) = lb ++ ".." ++ ub
2✔
234
    where
235
      lb = "[" ++ maybe "" show ml
2✔
236
      ub = maybe "" show mu ++ "]"
2✔
237

238
instance Ord n => Semigroup (NumSpec n) where
×
239
  NumSpecInterval ml mu <> NumSpecInterval ml' mu' =
2✔
240
    NumSpecInterval
2✔
241
      (unionWithMaybe max ml ml')
2✔
242
      (unionWithMaybe min mu mu')
2✔
243

244
instance Ord n => Monoid (NumSpec n) where
×
245
  mempty = NumSpecInterval Nothing Nothing
2✔
246

247
-- ===========================================
248
-- Arbitrary for Num like things
249
-- ===========================================
250

251
instance (Arbitrary a, Ord a) => Arbitrary (NumSpec a) where
252
  arbitrary = do
2✔
253
    m <- arbitrary
2✔
254
    m' <- arbitrary
2✔
255
    frequency [(10, pure $ mkLoHiInterval m m'), (1, pure $ NumSpecInterval m m')]
2✔
256
    where
257
      mkLoHiInterval (Just a) (Just b) = NumSpecInterval (Just $ min a b) (Just $ max a b)
2✔
258
      mkLoHiInterval m m' = NumSpecInterval m m'
2✔
259
  shrink (NumSpecInterval m m') =
×
260
    uncurry NumSpecInterval <$> shrink (m, m')
×
261

262
#if !MIN_VERSION_QuickCheck(2, 17, 0)
263
instance Arbitrary Natural where
264
  arbitrary = wordToNatural . abs <$> arbitrary
×
265
  shrink n = [wordToNatural w | w <- shrink (naturalToWord n)]
2✔
266
#endif
267

268
instance Uniform Natural where
269
  uniformM g = wordToNatural . abs <$> uniformM g
×
270

271
instance Random Natural where
×
272
  randomR (lo, hi) g = first fromIntegral $ randomR (toInteger lo, toInteger hi) g
2✔
273

274
instance Random (Ratio Integer) where
×
275
  randomR (lo, hi) g =
2✔
276
    let (r, g') = random g
2✔
277
     in (lo + (hi - lo) * r, g')
1✔
278
  random g =
2✔
279
    let (d, g') = first ((+ 1) . abs) $ random g
2✔
280
        (n, g'') = randomR (0, d) g'
2✔
281
     in (n % d, g'')
1✔
282

283
-- ==============================================================================
284
-- Operations on NumSpec, that give it the required properties of a TypeSpec
285
-- ==============================================================================
286

287
-- | Admits anything
288
emptyNumSpec :: Ord a => NumSpec a
289
emptyNumSpec = mempty
2✔
290

291
guardNumSpec ::
292
  (Ord n, HasSpec n, TypeSpec n ~ NumSpec n) =>
293
  [String] ->
294
  NumSpec n ->
295
  Specification n
296
guardNumSpec msg s@(NumSpecInterval (Just a) (Just b))
2✔
297
  | a > b = ErrorSpec ("NumSpec has low bound greater than hi bound" :| (("   " ++ show s) : msg))
2✔
298
  | a == b = equalSpec a
2✔
299
guardNumSpec _ s = typeSpec s
2✔
300

301
-- | Conjunction
302
combineNumSpec ::
303
  (HasSpec n, Ord n, TypeSpec n ~ NumSpec n) =>
304
  NumSpec n ->
305
  NumSpec n ->
306
  Specification n
307
combineNumSpec s s' = guardNumSpec ["when combining two NumSpecs", "   " ++ show s, "   " ++ show s'] (s <> s')
2✔
308

309
-- | Generate a value that satisfies the spec
310
genFromNumSpec ::
311
  (MonadGenError m, Show n, Random n, Ord n, Num n, MaybeBounded n) =>
312
  NumSpec n ->
313
  GenT m n
314
genFromNumSpec (NumSpecInterval ml mu) = do
2✔
315
  n <- sizeT
2✔
316
  pureGen . choose =<< constrainInterval (ml <|> lowerBound) (mu <|> upperBound) (fromIntegral n)
2✔
317

318
-- TODO: fixme
319

320
-- | Try to shrink using a `NumSpec`
321
shrinkWithNumSpec :: Arbitrary n => NumSpec n -> n -> [n]
322
shrinkWithNumSpec _ = shrink
2✔
323

324
-- TODO: fixme
325

326
fixupWithNumSpec :: Arbitrary n => NumSpec n -> n -> Maybe n
327
fixupWithNumSpec _ = listToMaybe . shrink
2✔
328

329
constrainInterval ::
330
  (MonadGenError m, Ord a, Num a, Show a) => Maybe a -> Maybe a -> Integer -> m (a, a)
331
constrainInterval ml mu r =
2✔
332
  case (ml, mu) of
2✔
333
    (Nothing, Nothing) -> pure (-r', r')
2✔
334
    (Just l, Nothing)
335
      | l < 0 -> pure (max l (negate r'), r')
2✔
336
      | otherwise -> pure (l, l + 2 * r')
1✔
337
    (Nothing, Just u)
338
      | u > 0 -> pure (negate r', min u r')
2✔
339
      | otherwise -> pure (u - r' - r', u)
1✔
340
    (Just l, Just u)
341
      | l > u -> genError ("bad interval: " ++ show l ++ " " ++ show u)
1✔
342
      | u < 0 -> pure (safeSub l (safeSub l u r') r', u)
2✔
343
      | l >= 0 -> pure (l, safeAdd u (safeAdd u l r') r')
2✔
344
      -- TODO: this is a bit suspect if the bounds are lopsided
345
      | otherwise -> pure (max l (-r'), min u r')
1✔
346
  where
347
    r' = abs $ fromInteger r
2✔
348
    safeSub l a b
2✔
349
      | a - b > a = l
1✔
350
      | otherwise = max l (a - b)
1✔
351
    safeAdd u a b
2✔
352
      | a + b < a = u
2✔
353
      | otherwise = min u (a + b)
1✔
354

355
-- | Check that a value is in the spec
356
conformsToNumSpec :: Ord n => n -> NumSpec n -> Bool
357
conformsToNumSpec i (NumSpecInterval ml mu) = maybe True (<= i) ml && maybe True (i <=) mu
2✔
358

359
-- =======================================================================
360
-- Several of the methods of HasSpec that have default implementations
361
-- could benefit from type specific implementations for numbers. Those
362
-- implementations are found here
363
-- =====================================================================
364

365
-- | Strip out duplicates (in n-log(n) time, by building an intermediate Set)
366
nubOrd :: Ord a => [a] -> [a]
367
nubOrd =
2✔
368
  loop mempty
2✔
369
  where
370
    loop _ [] = []
2✔
371
    loop s (a : as)
372
      | a `Set.member` s = loop s as
1✔
373
      | otherwise =
×
374
          let s' = Set.insert a s in s' `seq` a : loop s' as
2✔
375

376
-- | Builds a MemberSpec, but returns an Error spec if the list is empty
377
nubOrdMemberSpec :: Ord a => String -> [a] -> Specification a
378
nubOrdMemberSpec message xs =
2✔
379
  memberSpec
2✔
380
    (nubOrd xs)
2✔
381
    ( NE.fromList
×
382
        [ "In call to nubOrdMemberSpec"
×
383
        , "Called from context"
×
384
        , message
×
385
        , "The input is the empty list."
×
386
        ]
387
    )
388

389
lowBound :: Bounded n => Maybe n -> n
390
lowBound Nothing = minBound
2✔
391
lowBound (Just n) = n
×
392

393
highBound :: Bounded n => Maybe n -> n
394
highBound Nothing = maxBound
2✔
395
highBound (Just n) = n
×
396

397
-- | The exact count of the number elements in a Bounded NumSpec
398
countSpec :: forall n. (Bounded n, Integral n) => NumSpec n -> Integer
399
countSpec (NumSpecInterval lo hi) = if lo > hi then 0 else toInteger high - toInteger low + 1
1✔
400
  where
401
    high = highBound hi
2✔
402
    low = lowBound lo
2✔
403

404
-- | The exact number of elements in a Bounded Integral type.
405
finiteSize :: forall n. (Integral n, Bounded n) => Integer
406
finiteSize = toInteger (maxBound @n) - toInteger (minBound @n) + 1
2✔
407

408
-- | This is an optimizing version of  TypeSpec :: TypeSpec n -> [n] -> Specification n
409
--   for Bounded NumSpecs.
410
--                    notInNumSpec :: Bounded n => TypeSpec n -> [n] -> Specification n
411
--   We use this function to specialize the (HasSpec t) method 'typeSpecOpt' for Bounded n.
412
--   So given (TypeSpec interval badlist) we might want to transform it to (MemberSpec goodlist)
413
--   There are 2 opportunities where this can payoff big time.
414
--   1) Suppose the total count of the elements in the interval is < length badlist
415
--      we can then return (MemberSpec (filter elements (`notElem` badlist)))
416
--      this must be smaller than (TypeSpec interval badlist) because the filtered list must be smaller than badlist
417
--   2) Suppose the type 't' is finite with size N. If the length of the badlist > (N/2), then the number of possible
418
--      good things must be smaller than (length badlist), because (possible good + bad == N), so regardless of the
419
--      count of the interval (MemberSpec (filter elements (`notElem` badlist))) is better. Sometimes much better.
420
--      Example, let 'n' be the finite set {0,1,2,3,4,5,6,7,8,9} and the bad list be [0,1,3,4,5,6,8,9]
421
--      (TypeSpec [0..9]  [0,1,3,4,5,6,8,9]) = filter  {0,1,2,3,4,5,6,7,8,9} (`notElem` [0,1,3,4,5,6,8,9]) = [2,7]
422
--      So (MemberSpec [2,7]) is better than  (TypeSpec [0..9]  [0,1,3,4,5,6,8,9]). This works no matter what
423
--      the count of interval is. We only need the (length badlist > (N/2)).
424
notInNumSpec ::
425
  forall n.
426
  ( HasSpec n
427
  , TypeSpec n ~ NumSpec n
428
  , Bounded n
429
  , Integral n
430
  ) =>
431
  NumSpec n ->
432
  [n] ->
433
  Specification n
434
notInNumSpec ns@(NumSpecInterval a b) bad
2✔
435
  | toInteger (length bad) > (finiteSize @n `div` 2) || countSpec ns < toInteger (length bad) =
1✔
436
      nubOrdMemberSpec
×
437
        ("call to: (notInNumSpec " ++ show ns ++ " " ++ show bad ++ ")")
×
438
        [x | x <- [lowBound a .. highBound b], notElem x bad]
×
439
  | otherwise = TypeSpec @n ns bad
1✔
440

441
-- ==========================================================================
442
-- Num n => (NumSpec n) can support operation of Num as interval arithmetic.
443
-- So we will make a (Num (NumSpec Integer)) instance. We won't make other
444
-- instances, because  they would be subject to overflow.
445
-- Given operator ☉, then (a,b) ☉ (c,d) = (minimum s, maximum s) where s = [a ☉ c, a ☉ d, b ☉ c, b ☉ d]
446
-- There are simpler rules for (+) and (-), but for (*) we need to use the general rule.
447
-- ==========================================================================
448

449
guardEmpty :: (Ord n, Num n) => Maybe n -> Maybe n -> NumSpec n -> NumSpec n
450
guardEmpty (Just a) (Just b) s
2✔
451
  | a <= b = s
2✔
452
  | otherwise = NumSpecInterval (Just 1) (Just 0)
1✔
453
guardEmpty _ _ s = s
2✔
454

455
addNumSpec :: (Ord n, Num n) => NumSpec n -> NumSpec n -> NumSpec n
456
addNumSpec (NumSpecInterval x y) (NumSpecInterval a b) =
2✔
457
  guardEmpty x y $
2✔
458
    guardEmpty a b $
2✔
459
      NumSpecInterval ((+) <$> x <*> a) ((+) <$> y <*> b)
2✔
460

461
subNumSpec :: (Ord n, Num n) => NumSpec n -> NumSpec n -> NumSpec n
462
subNumSpec (NumSpecInterval x y) (NumSpecInterval a b) =
2✔
463
  guardEmpty x y $
2✔
464
    guardEmpty a b $
2✔
465
      NumSpecInterval ((-) <$> x <*> b) ((-) <$> y <*> a)
2✔
466

467
multNumSpec :: (Ord n, Num n) => NumSpec n -> NumSpec n -> NumSpec n
468
multNumSpec (NumSpecInterval a b) (NumSpecInterval c d) =
2✔
469
  guardEmpty a b $
2✔
470
    guardEmpty c d $
2✔
471
      NumSpecInterval (unT (minimum s)) (unT (maximum s))
2✔
472
  where
473
    s = [multT (neg a) (neg c), multT (neg a) (pos d), multT (pos b) (neg c), multT (pos b) (pos d)]
2✔
474

475
negNumSpec :: Num n => NumSpec n -> NumSpec n
476
negNumSpec (NumSpecInterval lo hi) = NumSpecInterval (negate <$> hi) (negate <$> lo)
2✔
477

478
instance Num (NumSpec Integer) where
479
  (+) = addNumSpec
2✔
480
  (-) = subNumSpec
2✔
481
  (*) = multNumSpec
2✔
482
  negate = negNumSpec
2✔
483
  fromInteger n = NumSpecInterval (Just (fromInteger n)) (Just (fromInteger n))
2✔
484
  abs = error "No abs in the Num (NumSpec  Integer) instance"
×
485
  signum = error "No signum in the Num (NumSpec  Integer) instance"
×
486

487
-- ========================================================================
488
-- Helper functions for interval multiplication
489
--  (a,b) * (c,d) = (minimum s, maximum s) where s = [a * c, a * d, b * c, b * d]
490

491
-- | T is a sort of special version of Maybe, with two Nothings.
492
--   Given:: NumSpecInterval (Maybe n) (Maybe n) -> Numspec
493
--   We can't distinguish between the two Nothings in (NumSpecInterval Nothing Nothing)
494
--   But using (NumSpecInterval NegInf PosInf) we can, In fact we can make a total ordering on 'T'
495
--   So an ascending Sorted [T x] would all the NegInf on the left and all the PosInf on the right, with
496
--   the Ok's sorted in between. I.e. [NegInf, NegInf, Ok 3, Ok 6, Ok 12, Pos Inf]
497
data T x = NegInf | Ok x | PosInf
498
  deriving (Show, Eq, Ord)
×
499

500
-- \| Conversion between (T x) and (Maybe x)
501
unT :: T x -> Maybe x
502
unT (Ok x) = Just x
2✔
503
unT _ = Nothing
2✔
504

505
-- | Use this on the lower bound. I.e. lo from pair (lo,hi)
506
neg :: Maybe x -> T x
507
neg Nothing = NegInf
2✔
508
neg (Just x) = Ok x
2✔
509

510
-- | Use this on the upper bound. I.e. hi from pair (lo,hi)
511
pos :: Maybe x -> T x
512
pos Nothing = PosInf
2✔
513
pos (Just x) = Ok x
2✔
514

515
-- | multiply two (T x), correctly handling the infinities NegInf and PosInf
516
multT :: Num x => T x -> T x -> T x
517
multT NegInf NegInf = PosInf
2✔
518
multT NegInf PosInf = NegInf
2✔
519
multT NegInf (Ok _) = NegInf
2✔
520
multT (Ok _) NegInf = NegInf
2✔
521
multT (Ok x) (Ok y) = Ok (x * y)
2✔
522
multT (Ok _) PosInf = PosInf
2✔
523
multT PosInf PosInf = PosInf
2✔
524
multT PosInf NegInf = NegInf
2✔
525
multT PosInf (Ok _) = PosInf
2✔
526

527
-- ========================================================================
528
-- We have
529
-- (1) Num Integer
530
-- (2) Num (NumSpec Integer)   And we need
531
-- (3) Num (Specification Integer)
532
-- We need this to implement the method cardinalTypeSpec of (HasSpec t).
533
-- cardinalTypeSpec :: HasSpec a => TypeSpec a -> Specification Integer
534
-- Basically for defining these two cases
535
-- cardinalTypeSpec (Cartesian x y) = (cardinality x) * (cardinality y)
536
-- cardinalTypeSpec (SumSpec leftspec rightspec) = (cardinality leftspec) + (cardinality rightspec)
537
-- So we define addSpecInt for (+)   and  multSpecInt for (*)
538

539
-- | What constraints we need to make HasSpec instance for a Haskell numeric type.
540
--   By abstracting over this, we can avoid making actual HasSpec instances until
541
--   all the requirements (HasSpec Bool, HasSpec(Sum a b)) have been met in
542
--   Constrained.TheKnot.
543
type Number n = (Num n, Enum n, TypeSpec n ~ NumSpec n, Num (NumSpec n), HasSpec n, Ord n)
544

545
-- | Addition on `Specification` for `Number`
546
addSpecInt ::
547
  Number n =>
548
  Specification n ->
549
  Specification n ->
550
  Specification n
551
addSpecInt x y = operateSpec " + " (+) (+) x y
1✔
552

553
subSpecInt ::
554
  Number n =>
555
  Specification n ->
556
  Specification n ->
557
  Specification n
558
subSpecInt x y = operateSpec " - " (-) (-) x y
1✔
559

560
multSpecInt ::
561
  Number n =>
562
  Specification n ->
563
  Specification n ->
564
  Specification n
565
multSpecInt x y = operateSpec " * " (*) (*) x y
×
566

567
-- | let 'n' be some numeric type, and 'f' and 'ft' be operations on 'n' and (TypeSpec n)
568
--   Then lift these operations from (TypeSpec n) to (Specification n)
569
--   Normally 'f' will be a (Num n) instance method (+,-,*) on n,
570
--   and 'ft' will be a a (Num (TypeSpec n)) instance method (+,-,*) on (TypeSpec n)
571
--   But this will work for any operations 'f' and 'ft' with the right types
572
operateSpec ::
573
  Number n =>
574
  String ->
575
  (n -> n -> n) ->
576
  (TypeSpec n -> TypeSpec n -> TypeSpec n) ->
577
  Specification n ->
578
  Specification n ->
579
  Specification n
580
operateSpec operator f ft (ExplainSpec es x) y = explainSpec es $ operateSpec operator f ft x y
1✔
581
operateSpec operator f ft x (ExplainSpec es y) = explainSpec es $ operateSpec operator f ft x y
×
582
operateSpec operator f ft x y = case (x, y) of
2✔
583
  (ErrorSpec xs, ErrorSpec ys) -> ErrorSpec (xs <> ys)
×
584
  (ErrorSpec xs, _) -> ErrorSpec xs
×
585
  (_, ErrorSpec ys) -> ErrorSpec ys
×
586
  (TrueSpec, _) -> TrueSpec
2✔
587
  (_, TrueSpec) -> TrueSpec
2✔
588
  (_, SuspendedSpec _ _) -> TrueSpec
×
589
  (SuspendedSpec _ _, _) -> TrueSpec
×
590
  (TypeSpec a bad1, TypeSpec b bad2) -> TypeSpec (ft a b) [f b1 b2 | b1 <- bad1, b2 <- bad2]
×
591
  (MemberSpec xs, MemberSpec ys) ->
592
    nubOrdMemberSpec
2✔
593
      (show x ++ operator ++ show y)
×
594
      [f x1 y1 | x1 <- NE.toList xs, y1 <- NE.toList ys]
2✔
595
  -- This block is all (MemberSpec{}, TypeSpec{}) with MemberSpec on the left
596
  (MemberSpec ys, TypeSpec (NumSpecInterval (Just i) (Just j)) bad) ->
597
    let xs = NE.toList ys
×
598
     in nubOrdMemberSpec
599
          (show x ++ operator ++ show y)
×
600
          [f x1 y1 | x1 <- xs, y1 <- [i .. j], not (elem y1 bad)]
×
601
  -- Somewhat loose spec here, but more accurate then TrueSpec, it is exact if 'xs' has one element (i.e. 'xs' = [i])
602
  (MemberSpec ys, TypeSpec (NumSpecInterval lo hi) bads) ->
603
    -- We use the specialized version of 'TypeSpec' 'typeSpecOpt'
604
    let xs = NE.toList ys
2✔
605
     in typeSpecOpt
606
          (NumSpecInterval (f (minimum xs) <$> lo) (f (maximum xs) <$> hi))
1✔
607
          [f x1 b | x1 <- xs, b <- bads]
1✔
608
  -- we flip the arguments, so we need to flip the functions as well
609
  (sleft, sright) -> operateSpec operator (\a b -> f b a) (\u v -> ft v u) sright sleft
1✔
610

611
-- | This is very liberal, since in lots of cases it returns TrueSpec.
612
--  for example all operations on SuspendedSpec, and certain
613
--  operations between TypeSpec and MemberSpec. Perhaps we should
614
--  remove it. Only the addSpec (+) and multSpec (*) methods are used.
615
--  But, it is kind of cool ...
616
--  In Fact we can use this to make Num(Specification n) instance for any 'n'.
617
--  But, only Integer is safe, because in all other types (+) and especially
618
--  (-) can lead to overflow or underflow failures.
619
instance Number Integer => Num (Specification Integer) where
×
620
  (+) = addSpecInt
2✔
621
  (-) = subSpecInt
×
622
  (*) = multSpecInt
×
623
  fromInteger n = TypeSpec (NumSpecInterval (Just n) (Just n)) []
×
624
  abs _ = TrueSpec
×
625
  signum _ = TrueSpec
×
626

627
-- ===========================================================================
628

629
-- | Put some (admittedly loose bounds) on the number of solutions that
630
--   'genFromTypeSpec' might return. For lots of types, there is no way to be very accurate.
631
--   Here we lift the HasSpec methods 'cardinalTrueSpec' and 'cardinalTypeSpec'
632
--   from (TypeSpec Integer) to (Specification Integer)
633
cardinality ::
634
  forall a. (Number Integer, HasSpec a) => Specification a -> Specification Integer
635
cardinality (ExplainSpec es s) = explainSpec es (cardinality s)
2✔
636
cardinality TrueSpec = cardinalTrueSpec @a
2✔
637
cardinality (MemberSpec es) = equalSpec (toInteger $ length (nub (NE.toList es)))
2✔
638
cardinality ErrorSpec {} = equalSpec 0
2✔
639
cardinality (TypeSpec s cant) =
640
  subSpecInt
2✔
641
    (cardinalTypeSpec @a s)
2✔
642
    (equalSpec (toInteger $ length (nub $ filter (\c -> conformsTo @a c s) cant)))
2✔
643
cardinality SuspendedSpec {} = cardinalTrueSpec @a
2✔
644

645
-- | A generic function to use as an instance for the HasSpec method
646
--   cardinalTypeSpec :: HasSpec a => TypeSpec a -> Specification Integer
647
--   for types 'n' such that (TypeSpec n ~ NumSpec n)
648
cardinalNumSpec ::
649
  forall n. (Integral n, MaybeBounded n, HasSpec n) => NumSpec n -> Specification Integer
650
cardinalNumSpec (NumSpecInterval (Just lo) (Just hi)) =
2✔
651
  if hi >= lo
1✔
652
    then equalSpec (toInteger hi - toInteger lo + 1)
2✔
UNCOV
653
    else equalSpec 0
×
654
cardinalNumSpec (NumSpecInterval Nothing (Just hi)) =
655
  case lowerBound @n of
2✔
656
    Just lo -> equalSpec (toInteger hi - toInteger lo)
2✔
657
    Nothing -> TrueSpec
×
658
cardinalNumSpec (NumSpecInterval (Just lo) Nothing) =
659
  case upperBound @n of
2✔
660
    Just hi -> equalSpec (toInteger hi - toInteger lo)
2✔
661
    Nothing -> TrueSpec
×
662
cardinalNumSpec (NumSpecInterval Nothing Nothing) = cardinalTrueSpec @n
2✔
663

664
-- ====================================================================
665
-- Now the operations on Numbers
666

667
-- | Everything we need to make the number operations make sense on a given type
668
class (Num a, HasSpec a, HasDivision a, OrdLike a) => NumLike a where
669
  subtractSpec :: a -> TypeSpec a -> Specification a
670
  default subtractSpec ::
671
    ( NumLike (SimpleRep a)
672
    , GenericRequires a
673
    ) =>
674
    a ->
675
    TypeSpec a ->
676
    Specification a
677
  subtractSpec a ts = fromSimpleRepSpec $ subtractSpec (toSimpleRep a) ts
×
678

679
  negateSpec :: TypeSpec a -> Specification a
680
  default negateSpec ::
681
    ( NumLike (SimpleRep a)
682
    , GenericRequires a
683
    ) =>
684
    TypeSpec a ->
685
    Specification a
686
  negateSpec = fromSimpleRepSpec . negateSpec @(SimpleRep a)
×
687

688
  safeSubtract :: a -> a -> Maybe a
689
  default safeSubtract ::
690
    (HasSimpleRep a, NumLike (SimpleRep a)) =>
691
    a ->
692
    a ->
693
    Maybe a
694
  safeSubtract a b = fromSimpleRep <$> safeSubtract @(SimpleRep a) (toSimpleRep a) (toSimpleRep b)
×
695

696
-- | Operations on numbers.
697
-- The reason there is no implementation of abs here is that you can't easily deal with abs
698
-- without specifications becoming very large. Consider the following example:
699
-- > constrained $ \ x -> [1000 <. abs_ x, abs_ x <. 1050]
700
-- The natural `Specification` here would be something like `(-1050, -1000) || (1000, 1050)`
701
-- - the disjoint union of two open, non-overlapping, intervals. However, this doesn't work
702
-- because number type-specs only support a single interval. You could fudge it in all sorts of ways
703
-- by using `chooseSpec` or by using the can't set (which would blow up to be 2000 elements large in this
704
-- case). In short, there is no _satisfactory_ solution here.
705
data IntW (as :: [Type]) b where
706
  AddW :: NumLike a => IntW '[a, a] a
707
  MultW :: NumLike a => IntW '[a, a] a
708
  NegateW :: NumLike a => IntW '[a] a
709
  SignumW :: NumLike a => IntW '[a] a
710

711
deriving instance Eq (IntW dom rng)
×
712

713
instance Show (IntW d r) where
×
714
  show AddW = "+"
2✔
715
  show NegateW = "negate_"
2✔
716
  show MultW = "*"
2✔
717
  show SignumW = "signum_"
2✔
718

719
instance Semantics IntW where
720
  semantics AddW = (+)
2✔
721
  semantics NegateW = negate
2✔
722
  semantics MultW = (*)
2✔
723
  semantics SignumW = signum
2✔
724

725
instance Syntax IntW where
2✔
726
  isInfix AddW = True
2✔
727
  isInfix NegateW = False
×
728
  isInfix MultW = True
×
729
  isInfix SignumW = False
×
730

731
class HasDivision a where
732
  doDivide :: a -> a -> a
733
  default doDivide ::
734
    ( HasDivision (SimpleRep a)
735
    , GenericRequires a
736
    ) =>
737
    a ->
738
    a ->
739
    a
740
  doDivide a b = fromSimpleRep $ doDivide (toSimpleRep a) (toSimpleRep b)
×
741

742
  divideSpec :: a -> TypeSpec a -> Specification a
743
  default divideSpec ::
744
    ( HasDivision (SimpleRep a)
745
    , GenericRequires a
746
    ) =>
747
    a ->
748
    TypeSpec a ->
749
    Specification a
750
  divideSpec a ts = fromSimpleRepSpec $ divideSpec (toSimpleRep a) ts
×
751

752
instance {-# OVERLAPPABLE #-} (HasSpec a, MaybeBounded a, Integral a, TypeSpec a ~ NumSpec a) => HasDivision a where
753
  doDivide = div
2✔
754

755
  divideSpec 0 _ = TrueSpec
1✔
756
  divideSpec a (NumSpecInterval (unionWithMaybe max lowerBound -> ml) (unionWithMaybe min upperBound -> mu)) = typeSpec ts
2✔
757
    where
758
      ts | a > 0 = NumSpecInterval ml' mu'
2✔
759
         | otherwise = NumSpecInterval mu' ml'
1✔
760
      ml' = adjustLowerBound <$> ml
2✔
761
      mu' = adjustUpperBound <$> mu
2✔
762

763
      -- NOTE: negate has different overflow semantics than div, so that's why we use negate below...
764

765
      adjustLowerBound l
2✔
766
        | a == 1 = l
2✔
767
        | a == -1 = negate l
2✔
768
        | otherwise =
×
769
          let r = l `div` a in
2✔
770
          if toInteger r * toInteger a < toInteger l
2✔
771
          then r + signum a
2✔
772
          else r
2✔
773

774
      adjustUpperBound u
2✔
775
        | a == 1  = u
2✔
776
        | a == -1 = negate u
2✔
777
        | otherwise =
×
778
          let r = u `div` a in
2✔
779
          if toInteger r * toInteger a > toInteger u
2✔
780
          then r - signum a
2✔
781
          else r
2✔
782

783
instance HasDivision (Ratio Integer) where
784
  doDivide = (/)
2✔
785

786
  divideSpec 0 _ = TrueSpec
1✔
787
  divideSpec a (NumSpecInterval ml mu) = typeSpec ts
2✔
788
    where
789
      ts | a > 0 = NumSpecInterval ml' mu'
1✔
790
         | otherwise = NumSpecInterval mu' ml'
×
791
      ml' = adjustLowerBound <$> ml
2✔
792
      mu' = adjustUpperBound <$> mu
1✔
793
      adjustLowerBound l =
2✔
794
        let r = l / a
2✔
795
            l' = r * a
2✔
796
        in
797
        if l' < l
1✔
798
        then r + (l - l') * 2 / a
×
799
        else r
2✔
800

801
      adjustUpperBound u =
×
802
        let r = u / a
×
803
            u' = r * a
×
804
        in
805
        if u < u'
×
806
        then r - (u' - u) * 2 / a
×
807
        else r
×
808

809

810
instance HasDivision Float where
811
  doDivide = (/)
2✔
812

813
  divideSpec 0 _ = TrueSpec
1✔
814
  divideSpec a (NumSpecInterval ml mu) = typeSpec ts
2✔
815
    where
816
      ts | a > 0 = NumSpecInterval ml' mu'
2✔
817
         | otherwise = NumSpecInterval mu' ml'
1✔
818
      ml' = adjustLowerBound <$> ml
2✔
819
      mu' = adjustUpperBound <$> mu
2✔
820
      adjustLowerBound l =
2✔
821
        let r = l / a
2✔
822
            l' = r * a
2✔
823
        in
824
        if l' < l
2✔
825
        then r + (l - l') * 2 / a
2✔
826
        else r
2✔
827

828
      adjustUpperBound u =
2✔
829
        let r = u / a
2✔
830
            u' = r * a
2✔
831
        in
832
        if u < u'
2✔
833
        then r - (u' - u) * 2 / a
2✔
834
        else r
2✔
835

836
instance HasDivision Double where
837
  doDivide = (/)
2✔
838

839
  divideSpec 0 _ = TrueSpec
1✔
840
  divideSpec a (NumSpecInterval ml mu) = typeSpec ts
2✔
841
    where
842
      ts | a > 0 = NumSpecInterval ml' mu'
2✔
843
         | otherwise = NumSpecInterval mu' ml'
1✔
844
      ml' = adjustLowerBound <$> ml
2✔
845
      mu' = adjustUpperBound <$> mu
2✔
846
      adjustLowerBound l =
2✔
847
        let r = l / a
2✔
848
            l' = r * a
2✔
849
        in
850
        if l' < l
2✔
851
        then r + (l - l') * 2 / a
2✔
852
        else r
2✔
853

854
      adjustUpperBound u =
2✔
855
        let r = u / a
2✔
856
            u' = r * a
2✔
857
        in
858
        if u < u'
2✔
859
        then r - (u' - u) * 2 / a
2✔
860
        else r
2✔
861

862
-- | A type that we can reason numerically about in constraints
863
type Numeric a = (HasSpec a, Ord a, Num a, TypeSpec a ~ NumSpec a, MaybeBounded a, HasDivision a)
864

865
instance {-# OVERLAPPABLE #-} Numeric a => NumLike a where
866
  subtractSpec a ts@(NumSpecInterval ml mu)
2✔
867
    | Just u <- mu
2✔
868
    , a > 0
2✔
869
    , Nothing <- safeSubtract a u =
2✔
870
        ErrorSpec $
2✔
871
          NE.fromList
×
872
            [ "Underflow in subtractSpec (" ++ showType @a ++ "):"
×
873
            , "  a = " ++ show a
×
874
            , "  ts = " ++ show ts
×
875
            ]
876
    | Just l <- ml
2✔
877
    , a < 0
2✔
878
    , Nothing <- safeSubtract a l =
2✔
879
        ErrorSpec $
2✔
880
          NE.fromList
×
881
            [ "Overflow in subtractSpec (" ++ showType @a ++ "):"
×
882
            , "  a = " ++ show a
×
883
            , "  ts = " ++ show ts
×
884
            ]
885
    | otherwise = typeSpec $ NumSpecInterval (safeSub a <$> ml) (safeSub a <$> mu)
1✔
886
    where
887
      safeSub :: a -> a -> a
888
      safeSub a1 x
2✔
889
        | Just r <- safeSubtract a1 x = r
2✔
890
        | a1 < 0 = fromJust upperBound
2✔
891
        | otherwise = fromJust lowerBound
1✔
892

893
  negateSpec (NumSpecInterval ml mu) = typeSpec $ NumSpecInterval (negate <$> mu) (negate <$> ml)
2✔
894

895
  safeSubtract a x
2✔
896
    | a > 0
2✔
897
    , Just lb <- lowerBound
2✔
898
    , lb + a > x =
2✔
899
        Nothing
2✔
900
    | a < 0
2✔
901
    , Just ub <- upperBound
2✔
902
    , ub + a < x =
2✔
903
        Nothing
2✔
904
    | otherwise = Just $ x - a
1✔
905

906
instance NumLike a => Num (Term a) where
2✔
907
  (+) = (+.)
2✔
908
  negate = negate_
2✔
909
  fromInteger = Lit . fromInteger
2✔
910
  (*) = (*.)
2✔
911
  signum = signum_
2✔
912
  abs = error "No implementation for abs @(Term a)"
×
913

914
invertMult :: (HasSpec a, Num a, HasDivision a) => a -> a -> Maybe a
915
invertMult a b =
2✔
916
  let r = a `doDivide` b in if r * b == a then Just r else Nothing
2✔
917

918
-- | Just a note that these instances won't work until we are in a context where
919
--   there is a HasSpec instance of 'a', which (NumLike a) demands.
920
--   This happens in Constrained.Experiment.TheKnot
921
instance Logic IntW where
1✔
922
  propagateTypeSpec AddW (HOLE :<: i) ts cant = subtractSpec i ts <> notMemberSpec (mapMaybe (safeSubtract i) cant)
2✔
923
  propagateTypeSpec AddW ctx ts cant = propagateTypeSpec AddW (flipCtx ctx) ts cant
2✔
924
  propagateTypeSpec NegateW (Unary HOLE) ts cant = negateSpec ts <> notMemberSpec (map negate cant)
2✔
925
  propagateTypeSpec MultW (HOLE :<: 0) ts cant
926
    | 0 `conformsToSpec` TypeSpec ts cant = TrueSpec
2✔
927
    | otherwise = ErrorSpec $ NE.fromList [ "zero" ]
1✔
928
  propagateTypeSpec MultW (HOLE :<: i) ts cant = divideSpec i ts <> notMemberSpec (mapMaybe (flip invertMult i) cant)
2✔
929
  propagateTypeSpec MultW ctx ts cant = propagateTypeSpec MultW (flipCtx ctx) ts cant
2✔
930
  propagateTypeSpec SignumW (Unary HOLE) ts cant =
931
    constrained $ \ x ->
2✔
932
      [ x `satisfies` notMemberSpec [0] | not $ ok 0 ] ++
2✔
933
      [ Assert $ 0 <=. x                | not $ ok (-1) ] ++
2✔
934
      [ Assert $ x <=. 0                | not $ ok 1 ]
2✔
935
    where ok = flip conformsToSpec (TypeSpec ts cant)
2✔
936

937
  propagateMemberSpec AddW (HOLE :<: i) es =
2✔
938
    memberSpec
2✔
939
      (nub $ mapMaybe (safeSubtract i) (NE.toList es))
2✔
940
      ( NE.fromList
×
941
          [ "propagateSpecFn on (" ++ show i ++ " +. HOLE)"
×
942
          , "The Spec is a MemberSpec = " ++ show es -- show (MemberSpec @HasSpec @TS es)
×
943
          , "We can't safely subtract " ++ show i ++ " from any choice in the MemberSpec."
×
944
          ]
945
      )
946
  propagateMemberSpec AddW ctx es = propagateMemberSpec AddW (flipCtx ctx) es
2✔
947
  propagateMemberSpec NegateW (Unary HOLE) es = MemberSpec $ NE.nub $ fmap negate es
2✔
948
  propagateMemberSpec MultW (HOLE :<: 0) es
949
    | 0 `elem` es = TrueSpec
2✔
950
    | otherwise = ErrorSpec $ NE.fromList [ "zero" ]
1✔
951
  propagateMemberSpec MultW (HOLE :<: i) es = memberSpec (mapMaybe (flip invertMult i) (NE.toList es)) (NE.fromList ["propagateSpec"])
1✔
952
  propagateMemberSpec MultW ctx es = propagateMemberSpec MultW (flipCtx ctx) es
2✔
953
  propagateMemberSpec SignumW (Unary HOLE) es
954
    | all ((`notElem` [-1, 0, 1]) . signum) es = ErrorSpec $ NE.fromList [ "signum for invalid member spec", show es ]
1✔
955
    | otherwise = constrained $ \ x ->
1✔
956
                    [ x `satisfies` notMemberSpec [0] | 0  `notElem` es ] ++
2✔
957
                    [ Assert $ 0 <=. x                | -1 `notElem` es ] ++
2✔
958
                    [ Assert $ x <=. 0                | 1  `notElem` es ]
2✔
959

960
  rewriteRules AddW (x :> y :> Nil) _ | x == y = Just $ 2 * x
2✔
961
  rewriteRules _ _ _ = Nothing
2✔
962

963
infix 4 +.
964

965
-- | `Term`-level `(+)`
966
(+.) :: NumLike a => Term a -> Term a -> Term a
967
(+.) = appTerm AddW
2✔
968

969
infixl 7 *.
970

971
-- | `Term`-level `(+)`
972
(*.) :: NumLike a => Term a -> Term a -> Term a
973
(*.) = appTerm MultW
2✔
974

975
-- | `Term`-level `negate`
976
negate_ :: NumLike a => Term a -> Term a
977
negate_ = appTerm NegateW
2✔
978

979
-- | `Term`-level `signum`
980
signum_ :: NumLike a => Term a -> Term a
981
signum_ = appTerm SignumW
2✔
982

983
infix 4 -.
984

985
-- | `Term`-level `(-)`
986
(-.) :: Numeric n => Term n -> Term n -> Term n
987
(-.) x y = x +. negate_ y
×
988

989
infixr 4 <=.
990

991
-- | `Term`-level `(<=)`
992
(<=.) :: forall a. OrdLike a => Term a -> Term a -> Term Bool
993
(<=.) = appTerm LessOrEqualW
2✔
994

995
infixr 4 <.
996

997
-- | `Term`-level `(<)`
998
(<.) :: forall a. OrdLike a => Term a -> Term a -> Term Bool
999
(<.) = appTerm LessW
2✔
1000

1001
infixr 4 >=.
1002

1003
-- | `Term`-level `(>=)`
1004
(>=.) :: forall a. OrdLike a => Term a -> Term a -> Term Bool
1005
(>=.) = appTerm GreaterOrEqualW
2✔
1006

1007
infixr 4 >.
1008

1009
-- | `Term`-level `(>)`
1010
(>.) :: forall a. OrdLike a => Term a -> Term a -> Term Bool
1011
(>.) = appTerm GreaterW
2✔
1012

1013
-- | t`TypeSpec`-level `satisfies` to implement `toPreds` in
1014
-- `HasSpec` instance
1015
toPredsNumSpec ::
1016
  OrdLike n =>
1017
  Term n ->
1018
  NumSpec n ->
1019
  Pred
1020
toPredsNumSpec v (NumSpecInterval ml mu) =
2✔
1021
  fold $
2✔
1022
    [Assert $ Lit l <=. v | l <- maybeToList ml]
2✔
1023
      ++ [Assert $ v <=. Lit u | u <- maybeToList mu]
2✔
1024

1025
instance Logic OrdW where
×
1026
  propagate f ctxt (ExplainSpec [] s) = propagate f ctxt s
1✔
1027
  propagate f ctxt (ExplainSpec es s) = ExplainSpec es $ propagate f ctxt s
2✔
1028
  propagate _ _ TrueSpec = TrueSpec
2✔
1029
  propagate _ _ (ErrorSpec msgs) = ErrorSpec msgs
1✔
1030
  propagate GreaterW (HOLE :? x :> Nil) spec =
1031
    propagate LessW (x :! Unary HOLE) spec
2✔
1032
  propagate GreaterW (x :! Unary HOLE) spec =
1033
    propagate LessW (HOLE :? x :> Nil) spec
2✔
1034
  propagate LessOrEqualW (HOLE :? Value x :> Nil) (SuspendedSpec v ps) =
1035
    constrained $ \v' -> Let (App LessOrEqualW (v' :> Lit x :> Nil)) (v :-> ps)
2✔
1036
  propagate LessOrEqualW (Value x :! Unary HOLE) (SuspendedSpec v ps) =
1037
    constrained $ \v' -> Let (App LessOrEqualW (Lit x :> v' :> Nil)) (v :-> ps)
2✔
1038
  propagate LessOrEqualW (HOLE :? Value l :> Nil) spec =
1039
    caseBoolSpec spec $ \case True -> leqSpec l; False -> gtSpec l
2✔
1040
  propagate LessOrEqualW (Value l :! Unary HOLE) spec =
1041
    caseBoolSpec spec $ \case True -> geqSpec l; False -> ltSpec l
2✔
1042
  propagate GreaterOrEqualW (HOLE :? Value x :> Nil) spec =
1043
    propagate LessOrEqualW (Value x :! Unary HOLE) spec
2✔
1044
  propagate GreaterOrEqualW (x :! Unary HOLE) spec =
1045
    propagate LessOrEqualW (HOLE :? x :> Nil) spec
×
1046
  propagate LessW (HOLE :? Value x :> Nil) (SuspendedSpec v ps) =
1047
    constrained $ \v' -> Let (App LessW (v' :> Lit x :> Nil)) (v :-> ps)
2✔
1048
  propagate LessW (Value x :! Unary HOLE) (SuspendedSpec v ps) =
1049
    constrained $ \v' -> Let (App LessW (Lit x :> v' :> Nil)) (v :-> ps)
2✔
1050
  propagate LessW (HOLE :? Value l :> Nil) spec =
1051
    caseBoolSpec spec $ \case True -> ltSpec l; False -> geqSpec l
2✔
1052
  propagate LessW (Value l :! Unary HOLE) spec =
1053
    caseBoolSpec spec $ \case True -> gtSpec l; False -> leqSpec l
2✔
1054

1055
-- | @if-then-else@ on a specification, useful for writing `propagate` implementations
1056
-- of predicates, e.g.:
1057
-- > propagate LessW (Value l :! Unary HOLE) spec =
1058
-- >   caseBoolSpec spec $ \case True -> gtSpec l; False -> leqSpec l
1059
caseBoolSpec ::
1060
  HasSpec a => Specification Bool -> (Bool -> Specification a) -> Specification a
1061
caseBoolSpec spec cont = case possibleValues spec of
2✔
1062
  [] -> ErrorSpec (NE.fromList ["No possible values in caseBoolSpec"])
1✔
1063
  [b] -> cont b
2✔
1064
  _ -> mempty
2✔
1065
  where
1066
    -- This will always get the same result, and probably faster since running 2
1067
    -- conformsToSpec on True and False takes less time than simplifying the spec.
1068
    -- Since we are in TheKnot, we could keep the simplifySpec. Is there a good reason to?
1069
    possibleValues s = filter (flip conformsToSpec s) [True, False]
2✔
1070

1071
------------------------------------------------------------------------
1072
-- Instances of HasSpec for numeric types
1073
------------------------------------------------------------------------
1074

1075
instance HasSpec Integer where
×
1076
  type TypeSpec Integer = NumSpec Integer
1077
  emptySpec = emptyNumSpec
2✔
1078
  combineSpec = combineNumSpec
2✔
1079
  genFromTypeSpec = genFromNumSpec
2✔
1080
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1081
  fixupWithTypeSpec = fixupWithNumSpec
×
1082
  conformsTo = conformsToNumSpec
2✔
1083
  toPreds = toPredsNumSpec
2✔
1084
  cardinalTypeSpec = cardinalNumSpec
×
1085
  guardTypeSpec = guardNumSpec
2✔
1086

1087
instance HasSpec Int where
×
1088
  type TypeSpec Int = NumSpec Int
1089
  emptySpec = emptyNumSpec
2✔
1090
  combineSpec = combineNumSpec
2✔
1091
  genFromTypeSpec = genFromNumSpec
2✔
1092
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1093
  fixupWithTypeSpec = fixupWithNumSpec
2✔
1094
  conformsTo = conformsToNumSpec
2✔
1095
  toPreds = toPredsNumSpec
2✔
1096
  cardinalTypeSpec = cardinalNumSpec
2✔
1097
  guardTypeSpec = guardNumSpec
2✔
1098

1099
instance HasSpec (Ratio Integer) where
×
1100
  type TypeSpec (Ratio Integer) = NumSpec (Ratio Integer)
1101
  emptySpec = emptyNumSpec
2✔
1102
  combineSpec = combineNumSpec
2✔
1103
  genFromTypeSpec = genFromNumSpec
2✔
1104
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1105
  fixupWithTypeSpec = fixupWithNumSpec
×
1106
  conformsTo = conformsToNumSpec
2✔
1107
  toPreds = toPredsNumSpec
2✔
1108
  cardinalTypeSpec _ = TrueSpec
×
1109
  guardTypeSpec = guardNumSpec
2✔
1110

1111
instance HasSpec Natural where
×
1112
  type TypeSpec Natural = NumSpec Natural
1113
  emptySpec = emptyNumSpec
2✔
1114
  combineSpec = combineNumSpec
2✔
1115
  genFromTypeSpec = genFromNumSpec
2✔
1116
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1117
  fixupWithTypeSpec = fixupWithNumSpec
×
1118
  conformsTo = conformsToNumSpec
2✔
1119
  toPreds = toPredsNumSpec
×
1120
  cardinalTypeSpec (NumSpecInterval (fromMaybe 0 -> lo) (Just hi)) =
×
1121
    if lo < hi
×
1122
      then equalSpec (fromIntegral $ hi - lo + 1)
×
1123
      else equalSpec 0
×
1124
  cardinalTypeSpec _ = TrueSpec
×
1125
  guardTypeSpec = guardNumSpec
2✔
1126

1127
instance HasSpec Word8 where
×
1128
  type TypeSpec Word8 = NumSpec Word8
1129
  emptySpec = emptyNumSpec
2✔
1130
  combineSpec = combineNumSpec
2✔
1131
  genFromTypeSpec = genFromNumSpec
2✔
1132
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1133
  fixupWithTypeSpec = fixupWithNumSpec
×
1134
  conformsTo = conformsToNumSpec
2✔
1135
  toPreds = toPredsNumSpec
2✔
1136
  cardinalTypeSpec = cardinalNumSpec
×
1137
  cardinalTrueSpec = equalSpec 256
×
1138
  typeSpecOpt = notInNumSpec
2✔
1139
  guardTypeSpec = guardNumSpec
2✔
1140

1141
instance HasSpec Word16 where
×
1142
  type TypeSpec Word16 = NumSpec Word16
1143
  emptySpec = emptyNumSpec
2✔
1144
  combineSpec = combineNumSpec
2✔
1145
  genFromTypeSpec = genFromNumSpec
2✔
1146
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1147
  fixupWithTypeSpec = fixupWithNumSpec
×
1148
  conformsTo = conformsToNumSpec
2✔
1149
  toPreds = toPredsNumSpec
×
1150
  cardinalTypeSpec = cardinalNumSpec
×
1151
  cardinalTrueSpec = equalSpec 65536
×
1152
  guardTypeSpec = guardNumSpec
2✔
1153

1154
instance HasSpec Word32 where
×
1155
  type TypeSpec Word32 = NumSpec Word32
1156
  emptySpec = emptyNumSpec
2✔
1157
  combineSpec = combineNumSpec
2✔
1158
  genFromTypeSpec = genFromNumSpec
2✔
1159
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1160
  fixupWithTypeSpec = fixupWithNumSpec
×
1161
  conformsTo = conformsToNumSpec
2✔
1162
  toPreds = toPredsNumSpec
×
1163
  cardinalTypeSpec = cardinalNumSpec
×
1164
  guardTypeSpec = guardNumSpec
2✔
1165

1166
instance HasSpec Word64 where
×
1167
  type TypeSpec Word64 = NumSpec Word64
1168
  emptySpec = emptyNumSpec
2✔
1169
  combineSpec = combineNumSpec
2✔
1170
  genFromTypeSpec = genFromNumSpec
2✔
1171
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1172
  fixupWithTypeSpec = fixupWithNumSpec
×
1173
  conformsTo = conformsToNumSpec
2✔
1174
  toPreds = toPredsNumSpec
2✔
1175
  cardinalTypeSpec = cardinalNumSpec
2✔
1176
  guardTypeSpec = guardNumSpec
2✔
1177

1178
instance HasSpec Int8 where
×
1179
  type TypeSpec Int8 = NumSpec Int8
1180
  emptySpec = emptyNumSpec
2✔
1181
  combineSpec = combineNumSpec
2✔
1182
  genFromTypeSpec = genFromNumSpec
2✔
1183
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1184
  fixupWithTypeSpec = fixupWithNumSpec
×
1185
  conformsTo = conformsToNumSpec
2✔
1186
  toPreds = toPredsNumSpec
2✔
1187
  cardinalTrueSpec = equalSpec 256
×
1188
  cardinalTypeSpec = cardinalNumSpec
×
1189
  guardTypeSpec = guardNumSpec
2✔
1190

1191
instance HasSpec Int16 where
×
1192
  type TypeSpec Int16 = NumSpec Int16
1193
  emptySpec = emptyNumSpec
2✔
1194
  combineSpec = combineNumSpec
2✔
1195
  genFromTypeSpec = genFromNumSpec
2✔
1196
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1197
  fixupWithTypeSpec = fixupWithNumSpec
×
1198
  conformsTo = conformsToNumSpec
2✔
1199
  toPreds = toPredsNumSpec
×
1200
  cardinalTypeSpec = cardinalNumSpec
×
1201
  cardinalTrueSpec = equalSpec 65536
×
1202
  guardTypeSpec = guardNumSpec
2✔
1203

1204
instance HasSpec Int32 where
×
1205
  type TypeSpec Int32 = NumSpec Int32
1206
  emptySpec = emptyNumSpec
2✔
1207
  combineSpec = combineNumSpec
2✔
1208
  genFromTypeSpec = genFromNumSpec
2✔
1209
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1210
  fixupWithTypeSpec = fixupWithNumSpec
×
1211
  conformsTo = conformsToNumSpec
2✔
1212
  toPreds = toPredsNumSpec
×
1213
  cardinalTypeSpec = cardinalNumSpec
×
1214
  guardTypeSpec = guardNumSpec
2✔
1215

1216
instance HasSpec Int64 where
×
1217
  type TypeSpec Int64 = NumSpec Int64
1218
  emptySpec = emptyNumSpec
2✔
1219
  combineSpec = combineNumSpec
2✔
1220
  genFromTypeSpec = genFromNumSpec
2✔
1221
  shrinkWithTypeSpec = shrinkWithNumSpec
2✔
1222
  fixupWithTypeSpec = fixupWithNumSpec
×
1223
  conformsTo = conformsToNumSpec
2✔
1224
  toPreds = toPredsNumSpec
×
1225
  cardinalTypeSpec = cardinalNumSpec
×
1226
  guardTypeSpec = guardNumSpec
2✔
1227

1228
instance HasSpec Float where
×
1229
  type TypeSpec Float = NumSpec Float
1230
  emptySpec = emptyNumSpec
2✔
1231
  combineSpec = combineNumSpec
2✔
1232
  genFromTypeSpec = genFromNumSpec
2✔
1233
  shrinkWithTypeSpec = shrinkWithNumSpec
×
1234
  fixupWithTypeSpec = fixupWithNumSpec
×
1235
  conformsTo = conformsToNumSpec
2✔
1236
  toPreds = toPredsNumSpec
2✔
1237
  cardinalTypeSpec _ = TrueSpec
×
1238
  guardTypeSpec = guardNumSpec
2✔
1239

1240
instance HasSpec Double where
×
1241
  type TypeSpec Double = NumSpec Double
1242
  emptySpec = emptyNumSpec
2✔
1243
  combineSpec = combineNumSpec
2✔
1244
  genFromTypeSpec = genFromNumSpec
2✔
1245
  shrinkWithTypeSpec = shrinkWithNumSpec
×
1246
  fixupWithTypeSpec = fixupWithNumSpec
×
1247
  conformsTo = conformsToNumSpec
2✔
1248
  toPreds = toPredsNumSpec
2✔
1249
  cardinalTypeSpec _ = TrueSpec
×
1250
  guardTypeSpec = guardNumSpec
2✔
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc