Check a lack of a constraint?

Hello cafe, Is it possible in Haskell to check a lack of a certain constraint? For example, ``` foo :: C => a foo = undefined ``` Here `foo` can only be compiled if called with C satisfied. How do I write the opposite, so that `foo` is only possible to use when C is not satisfied? With best regards.

On Mon, 12 Jul 2021, Lana Black wrote:
Hello cafe,
Is it possible in Haskell to check a lack of a certain constraint?
For example,
``` foo :: C => a foo = undefined
```
Here `foo` can only be compiled if called with C satisfied. How do I write the opposite, so that `foo` is only possible to use when C is not satisfied?
Do you mean "C a"? Is it sensible to want this? Any instance that you import transitively will reduce the applicability of 'foo'.

On 12 Jul 2021, at 2:24 pm, Lana Black
wrote: Is it possible in Haskell to check a lack of a certain constraint?
Such a check is semantically dubious, because the complete list of instances for a given type is unknowable; given orphan instances, an instance could be defined in some module that has not been imported at the call site. So wanting to do this suggests the possibility of a design issue.
For example,
``` foo :: C => a foo = undefined
```
However, it is possible to get something along those lines with a closed type family and an explicit list of verboten types: {-# LANGUAGE DataKinds , FlexibleContexts , TypeFamilies , UndecidableInstances #-} import GHC.TypeLits (ErrorMessage(..), TypeError) type family Filtered a where Filtered Int = TypeError (Text "Ints not welcome here") Filtered a = a foo :: (Show a, a ~ Filtered a) => a -> String foo = show As seen in: λ> foo ('a' :: Char) "'a'" λ> foo (1 :: Int) <interactive>:2:1: error: • Ints not welcome here • In the expression: foo (1 :: Int) In an equation for ‘it’: it = foo (1 :: Int) -- Viktor.

On 12 Jul 2021, at 4:24 pm, Viktor Dukhovni
wrote: However, it is possible to get something along those lines with a closed type family and an explicit list of verboten types:
Somewhat cleaner (no complaints from -Wall, and the Filtered type family now returns a constraint): {-# LANGUAGE ConstraintKinds , DataKinds , FlexibleContexts , TypeFamilies , TypeOperators , UndecidableInstances #-} import GHC.TypeLits (ErrorMessage(..), TypeError) import Data.Kind (Constraint) type family Filtered a :: Constraint where Filtered Int = TypeError ('ShowType Int ':<>: 'Text "s not welcome here") Filtered a = () foo :: (Show a, Filtered a) => a -> String foo = show -- Viktor.

Oh, very nice approach Viktor. It really seems easier than having a custom typeclass for which the blessed types have an instance, if the set of verboten types is considerably smaller than the set of allowed types. Le 12/07/2021 à 22:59, Viktor Dukhovni a écrit :
On 12 Jul 2021, at 4:24 pm, Viktor Dukhovni
wrote: However, it is possible to get something along those lines with a closed type family and an explicit list of verboten types: Somewhat cleaner (no complaints from -Wall, and the Filtered type family now returns a constraint):
{-# LANGUAGE ConstraintKinds , DataKinds , FlexibleContexts , TypeFamilies , TypeOperators , UndecidableInstances #-}
import GHC.TypeLits (ErrorMessage(..), TypeError) import Data.Kind (Constraint)
type family Filtered a :: Constraint where Filtered Int = TypeError ('ShowType Int ':<>: 'Text "s not welcome here") Filtered a = ()
foo :: (Show a, Filtered a) => a -> String foo = show
-- Hécate ✨ 🐦: @TechnoEmpress IRC: Hecate WWW: https://glitchbra.in RUN: BSD

On Monday, 12 July 2021 20:59:46 UTC Viktor Dukhovni wrote:
On 12 Jul 2021, at 4:24 pm, Viktor Dukhovni
wrote: However, it is possible to get something along those lines with
a closed type family and an explicit list of verboten types: Somewhat cleaner (no complaints from -Wall, and the Filtered type family now returns a constraint):
{-# LANGUAGE ConstraintKinds , DataKinds , FlexibleContexts , TypeFamilies , TypeOperators , UndecidableInstances #-}
import GHC.TypeLits (ErrorMessage(..), TypeError) import Data.Kind (Constraint)
type family Filtered a :: Constraint where Filtered Int = TypeError ('ShowType Int ':<>: 'Text "s not welcome here") Filtered a = ()
foo :: (Show a, Filtered a) => a -> String foo = show
Thank you! I know this seems like an extreme case and I doubt I will ever use your example in any real application. My question was prompted by the package called reflection (https:// hackage.haskell.org/package/reflection-2.1.6/docs/Data-Reflection.html), that allows to implicitly pass data to functions via a typeclass dictionary. The big issue with it however is that you can pass values of same type multiple times, therefore shooting yourself in the foot somewhere.
From the manual:
give :: forall a r. a -> (Given a => r) -> r
Reify a value into an instance to be recovered with given.
You should only give a single value for each type. If multiple instances are in scope, then the behavior is implementation defined.
I was curious whether it would be possible to allow `give` to be used only once in the same call stack with something like give :: forall a r. Not (Given a) => a -> (Given a => r) -> r If this even makes sense.

On Tue, Jul 13, 2021 at 03:07:39PM +0000, Lana Black wrote:
type family Filtered a :: Constraint where Filtered Int = TypeError ('ShowType Int ':<>: 'Text "s not welcome here") Filtered a = ()
foo :: (Show a, Filtered a) => a -> String foo = show
Thank you! I know this seems like an extreme case and I doubt I will ever use your example in any real application.
Indeed, since this is generally a rather odd thing to do.
My question was prompted by the package called reflection (https:// hackage.haskell.org/package/reflection-2.1.6/docs/Data-Reflection.html), that allows to implicitly pass data to functions via a typeclass dictionary. The big issue with it however is that you can pass values of same type multiple times, therefore shooting yourself in the foot somewhere.
This is only a problem if these multiple times are *nested*: module Test (foo) where import Data.Reflection foo :: Int -> Int foo x = give x given bar :: Int -> Int bar x = give x $ let y :: Int y = given in give (y + 5) given in the above, you can call `foo` as many times as you like, with separate values, but `bar` does not behave as one might wish.
I was curious whether it would be possible to allow `give` to be used only once in the same call stack with something like
give :: forall a r. Not (Given a) => a -> (Given a => r) -> r
If this even makes sense.
If you're concerned about nested uses of `Given` the simplest solution is to just use `reify` and `reflect` and avoid `given`: baz :: Int -> Int baz x = reify x $ \p -> let y :: Int y = reflect p in reify (y + 5) reflect -- Viktor.

On Tuesday, 13 July 2021 17:39:04 UTC Viktor Dukhovni wrote:
This is only a problem if these multiple times are *nested*:
Yes, this is exactly that I mean by "within the same call stack".
If you're concerned about nested uses of `Given` the simplest solution is to just use `reify` and `reflect` and avoid `given`:
Frankly, I'd rather stick to multireaders. Reflection seems to me like a worse case of extreme language abuse.

On 13 Jul 2021, at 1:56 pm, Lana Black
wrote: If you're concerned about nested uses of `Given` the simplest solution is to just use `reify` and `reflect` and avoid `given`:
Frankly, I'd rather stick to multireaders. Reflection seems to me like a worse case of extreme language abuse.
When clear and effective alternatives exist, by all means keep it simple. With reflection you get run-time type classes, which can be useful, but I agree should generally not be the first thing you reach for... -- Viktor.

Hi, I've proposed something like this in the past (which was rightfully rejected). You may be interested in the discussion here: https://github.com/ghc-proposals/ghc-proposals/pull/22 Sylvain On 12/07/2021 20:24, Lana Black wrote:
Hello cafe,
Is it possible in Haskell to check a lack of a certain constraint?
For example,
``` foo :: C => a foo = undefined
```
Here `foo` can only be compiled if called with C satisfied. How do I write the opposite, so that `foo` is only possible to use when C is not satisfied?
With best regards.
_______________________________________________ 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)
-
Henning Thielemann
-
Hécate
-
Lana Black
-
Sylvain Henry
-
Viktor Dukhovni