
Ola! Currently we have: type family If cond tru fls where If True tru fls = tru If False tru fls = fls Unfortunately, this appears to turned into a monomorphicly kinded type family by GHC, which means it’s impossible to do foo :: If cond () (“Condition does not hold” ~ “”) => Foo -> Bar or similar fancy constraints. I hereby propose altering If to: type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where If True tru fls = tru If False tru fls = fls Allowing it to work with kinds other than *. Discussion period: 2 weeks? Seems like a minor change. Cheers, Merijn

Hi Merijn,
I believe that `If` is already the way you want:
λ> :k If
If :: Bool -> k -> k -> k
The problem in your code is that GHC is a little... er... unprincipled about the kind of `()`. It basically assumes that `()` is of kind `*` unless it is very, absolutely, abundantly obvious that it should have kind `Constraint`. Your code is not abundantly obvious enough in this regard. If you say `If cond (() :: Constraint) (...) => ...`, I believe your code will work.
Does this in fact work for you?
Richard
On Sep 1, 2014, at 11:41 PM, Merijn Verstraaten
Ola!
Currently we have:
type family If cond tru fls where If True tru fls = tru If False tru fls = fls
Unfortunately, this appears to turned into a monomorphicly kinded type family by GHC, which means it’s impossible to do
foo :: If cond () (“Condition does not hold” ~ “”) => Foo -> Bar
or similar fancy constraints.
I hereby propose altering If to:
type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where If True tru fls = tru If False tru fls = fls
Allowing it to work with kinds other than *.
Discussion period: 2 weeks? Seems like a minor change.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi Richard,
It would appear that you’re right! I had expected GHC to infer the kind Constraint for () from the second argument, rather than reporting an error, but adding an explicit annotation works. I would still say that warrants a clearer error message from GHC, but at least it works :)
Cheers,
Merijn
On 02 Sep 2014, at 01:20 , Richard Eisenberg
Hi Merijn,
I believe that `If` is already the way you want:
λ> :k If If :: Bool -> k -> k -> k
The problem in your code is that GHC is a little... er... unprincipled about the kind of `()`. It basically assumes that `()` is of kind `*` unless it is very, absolutely, abundantly obvious that it should have kind `Constraint`. Your code is not abundantly obvious enough in this regard. If you say `If cond (() :: Constraint) (...) => ...`, I believe your code will work.
Does this in fact work for you?
Richard
On Sep 1, 2014, at 11:41 PM, Merijn Verstraaten
wrote: Ola!
Currently we have:
type family If cond tru fls where If True tru fls = tru If False tru fls = fls
Unfortunately, this appears to turned into a monomorphicly kinded type family by GHC, which means it’s impossible to do
foo :: If cond () (“Condition does not hold” ~ “”) => Foo -> Bar
or similar fancy constraints.
I hereby propose altering If to:
type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where If True tru fls = tru If False tru fls = fls
Allowing it to work with kinds other than *.
Discussion period: 2 weeks? Seems like a minor change.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (2)
-
Merijn Verstraaten
-
Richard Eisenberg