How to expose if a constraint is satisfiable

It's occurred to me that one could write a class C t which is satisfied whenever (A t) or (B t) is satisfied like so: --- data Satisfied type family IsSatisfiable :: Constraint -> Type class A t class B t class C' t ta tb instance A t => C' t Satisfied tb where ... instance B t => C' t ta Satisfied where ... instance (A t, B t) => C' t Satisfied Satisfied where ... class C' t ( IsSatisfiable (A t)) ( IsSatisfiable (B t)) => C t --- We may need overlapping instances (with all the caveats that come with it) but it should be fine otherwise. "IsSatisfiable" here is defined as follows: IsSatisfiable c = Satisfied -- (if c is satisfiable) IsSatisfiable c = IsSatisfiable c -- (if c is not satisfiable) That's all that's needed. And it seems to be a reasonable type function. I note classes are open, so perhaps it could be dangerous to state that a constraint is not satisfiable (because it might be in another part of a program) but simply not reducing if we can't satisfy the constraint locally should be fine I think. At worst we'll get a compile error, but we shouldn't get inconsistent types. Is there anyway to implement this type function, or alternatively an approach which allows this type of "inherit from two classes" idea?

Hi Clinton,
instance A t => C' t Satisfied tb where ...
instance B t => C' t ta Satisfied where ...
instance (A t, B t) => C' t Satisfied Satisfied where ...
The first two instances will only be picked if `ta` or `tb` can be determined to not "unify" with `Satisfied`. But a type family that cannot reduce will still "unify" with anything (it might just be that the rules to reduce it exist but are not in scope). I'm not sure "unify" is the right term when talking about this behavior of type families, but it's the one used in describing the instance resolution algorithm ("find all instances that unify with the target constraint"): https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts... These instances are only useful if we can actually decide satisfiability of constraints, which contradicts the open-world assumption as you mentioned. IsSatisfiable c = Satisfied -- (if c is satisfiable) IsSatisfiable c = Unsatisfiable -- (if c is not satisfiable) Regards, Li-yao

On Mon, May 7, 2018 at 10:27 PM, Li-yao Xia
Hi Clinton,
instance A t => C' t Satisfied tb where
...
instance B t => C' t ta Satisfied where ...
instance (A t, B t) => C' t Satisfied Satisfied where ...
The first two instances will only be picked if `ta` or `tb` can be determined to not "unify" with `Satisfied`. But a type family that cannot reduce will still "unify" with anything (it might just be that the rules to reduce it exist but are not in scope).
Why is this the case? Can't the first instance be picked even if tb hasn't been determined not to unify with "Satisfied", as long as the 2nd type variable does unify with "Satisfied"?
I'm not sure "unify" is the right term when talking about this behavior of type families, but it's the one used in describing the instance resolution algorithm ("find all instances that unify with the target constraint"): https://downloads.haskell.org/~ghc/latest/docs/html/users_gu ide/glasgow_exts.html#overlapping-instances
These instances are only useful if we can actually decide satisfiability of constraints, which contradicts the open-world assumption as you mentioned.
IsSatisfiable c = Satisfied -- (if c is satisfiable) IsSatisfiable c = Unsatisfiable -- (if c is not satisfiable)
But your example is different to mine. I've said I'm looking for the following:
IsSatisfiable c = Satisfied -- (if c is satisfiable) IsSatisfiable c = *IsSatisfiable c* -- (if c is not satisfiable) Notice I never mentioned "Unsatisfiable". Without "Unsatisfiable", I don't see how this violates the open-world assumption.
Regards, Li-yao
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi Clinton, On 05/07/2018 08:39 AM, Clinton Mead wrote:
On Mon, May 7, 2018 at 10:27 PM, Li-yao Xia
mailto:lysxia@gmail.com> wrote: Hi Clinton,
instance A t => C' t Satisfied tb where ...
instance B t => C' t ta Satisfied where ...
instance (A t, B t) => C' t Satisfied Satisfied where ...
The first two instances will only be picked if `ta` or `tb` can be determined to not "unify" with `Satisfied`. But a type family that cannot reduce will still "unify" with anything (it might just be that the rules to reduce it exist but are not in scope).
Why is this the case? Can't the first instance be picked even if tb hasn't been determined not to unify with "Satisfied", as long as the 2nd type variable does unify with "Satisfied"?
If you pick an instance to solve a constraint that still unifies with another one, the broken assumption is uniqueness of instances. Many libraries assume instances are unique. The most common example is containers, which uses Ord to implement Set/Map with binary search trees. (De)serialization libraries are another example. For a concrete illustration, consider the following newtype, whose Ord instance depends on the existence of Ord or Show for the wrapped type: newtype T a = T a instance OrdIf a (IsSatisfiable (Ord a)) (IsSatisfiable (Show a)) => Ord (T a) where compare = compareIf class OrdIf a ta tb where compareIf :: a -> a -> Ordering instance Ord a => OrdIf a Satisfied tb where compareIf (T a) (T b) = compare a b instance Show a => OrdIf a ta Satisfied where compareIf (T a) (T b) = compare (show a) (show b) instance Ord a => OrdIf a Satisfied Satisfied where compareIf (T a) (T b) = compare b a -- flipped We can have the following three definitions, that use three different instances for (Ord (T a)). f1 :: Ord a => T a -> T a -> Ordering f1 = compare -- first OrdIf instance f2 :: Show a => T a -> T a -> Ordering f2 = compare -- second OrdIf instance f3 :: (Ord a, Show a) => T a -> T a -> Ordering f3 = compare -- third OrdIf instance Now specialize them to a type that has both Ord and Show instances. g1 :: T Int -> T Int -> Ordering g1 = f1 g2 :: T Int -> T Int -> Ordering g2 = f2 g3 :: T Int -> T Int -> Ordering g3 = f3 Referential transparency is lost. If you replace fi (for i=1,2,3) with its body (compare), only g3 doesn't change meaning (and that's assuming the most specific instance was picked in f3, which can be nontrivial to guarantee in general without that rule about ensuring there is no other unifiable instance). g4 :: T Int -> T Int -> Ordering g4 = compare Perhaps a more general litmus test for features related to instance resolution is: can the meaning of a well-typed polymorphic function change if I make it (more) monomorphic, or if I add instances to the context? I believe I demonstrated that can happen above, which is bad. The rationale is that we should be able to understand what a function does without keeping track of all instances we import (it's right there in the PVP that new non-orphan instances are not breaking changes), and without knowing the exact types of local functions (it happens often that a function has a much more general inferred type than what we have in mind).
These instances are only useful if we can actually decide satisfiability of constraints, which contradicts the open-world assumption as you mentioned.
IsSatisfiable c = Satisfied -- (if c is satisfiable) IsSatisfiable c = Unsatisfiable -- (if c is not satisfiable)
But your example is different to mine. I've said I'm looking for the following:
IsSatisfiable c = Satisfied -- (if c is satisfiable) IsSatisfiable c =*IsSatisfiable c*-- (if c is not satisfiable)
Notice I never mentioned "Unsatisfiable". Without "Unsatisfiable", I don't see how this violates the open-world assumption.
Sorry, that was a clumsy way for me to say that this approach you propose would not work. Regards, Li-yao

Hi Li-yao
I understand this issue, but I think what your describing doesn't relate to
what I'm talking about uniquely.
For example:
instance {-# OVERLAPPABLE #-} Num x => C x where ...
instance {-# OVERLAPPING #-} C Int where ...
is completely legal, and the instance used depends on context.
This is an issue with overlapping instances, but already GHC allows it. I
don't think what I'm proposing is any worse to what's already legal.
On Tue, May 8, 2018 at 1:34 PM, Li-yao Xia
Hi Clinton,
On 05/07/2018 08:39 AM, Clinton Mead wrote:
On Mon, May 7, 2018 at 10:27 PM, Li-yao Xia
> wrote: Hi Clinton,
instance A t => C' t Satisfied tb where ...
instance B t => C' t ta Satisfied where ...
instance (A t, B t) => C' t Satisfied Satisfied where ...
The first two instances will only be picked if `ta` or `tb` can be determined to not "unify" with `Satisfied`. But a type family that cannot reduce will still "unify" with anything (it might just be that the rules to reduce it exist but are not in scope).
Why is this the case? Can't the first instance be picked even if tb hasn't been determined not to unify with "Satisfied", as long as the 2nd type variable does unify with "Satisfied"?
If you pick an instance to solve a constraint that still unifies with another one, the broken assumption is uniqueness of instances. Many libraries assume instances are unique. The most common example is containers, which uses Ord to implement Set/Map with binary search trees. (De)serialization libraries are another example.
For a concrete illustration, consider the following newtype, whose Ord instance depends on the existence of Ord or Show for the wrapped type:
newtype T a = T a
instance OrdIf a (IsSatisfiable (Ord a)) (IsSatisfiable (Show a)) => Ord (T a) where compare = compareIf
class OrdIf a ta tb where compareIf :: a -> a -> Ordering
instance Ord a => OrdIf a Satisfied tb where compareIf (T a) (T b) = compare a b
instance Show a => OrdIf a ta Satisfied where compareIf (T a) (T b) = compare (show a) (show b)
instance Ord a => OrdIf a Satisfied Satisfied where compareIf (T a) (T b) = compare b a -- flipped
We can have the following three definitions, that use three different instances for (Ord (T a)).
f1 :: Ord a => T a -> T a -> Ordering f1 = compare -- first OrdIf instance
f2 :: Show a => T a -> T a -> Ordering f2 = compare -- second OrdIf instance
f3 :: (Ord a, Show a) => T a -> T a -> Ordering f3 = compare -- third OrdIf instance
Now specialize them to a type that has both Ord and Show instances.
g1 :: T Int -> T Int -> Ordering g1 = f1
g2 :: T Int -> T Int -> Ordering g2 = f2
g3 :: T Int -> T Int -> Ordering g3 = f3
Referential transparency is lost. If you replace fi (for i=1,2,3) with its body (compare), only g3 doesn't change meaning (and that's assuming the most specific instance was picked in f3, which can be nontrivial to guarantee in general without that rule about ensuring there is no other unifiable instance).
g4 :: T Int -> T Int -> Ordering g4 = compare
Perhaps a more general litmus test for features related to instance resolution is: can the meaning of a well-typed polymorphic function change if I make it (more) monomorphic, or if I add instances to the context? I believe I demonstrated that can happen above, which is bad.
The rationale is that we should be able to understand what a function does without keeping track of all instances we import (it's right there in the PVP that new non-orphan instances are not breaking changes), and without knowing the exact types of local functions (it happens often that a function has a much more general inferred type than what we have in mind).
These instances are only useful if we can actually decide
satisfiability of constraints, which contradicts the open-world assumption as you mentioned.
IsSatisfiable c = Satisfied -- (if c is satisfiable) IsSatisfiable c = Unsatisfiable -- (if c is not satisfiable)
But your example is different to mine. I've said I'm looking for the following:
IsSatisfiable c = Satisfied -- (if c is satisfiable) IsSatisfiable c =*IsSatisfiable c*-- (if c is not satisfiable)
Notice I never mentioned "Unsatisfiable". Without "Unsatisfiable", I don't see how this violates the open-world assumption.
Sorry, that was a clumsy way for me to say that this approach you propose would not work.
Regards, Li-yao

On Mon, May 7, 2018 at 11:45 PM, Clinton Mead
instance {-# OVERLAPPABLE #-} Num x => C x where ... instance {-# OVERLAPPING #-} C Int where ...
is completely legal, and the instance used depends on context.
This is an issue with overlapping instances, but already GHC allows it. I don't think what I'm proposing is any worse to what's already legal.
Int can be verified as more specific than "matches any type". Two instance heads differing *only* in context cannot. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On 05/07/2018 11:45 PM, Clinton Mead wrote:
Hi Li-yao
I understand this issue, but I think what your describing doesn't relate to what I'm talking about uniquely.
For example:
instance {-# OVERLAPPABLE #-} Num x => C x where ... instance {-# OVERLAPPING #-} C Int where ...
is completely legal, and the instance used depends on context.
This is an issue with overlapping instances, but already GHC allows it. I don't think what I'm proposing is any worse to what's already legal.
No instance for the C type class above will be picked until x is equal to some applied type constructor; it will be more challenging to break coherence with that than using what you're proposing. It seems difficult to make a clear point because the whole topic of coherence with Haskell type classes is already a minefield. Li-yao

I've only skimmed the thread, so sorry if this is a red herring, but could
this be helpful?
https://github.com/rampion/constraint-unions/blob/master/README.md
On Tue, May 8, 2018 at 12:49 PM, Li-yao Xia
On 05/07/2018 11:45 PM, Clinton Mead wrote:
Hi Li-yao
I understand this issue, but I think what your describing doesn't relate to what I'm talking about uniquely.
For example:
instance {-# OVERLAPPABLE #-} Num x => C x where ... instance {-# OVERLAPPING #-} C Int where ...
is completely legal, and the instance used depends on context.
This is an issue with overlapping instances, but already GHC allows it. I don't think what I'm proposing is any worse to what's already legal.
No instance for the C type class above will be picked until x is equal to some applied type constructor; it will be more challenging to break coherence with that than using what you're proposing.
It seems difficult to make a clear point because the whole topic of coherence with Haskell type classes is already a minefield.
Li-yao _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Maybe look at https://www.reddit.com/r/haskell/comments/6k86je/constraint_unions_bringing_...
(relating to the repository Oliver links to) and note also Edward
Kmett's response.
On Tue, May 8, 2018 at 9:52 AM, Oliver Charles
I've only skimmed the thread, so sorry if this is a red herring, but could this be helpful? https://github.com/rampion/constraint-unions/blob/master/README.md
On Tue, May 8, 2018 at 12:49 PM, Li-yao Xia
wrote: On 05/07/2018 11:45 PM, Clinton Mead wrote:
Hi Li-yao
I understand this issue, but I think what your describing doesn't relate to what I'm talking about uniquely.
For example:
instance {-# OVERLAPPABLE #-} Num x => C x where ... instance {-# OVERLAPPING #-} C Int where ...
is completely legal, and the instance used depends on context.
This is an issue with overlapping instances, but already GHC allows it. I don't think what I'm proposing is any worse to what's already legal.
No instance for the C type class above will be picked until x is equal to some applied type constructor; it will be more challenging to break coherence with that than using what you're proposing.
It seems difficult to make a clear point because the whole topic of coherence with Haskell type classes is already a minefield.
Li-yao _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (5)
-
Brandon Allbery
-
Clinton Mead
-
David Feuer
-
Li-yao Xia
-
Oliver Charles