@@ -656,7 +656,7 @@ cardinalNumSpec (NumSpecInterval Nothing Nothing) = cardinalTrueSpec @n
656656-- Now the operations on Numbers
657657
658658-- | Everything we need to make the number operations make sense on a given type
659- class (Num a , HasSpec a , HasDivision a ) => NumLike a where
659+ class (Num a , HasSpec a , HasDivision a , OrdLike a ) => NumLike a where
660660 subtractSpec :: a -> TypeSpec a -> Specification a
661661 default subtractSpec ::
662662 ( NumLike (SimpleRep a)
@@ -684,28 +684,40 @@ class (Num a, HasSpec a, HasDivision a) => NumLike a where
684684 Maybe a
685685 safeSubtract a b = fromSimpleRep <$> safeSubtract @ (SimpleRep a ) (toSimpleRep a) (toSimpleRep b)
686686
687- -- | Operations on numbers
687+ -- | Operations on numbers.
688+ -- The reason there is no implementation of abs here is that you can't easily deal with abs
689+ -- without specifications becoming very large. Consider the following example:
690+ -- > constrained $ \ x -> [1000 <. abs_ x, abs_ x <. 1050]
691+ -- The natural `Specification` here would be something like `(-1050, -1000) || (1000, 1050)`
692+ -- - the disjoint union of two open, non-overlapping, intervals. However, this doesn't work
693+ -- because number type-specs only support a single interval. You could fudge it in all sorts of ways
694+ -- by using `chooseSpec` or by using the can't set (which would blow up to be 2000 elements large in this
695+ -- case). In short, there is no _satisfactory_ solution here.
688696data IntW (as :: [Type ]) b where
689697 AddW :: NumLike a => IntW '[a , a ] a
690698 MultW :: NumLike a => IntW '[a , a ] a
691699 NegateW :: NumLike a => IntW '[a ] a
700+ SignumW :: NumLike a => IntW '[a ] a
692701
693702deriving instance Eq (IntW dom rng )
694703
695704instance Show (IntW d r ) where
696705 show AddW = " +"
697706 show NegateW = " negate_"
698707 show MultW = " *"
708+ show SignumW = " signum_"
699709
700710instance Semantics IntW where
701711 semantics AddW = (+)
702712 semantics NegateW = negate
703713 semantics MultW = (*)
714+ semantics SignumW = signum
704715
705716instance Syntax IntW where
706717 isInfix AddW = True
707718 isInfix NegateW = False
708719 isInfix MultW = True
720+ isInfix SignumW = False
709721
710722class HasDivision a where
711723 doDivide :: a -> a -> a
@@ -860,8 +872,8 @@ instance NumLike a => Num (Term a) where
860872 negate = negate_
861873 fromInteger = Lit . fromInteger
862874 (*) = (*.)
863- abs = error " abs not implemented for Term Fn Int "
864- signum = error " signum not implemented for Term Fn Int "
875+ signum = signum_
876+ abs = error " No implementation for abs @( Term a) "
865877
866878invertMult :: (HasSpec a , Num a , HasDivision a ) => a -> a -> Maybe a
867879invertMult a b =
@@ -879,6 +891,12 @@ instance Logic IntW where
879891 | otherwise = ErrorSpec $ NE. fromList [ " zero" ]
880892 propagateTypeSpec MultW (HOLE :<: i) ts cant = divideSpec i ts <> notMemberSpec (mapMaybe (flip invertMult i) cant)
881893 propagateTypeSpec MultW ctx ts cant = propagateTypeSpec MultW (flipCtx ctx) ts cant
894+ propagateTypeSpec SignumW (Unary HOLE ) ts cant =
895+ constrained $ \ x ->
896+ [ x `satisfies` notMemberSpec [0 ] | not $ ok 0 ] ++
897+ [ Assert $ 0 <=. x | not $ ok (- 1 ) ] ++
898+ [ Assert $ x <=. 0 | not $ ok 1 ]
899+ where ok = flip conformsToSpec (TypeSpec ts cant)
882900
883901 propagateMemberSpec AddW (HOLE :<: i) es =
884902 memberSpec
@@ -896,6 +914,12 @@ instance Logic IntW where
896914 | otherwise = ErrorSpec $ NE. fromList [ " zero" ]
897915 propagateMemberSpec MultW (HOLE :<: i) es = memberSpec (mapMaybe (flip invertMult i) (NE. toList es)) (NE. fromList [" propagateSpec" ])
898916 propagateMemberSpec MultW ctx es = propagateMemberSpec MultW (flipCtx ctx) es
917+ propagateMemberSpec SignumW (Unary HOLE ) es
918+ | all ((`notElem` [- 1 , 0 , 1 ]) . signum ) es = ErrorSpec $ NE. fromList [ " signum for invalid member spec" , show es ]
919+ | otherwise = constrained $ \ x ->
920+ [ x `satisfies` notMemberSpec [0 ] | 0 `notElem` es ] ++
921+ [ Assert $ 0 <=. x | - 1 `notElem` es ] ++
922+ [ Assert $ x <=. 0 | 1 `notElem` es ]
899923
900924 rewriteRules AddW (x :> y :> Nil ) _ | x == y = Just $ 2 * x
901925 rewriteRules _ _ _ = Nothing
@@ -916,6 +940,10 @@ infixl 7 *.
916940negate_ :: NumLike a => Term a -> Term a
917941negate_ = appTerm NegateW
918942
943+ -- | `Term`-level `signum`
944+ signum_ :: NumLike a => Term a -> Term a
945+ signum_ = appTerm SignumW
946+
919947infix 4 -.
920948
921949-- | `Term`-level `(-)`
0 commit comments