3

I have a bunch of complicated type level functions that evaluate to things like:

(If (EqNat n 2)
  1
  (If (EqNat n 1)
    2
    (If (EqNat n 0) 3 0)))

Now obviously in this case this expression is a KnownNat. More generally we may say:

forall (c :: * -> Constraint) (p :: Bool) a b .
(c a, c b) => c (If p a b)

Is there a way to teach GHC to infer this?

Edit: @chi noted that in some cases this is solvable with GADTs but my particular case is this one:

module M1 (C(..)) where

type familiy NestedIfs (n :: Nat) :: Nat
type NestedIfs n = <<complex nested ifs like the above that evals to literals>>

class C a (n :: Nat) where
  f :: KnownNat n => a -> NestedIfs n -> Bool

and then

module M2 () where
import M1

instance C Int n where
    f = ...require that KnownNat (NestedIfs n)...

NestedIfs is not accessible to M2 but maybe GHC should be able to infer that forall n . KnownNat n => KnownNat (NestedIfs n) from the general inference I mention above.

fakedrake
  • 6,528
  • 8
  • 41
  • 64
  • 1
    We would need `forall (p::Bool). Either (p:~:True) (p:~:False)` for that. I don't think one can achieve that without a singleton argument for `p::Bool`. – chi Feb 20 '17 at 16:17
  • Could you elaborate on that? 1) What other types inhabit the `Bool` kind, 2) If `Either (p:~:True) (p:~:False)` were a terminal of the Bool kind, would that actually help us at the technical level of helping GHC to automatically infer what I asked about? – fakedrake Feb 20 '17 at 16:34
  • By the way maybe take into account [this question I asked the other day](http://stackoverflow.com/questions/42240533/infer-constraints-for-both-if-and-else-of-type-equality) – fakedrake Feb 20 '17 at 16:36
  • 1) I'm not an expert of this, but IIRC type families can cause e.g. `F Char :: Bool' to be stuck and fail to reduce to `True` or `False`. (Yes, that's quite annoying) 2) Assuming that anyway, one can pattern match `case proof of Left Refl -> ... ; Right Refl -> ...` and cause `p` to be instantiated with true/false, so that `If` simplifies and the constraint is found to be satisfied. – chi Feb 20 '17 at 16:47
  • 1) If there is a bottom type inhabiting all kinds I don't think it manifests in the [same way](https://ghc.haskell.org/trac/ghc/ticket/7788#comment:16) as in values. 2) What you say only partially solves the problem. I will edit the question to demonstrate an example. – fakedrake Feb 20 '17 at 17:42
  • Cf. [this question](http://stackoverflow.com/questions/41492754/could-not-deduce-knownnat-in-two-existentials-with-respect-to-the-singletons-lib/41496362) – gallais Feb 20 '17 at 19:05
  • @fakedrake Regarding chi's first question: `Any :: Bool` (read as `Any` has kind `Bool`). Yep, it's ugly. – Alec Feb 21 '17 at 06:15
  • @alec thanks, you have even told me about it before I think. To give some [background](http://hackage.haskell.org/package/ghc-prim-0.5.0.0/docs/GHC-Prim.html#t:Any) for the future generations (and me when I desperately try to solve the same problem in a month or so): "`Any` [is] used to instantiate un-constrained type variables after type checking." eg `forall a. m a` – fakedrake Feb 21 '17 at 10:41
  • @fakedrake While that is true, anyone can make their own version of Any using a closed type family with no cases. The whole type level totality situation is a bit confusing. – Alec Feb 21 '17 at 15:45

1 Answers1

4

This question is not hard, but is ill-posed. What value do you expect to get back of type c (If p a b) :: Constraint? What you likely want to ask, is how to fill in the body of this

bisect :: forall b c x y. SingI b => Proxy b -> (c x, c y) :- c (If b x y)

Here, as noted in the comments, I am forcing c to be a singleton so that I can get Either (c :~: True) (c :~: False) (you may read my SingI constraint as enforcing that c :: Bool must be either True or False, which is unfortunately not a trivial request when at the type level since Any has kind Bool too). The :- comes from the constraints package. It is a way of saying that the constraint (a,b) implies the constraint If c a b. That is exactly how to express your request - you want a proof that two says given c x and c y hold, c (If b x y) will also hold.

Filling in the body of that function is actually very little code:

{-# LANGUAGE DataKinds, TypeFamilies, ConstraintKinds, TypeOperators, RankNTypes,
    ScopedTypeVariables, PolyKinds #-}

import Data.Constraint
import Data.Singletons.Prelude hiding ((:-))

bisect :: forall b c x y. (SingI b) => Proxy b -> (c x, c y) :- c (If b x y)
bisect _ = unmapDict $ case sing :: Sing b of
                         STrue -> mapDict weaken1
                         SFalse -> mapDict weaken2
Alec
  • 31,829
  • 7
  • 67
  • 114
  • Thnx! Is there a way to get rid of `Proxy b`? – fakedrake Feb 20 '17 at 18:45
  • 1
    @fakedrake Yes, you can just drop that argument out (and enable `AllowAmbiguousTypes`). To use `bisect`, may then need to have `TypeApplication` enabled. – Alec Feb 20 '17 at 19:09