@@ -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
203204deriving via Unbounded Float instance MaybeBounded Float
204205
206+ deriving via Unbounded Double instance MaybeBounded Double
207+
205208instance 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,92 @@ class (Num a, HasSpec a) => NumLike a where
682685-- | Operations on numbers
683686data 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
687691deriving instance Eq (IntW dom rng )
688692
689693instance Show (IntW d r ) where
690694 show AddW = " +"
691695 show NegateW = " negate_"
696+ show MultW = " *"
692697
693698instance Semantics IntW where
694699 semantics AddW = (+)
695700 semantics NegateW = negate
701+ semantics MultW = (*)
696702
697703instance 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+ -- TODO This is all wrong and hence the tests are all wrong
734+ divideSpec a (NumSpecInterval ml mu) = typeSpec ts
735+ where
736+ ts | a > 0 = NumSpecInterval ml' mu'
737+ | otherwise = NumSpecInterval mu' ml'
738+ ml' = adjustLowerBound <$> ml
739+ mu' = adjustUpperBound <$> mu
740+ adjustLowerBound l =
741+ let r = l `div` a in
742+ if r * a < l
743+ then r + 1
744+ else r
745+
746+ adjustUpperBound u =
747+ let r = u `div` a in
748+ if r * a > u
749+ then r - 1
750+ else r
751+
752+ instance HasDivision Float where
753+ doDivide = (/)
754+
755+ divideSpec 0 _ = TrueSpec
756+ divideSpec a (NumSpecInterval ml mu) = typeSpec ts
757+ where
758+ ts | a > 0 = NumSpecInterval ml' mu'
759+ | otherwise = NumSpecInterval mu' ml'
760+ ml' = adjustLowerBound <$> ml
761+ mu' = adjustUpperBound <$> mu
762+ adjustLowerBound l = l / a
763+
764+ adjustUpperBound u = u / a
765+
766+ instance HasDivision Double where
767+ doDivide = (/)
768+
769+ divideSpec 0 _ = TrueSpec
770+ divideSpec a (NumSpecInterval ml mu) = typeSpec $ NumSpecInterval ((/ a) <$> ml) ((/ a) <$> mu)
700771
701772-- | 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 )
773+ type Numeric a = (HasSpec a , Ord a , Num a , TypeSpec a ~ NumSpec a , MaybeBounded a , HasDivision a )
703774
704775instance {-# OVERLAPPABLE #-} Numeric a => NumLike a where
705776 subtractSpec a ts@ (NumSpecInterval ml mu)
@@ -728,6 +799,7 @@ instance {-# OVERLAPPABLE #-} Numeric a => NumLike a where
728799 | Just r <- safeSubtract a1 x = r
729800 | a1 < 0 = fromJust upperBound
730801 | otherwise = fromJust lowerBound
802+
731803 negateSpec (NumSpecInterval ml mu) = typeSpec $ NumSpecInterval (negate <$> mu) (negate <$> ml)
732804
733805 safeSubtract a x
@@ -742,20 +814,29 @@ instance {-# OVERLAPPABLE #-} Numeric a => NumLike a where
742814 | otherwise = Just $ x - a
743815
744816instance NumLike a => Num (Term a ) where
745- (+) = addFn
746- negate = negateFn
817+ (+) = (+.)
818+ negate = negate_
747819 fromInteger = Lit . fromInteger
748- (*) = error " (*) not implemented for Term Fn Int "
820+ (*) = (*.)
749821 abs = error " abs not implemented for Term Fn Int"
750822 signum = error " signum not implemented for Term Fn Int"
751823
824+ invertMult :: (HasSpec a , Num a , HasDivision a ) => a -> a -> Maybe a
825+ invertMult a b =
826+ let r = a `doDivide` b in if r * b == a then Just r else Nothing
827+
752828-- | Just a note that these instances won't work until we are in a context where
753829-- there is a HasSpec instance of 'a', which (NumLike a) demands.
754830-- This happens in Constrained.Experiment.TheKnot
755831instance Logic IntW where
756832 propagateTypeSpec AddW (HOLE :<: i) ts cant = subtractSpec i ts <> notMemberSpec (mapMaybe (safeSubtract i) cant)
757833 propagateTypeSpec AddW ctx ts cant = propagateTypeSpec AddW (flipCtx ctx) ts cant
758834 propagateTypeSpec NegateW (Unary HOLE ) ts cant = negateSpec ts <> notMemberSpec (map negate cant)
835+ propagateTypeSpec MultW (HOLE :<: 0 ) ts cant
836+ | 0 `conformsToSpec` TypeSpec ts cant = TrueSpec
837+ | otherwise = ErrorSpec $ NE. fromList [ " zero" ]
838+ propagateTypeSpec MultW (HOLE :<: i) ts cant = divideSpec i ts <> notMemberSpec (mapMaybe (flip invertMult i) cant)
839+ propagateTypeSpec MultW ctx ts cant = propagateTypeSpec MultW (flipCtx ctx) ts cant
759840
760841 propagateMemberSpec AddW (HOLE :<: i) es =
761842 memberSpec
@@ -768,28 +849,33 @@ instance Logic IntW where
768849 )
769850 propagateMemberSpec AddW ctx es = propagateMemberSpec AddW (flipCtx ctx) es
770851 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
852+ propagateMemberSpec MultW (HOLE :<: 0 ) es
853+ | 0 `elem` es = TrueSpec
854+ | otherwise = ErrorSpec $ NE. fromList [ " zero" ]
855+ propagateMemberSpec MultW (HOLE :<: i) es = memberSpec (mapMaybe (flip invertMult i) (NE. toList es)) (NE. fromList [" propagateSpec" ])
856+ propagateMemberSpec MultW ctx es = propagateMemberSpec MultW (flipCtx ctx) es
777857
778858infix 4 +.
779859
780860-- | `Term`-level `(+)`
781861(+.) :: NumLike a => Term a -> Term a -> Term a
782- (+.) = addFn
862+ (+.) = appTerm AddW
863+
864+ infixl 7 *.
865+
866+ -- | `Term`-level `(+)`
867+ (*.) :: NumLike a => Term a -> Term a -> Term a
868+ (*.) = appTerm MultW
783869
784870-- | `Term`-level `negate`
785871negate_ :: NumLike a => Term a -> Term a
786- negate_ = negateFn
872+ negate_ = appTerm NegateW
787873
788874infix 4 -.
789875
790876-- | `Term`-level `(-)`
791877(-.) :: Numeric n => Term n -> Term n -> Term n
792- (-.) x y = addFn x (negateFn y)
878+ (-.) x y = x +. negate_ y
793879
794880infixr 4 <=.
795881
@@ -1029,3 +1115,14 @@ instance HasSpec Float where
10291115 toPreds = toPredsNumSpec
10301116 cardinalTypeSpec _ = TrueSpec
10311117 guardTypeSpec = guardNumSpec
1118+
1119+ instance HasSpec Double where
1120+ type TypeSpec Double = NumSpec Double
1121+ emptySpec = emptyNumSpec
1122+ combineSpec = combineNumSpec
1123+ genFromTypeSpec = genFromNumSpec
1124+ shrinkWithTypeSpec = shrinkWithNumSpec
1125+ conformsTo = conformsToNumSpec
1126+ toPreds = toPredsNumSpec
1127+ cardinalTypeSpec _ = TrueSpec
1128+ guardTypeSpec = guardNumSpec
0 commit comments