2

In an attempt at learning how to work with dependent data types in haskell I encountered the following problem:

Suppose you have a function such as:

mean :: ((1 GHC.TypeLits.<=? n) ~ 'True, GHC.TypeLits.KnownNat n) => R n -> ℝ

defined in the hmatrix library, then how do you use this on a vector that has an existential type? E.g.:

{-# LANGUAGE DataKinds           #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators       #-}

import Data.Proxy                   (Proxy (..))
import GHC.TypeLits
import Numeric.LinearAlgebra.Static

getUserInput =
  let userInput = 3   -- pretend it's unknown at compile time
      seed      = 42
  in existentialCrisis seed userInput

existentialCrisis seed userInput
  | userInput <= 0 = 0
  | otherwise =
    case someNatVal userInput of
      Nothing -> undefined -- let's ignore this case for now
      Just (SomeNat (proxy :: Proxy n)) ->
        let someVector = randomVector seed Gaussian :: R n
        in mean someVector -- I know that 'n > 0' but the compiler doesn't

This gives the following error:

• Couldn't match type ‘1 <=? n’ with ‘'True’
    arising from a use of ‘mean’

Makes sense indeed, but after some googling and fiddling around, I could not find out how to deal with this. How can I get hold of an n :: Nat, based on user input, such that it satisfies the 1 <= n constraint?. I believe it must be possible since the someNatVal function already succeeds in satisfying the KnownNat constraint based on the condition that the input is not negative.

It seems to me that this is a common thing when working with dependent types, and maybe the answer is obvious but I don't see it.

So my question:

How, in general, can I bring an existential type in scope satisfying the constraints required for some function?

My attempts:

  • To my surprise, even the following modification

        let someVector = randomVector seed Gaussian :: R (n + 1)
    

    gave a type error:

    • Couldn't match type ‘1 <=? (n + 1)’ with ‘'True’
        arising from a use of ‘mean’
    

    Also, adding an extra instance to <=? to prove this equality does not work as <=? is closed.

  • I tried an approach combining GADTs with typeclasses as in this answer to a previous question of mine but could not make it work.

Sam De Meyer
  • 2,031
  • 1
  • 25
  • 32
  • You need a function like `forall n . Proxy n -> ((1 <=? n) ~ 'True => x) -> ((1 <=? n) ~ 'False => x) -> x` which replaces the value-level pattern match (i.e. `.. | userInput <= 0 = 0`). – user2407038 Oct 21 '17 at 23:01
  • To implement such a function, I still need to be able to inspect `n` in such a way that the compiler knows whether `1 <=? n` eqauls `'True` or `'False`. So this just seems to move the problem to another place. – Sam De Meyer Oct 22 '17 at 01:09
  • 2
    @SamDeMeyer The "typelits-witnesses" provides some extra functions for `GHC.TypeLits` that help with these kinds of tasks. See for example https://stackoverflow.com/a/34387963/1364288 and https://stackoverflow.com/a/39812205/1364288 – danidiaz Oct 22 '17 at 09:42
  • @danidiaz Thx, I had already started writing similar code as in `typelits-witnesses` before I read your answer. It's nice to see that someone else already implemented it for me :). – Sam De Meyer Oct 22 '17 at 12:07
  • See also https://stackoverflow.com/questions/41492754/could-not-deduce-knownnat-in-two-existentials-with-respect-to-the-singletons-lib/41496362#41496362 – gallais Oct 24 '17 at 15:29
  • @gallais, thx, `user3237465`'s answer in that post is also quite useful since it has no extra dependencies. – Sam De Meyer Oct 24 '17 at 17:44

1 Answers1

2

Thanks @danidiaz for pointing me in the right direction, the typelist-witnesses documentation provides a nearly direct answer to my question. Seems like I was using the wrong search terms when googling for a solution.

So here is a self contained compileable solution:

{-# LANGUAGE DataKinds           #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators       #-}
{-# LANGUAGE TypeFamilies        #-}

import Data.Proxy                   (Proxy (..))
import Data.Type.Equality           ((:~:)(Refl))
import GHC.TypeLits
import GHC.TypeLits.Compare
import Numeric.LinearAlgebra.Static

existentialCrisis :: Int -> Int -> IO (Double)
existentialCrisis seed userInput =
    case someNatVal (fromIntegral userInput) of
      Nothing -> print "someNatVal failed" >> return 0
      Just (SomeNat (proxy :: Proxy n)) ->
        case isLE (Proxy :: Proxy 1) proxy of
          Nothing -> print "isLE failed" >> return 0
          Just Refl ->
            let someVector = randomVector seed Gaussian :: R n
            in do
              print userInput
              -- I know that 'n > 0' and so does the compiler
              return (mean someVector)

And it works with input only known at runtime:

λ: :l ExistentialCrisis.hs 
λ: existentialCrisis 41 1
(0.2596687587224799 :: R 1)
0.2596687587224799
*Main
λ: existentialCrisis 41 0
"isLE failed"
0.0
*Main
λ: existentialCrisis 41 (-1)
"someNatVal failed"
0.0

It seems like typelist-witnesses does a lot unsafeCoerceing under the hood. But the interface is type-safe so it doesn't really matter that much for practical use cases.

EDIT:

If this question was of interest to you, might also find this post interesting: https://stackoverflow.com/a/41615278/2496293

Sam De Meyer
  • 2,031
  • 1
  • 25
  • 32