Skip to content

Commit 8788d28

Browse files
WIP initial (broken, but close) attempt at multiplication
1 parent 45559e0 commit 8788d28

File tree

3 files changed

+94
-20
lines changed

3 files changed

+94
-20
lines changed

src/Constrained/NumOrd.hs

Lines changed: 86 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ module Constrained.NumOrd (
2828
(>=.),
2929
(<=.),
3030
(+.),
31+
(*.),
3132
negate_,
3233
cardinality,
3334
caseBoolSpec,
@@ -202,6 +203,8 @@ deriving via Unbounded (Ratio Integer) instance MaybeBounded (Ratio Integer)
202203

203204
deriving via Unbounded Float instance MaybeBounded Float
204205

206+
deriving via Unbounded Double instance MaybeBounded Double
207+
205208
instance MaybeBounded Natural where
206209
lowerBound = Just 0
207210
upperBound = Nothing
@@ -651,7 +654,7 @@ cardinalNumSpec (NumSpecInterval Nothing Nothing) = cardinalTrueSpec @n
651654
-- Now the operations on Numbers
652655

653656
-- | Everything we need to make the number operations make sense on a given type
654-
class (Num a, HasSpec a) => NumLike a where
657+
class (Num a, HasSpec a, HasDivision a) => NumLike a where
655658
subtractSpec :: a -> TypeSpec a -> Specification a
656659
default subtractSpec ::
657660
( NumLike (SimpleRep a)
@@ -682,24 +685,67 @@ class (Num a, HasSpec a) => NumLike a where
682685
-- | Operations on numbers
683686
data IntW (as :: [Type]) b where
684687
AddW :: NumLike a => IntW '[a, a] a
688+
MultW :: NumLike a => IntW '[a, a] a
685689
NegateW :: NumLike a => IntW '[a] a
686690

687691
deriving instance Eq (IntW dom rng)
688692

689693
instance Show (IntW d r) where
690694
show AddW = "+"
691695
show NegateW = "negate_"
696+
show MultW = "*"
692697

693698
instance Semantics IntW where
694699
semantics AddW = (+)
695700
semantics NegateW = negate
701+
semantics MultW = (*)
696702

697703
instance Syntax IntW where
698704
isInfix AddW = True
699705
isInfix NegateW = False
706+
isInfix MultW = True
707+
708+
class HasDivision a where
709+
doDivide :: a -> a -> a
710+
default doDivide ::
711+
( HasDivision (SimpleRep a)
712+
, GenericRequires a
713+
) =>
714+
a ->
715+
a ->
716+
a
717+
doDivide a b = fromSimpleRep $ doDivide (toSimpleRep a) (toSimpleRep b)
718+
719+
divideSpec :: a -> TypeSpec a -> Specification a
720+
default divideSpec ::
721+
( HasDivision (SimpleRep a)
722+
, GenericRequires a
723+
) =>
724+
a ->
725+
TypeSpec a ->
726+
Specification a
727+
divideSpec a ts = fromSimpleRepSpec $ divideSpec (toSimpleRep a) ts
728+
729+
instance {-# OVERLAPPABLE #-} (HasSpec a, Integral a, TypeSpec a ~ NumSpec a) => HasDivision a where
730+
doDivide = div
731+
732+
divideSpec 0 _ = TrueSpec
733+
divideSpec a (NumSpecInterval ml mu) = typeSpec $ NumSpecInterval (((`div`a) . (+1)) <$> ml) ((`div`a) <$> mu)
734+
735+
instance HasDivision Float where
736+
doDivide = (/)
737+
738+
divideSpec 0 _ = TrueSpec
739+
divideSpec a (NumSpecInterval ml mu) = typeSpec $ NumSpecInterval ((/a) <$> ml) ((/a) <$> mu)
740+
741+
instance HasDivision Double where
742+
doDivide = (/)
743+
744+
divideSpec 0 _ = TrueSpec
745+
divideSpec a (NumSpecInterval ml mu) = typeSpec $ NumSpecInterval ((/a) <$> ml) ((/a) <$> mu)
700746

701747
-- | A type that we can reason numerically about in constraints
702-
type Numeric a = (HasSpec a, Ord a, Num a, TypeSpec a ~ NumSpec a, MaybeBounded a)
748+
type Numeric a = (HasSpec a, Ord a, Num a, TypeSpec a ~ NumSpec a, MaybeBounded a, HasDivision a)
703749

704750
instance {-# OVERLAPPABLE #-} Numeric a => NumLike a where
705751
subtractSpec a ts@(NumSpecInterval ml mu)
@@ -728,6 +774,7 @@ instance {-# OVERLAPPABLE #-} Numeric a => NumLike a where
728774
| Just r <- safeSubtract a1 x = r
729775
| a1 < 0 = fromJust upperBound
730776
| otherwise = fromJust lowerBound
777+
731778
negateSpec (NumSpecInterval ml mu) = typeSpec $ NumSpecInterval (negate <$> mu) (negate <$> ml)
732779

733780
safeSubtract a x
@@ -742,20 +789,29 @@ instance {-# OVERLAPPABLE #-} Numeric a => NumLike a where
742789
| otherwise = Just $ x - a
743790

744791
instance NumLike a => Num (Term a) where
745-
(+) = addFn
746-
negate = negateFn
792+
(+) = (+.)
793+
negate = negate_
747794
fromInteger = Lit . fromInteger
748-
(*) = error "(*) not implemented for Term Fn Int"
795+
(*) = (*.)
749796
abs = error "abs not implemented for Term Fn Int"
750797
signum = error "signum not implemented for Term Fn Int"
751798

799+
invertMult :: (HasSpec a, Num a, HasDivision a) => a -> a -> Maybe a
800+
invertMult a b =
801+
let r = a `doDivide` b in if r * b == a then Just r else Nothing
802+
752803
-- | Just a note that these instances won't work until we are in a context where
753804
-- there is a HasSpec instance of 'a', which (NumLike a) demands.
754805
-- This happens in Constrained.Experiment.TheKnot
755806
instance Logic IntW where
756807
propagateTypeSpec AddW (HOLE :<: i) ts cant = subtractSpec i ts <> notMemberSpec (mapMaybe (safeSubtract i) cant)
757808
propagateTypeSpec AddW ctx ts cant = propagateTypeSpec AddW (flipCtx ctx) ts cant
758809
propagateTypeSpec NegateW (Unary HOLE) ts cant = negateSpec ts <> notMemberSpec (map negate cant)
810+
propagateTypeSpec MultW (HOLE :<: 0) ts cant
811+
| 0 `conformsToSpec` TypeSpec ts cant = TrueSpec
812+
| otherwise = ErrorSpec $ NE.fromList [ "zero" ]
813+
propagateTypeSpec MultW (HOLE :<: i) ts cant = divideSpec i ts <> notMemberSpec (mapMaybe (flip invertMult i) cant)
814+
propagateTypeSpec MultW ctx ts cant = propagateTypeSpec MultW (flipCtx ctx) ts cant
759815

760816
propagateMemberSpec AddW (HOLE :<: i) es =
761817
memberSpec
@@ -768,28 +824,33 @@ instance Logic IntW where
768824
)
769825
propagateMemberSpec AddW ctx es = propagateMemberSpec AddW (flipCtx ctx) es
770826
propagateMemberSpec NegateW (Unary HOLE) es = MemberSpec $ NE.nub $ fmap negate es
771-
772-
addFn :: forall a. NumLike a => Term a -> Term a -> Term a
773-
addFn = appTerm AddW
774-
775-
negateFn :: forall a. NumLike a => Term a -> Term a
776-
negateFn = appTerm NegateW
827+
propagateMemberSpec MultW (HOLE :<: 0) es
828+
| 0 `elem` es = TrueSpec
829+
| otherwise = ErrorSpec $ NE.fromList [ "zero" ]
830+
propagateMemberSpec MultW (HOLE :<: i) es = memberSpec (mapMaybe (flip invertMult i) (NE.toList es)) (NE.fromList ["propagateSpec"])
831+
propagateMemberSpec MultW ctx es = propagateMemberSpec MultW (flipCtx ctx) es
777832

778833
infix 4 +.
779834

780835
-- | `Term`-level `(+)`
781836
(+.) :: NumLike a => Term a -> Term a -> Term a
782-
(+.) = addFn
837+
(+.) = appTerm AddW
838+
839+
infixl 7 *.
840+
841+
-- | `Term`-level `(+)`
842+
(*.) :: NumLike a => Term a -> Term a -> Term a
843+
(*.) = appTerm MultW
783844

784845
-- | `Term`-level `negate`
785846
negate_ :: NumLike a => Term a -> Term a
786-
negate_ = negateFn
847+
negate_ = appTerm NegateW
787848

788849
infix 4 -.
789850

790851
-- | `Term`-level `(-)`
791852
(-.) :: Numeric n => Term n -> Term n -> Term n
792-
(-.) x y = addFn x (negateFn y)
853+
(-.) x y = x +. negate_ y
793854

794855
infixr 4 <=.
795856

@@ -1029,3 +1090,14 @@ instance HasSpec Float where
10291090
toPreds = toPredsNumSpec
10301091
cardinalTypeSpec _ = TrueSpec
10311092
guardTypeSpec = guardNumSpec
1093+
1094+
instance HasSpec Double where
1095+
type TypeSpec Double = NumSpec Double
1096+
emptySpec = emptyNumSpec
1097+
combineSpec = combineNumSpec
1098+
genFromTypeSpec = genFromNumSpec
1099+
shrinkWithTypeSpec = shrinkWithNumSpec
1100+
conformsTo = conformsToNumSpec
1101+
toPreds = toPredsNumSpec
1102+
cardinalTypeSpec _ = TrueSpec
1103+
guardTypeSpec = guardNumSpec

src/Constrained/SumList.hs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -166,10 +166,8 @@ genNumList ::
166166
( MonadGenError m
167167
, Arbitrary a
168168
, Integral a
169-
, MaybeBounded a
170-
, TypeSpec a ~ NumSpec a
171-
, -- , Foldy a
172-
Random a
169+
, Numeric a
170+
, Random a
173171
, Complete a
174172
) =>
175173
Specification a ->
@@ -470,12 +468,11 @@ narrowByFuelAndSize fuel size specpair =
470468
genListWithSize ::
471469
forall a m.
472470
( Complete a
473-
, TypeSpec a ~ NumSpec a
474471
, MonadGenError m
475472
, Random a
476473
, Integral a
477474
, Arbitrary a
478-
, MaybeBounded a
475+
, Numeric a
479476
, Complete Integer
480477
) =>
481478
Specification Integer ->

src/Constrained/Test.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ module Constrained.Test (
2424
prop_propagateSpecSound,
2525
prop_gen_sound,
2626
specType,
27+
TestableFn(..),
2728
) where
2829

2930
import Constrained.API.Extend
@@ -47,6 +48,7 @@ import Data.Typeable (Typeable, typeOf)
4748
import Prettyprinter
4849
import Test.QuickCheck hiding (Fun)
4950
import qualified Test.QuickCheck as QC
51+
import Data.Word
5052

5153
-- | Check that a generator from a given `Specification` is sound, it never
5254
-- generates a bad value that doesn't satisfy the constraint
@@ -389,6 +391,9 @@ instance QC.Arbitrary TestableFn where
389391
[ -- data IntW
390392
TestableFn $ AddW @Int
391393
, TestableFn $ NegateW @Int
394+
, TestableFn $ MultW @Int
395+
, TestableFn $ MultW @Float
396+
, TestableFn $ MultW @Word8
392397
, TestableFn $ SizeOfW @(Map Int Int)
393398
, -- data BaseW
394399
TestableFn $ EqualW @Int

0 commit comments

Comments
 (0)