5

Here's the code:

{-# LANGUAGE RankNTypes, FlexibleContexts, ScopedTypeVariables #-}

module Foo where

import Data.Vector.Generic.Mutable as M
import Data.Vector.Generic as V
import Control.Monad.ST
import Control.Monad.Primitive
import Control.Monad

data DimFun v s r = 
  DimFun {dim::Int, func :: v (PrimState s) r -> s ()}

runFun :: (Vector v r) => 
  (forall s . (PrimMonad s) => DimFun (Mutable v) s r) -> v r -> v r
runFun t x = runST $ do
  y <- thaw x
  evalFun t y
  unsafeFreeze y

evalFun :: (PrimMonad s, MVector v r) => DimFun v s r -> v (PrimState s) r -> s ()
evalFun (DimFun dim f) y | dim == M.length y = f y

fm :: (MVector v r, PrimMonad s, Num r, Monad m) => m (DimFun v s r)
fm = error ""

f :: forall v r m . (Vector v r, Num r, Monad m) => m (v r -> v r)
f = liftM runFun $ (fm :: forall s . (PrimMonad s) => m (DimFun (Mutable v) s r))

This results in errors:

Couldn't match type ‘DimFun (Mutable v) s0 r’
              with ‘forall (s :: * -> *). PrimMonad s => DimFun (Mutable v) s r’
Expected type: DimFun (Mutable v) s0 r -> v r -> v r
  Actual type: (forall (s :: * -> *).
                PrimMonad s =>
                DimFun (Mutable v) s r)
               -> v r -> v r
Relevant bindings include
  f :: m (v r -> v r) (bound at Testing/Foo.hs:36:1)
In the first argument of ‘liftM’, namely ‘runFun’
In the expression: liftM runFun

However, I'm not sure how to fix or diagnose the problem. It might be as simple as a well-place (and well-written) type signature.

While trying to figure out what was going on, I write a non-monadic version (useless to me), but it compiles:

gm :: (MVector v r, PrimMonad s, Num r) => DimFun v s r
gm = error ""

g :: forall v r m . (Vector v r, Num r) => v r -> v r
g = runFun (gm :: forall s . (PrimMonad s) => DimFun (Mutable v) s r)

This makes me thing the error above is related to the this question where there is no place for the dictionary to go, but that's really just a stab in the dark.

Community
  • 1
  • 1
crockeea
  • 21,467
  • 10
  • 44
  • 93
  • Looks like you might have done a double-post. This should probably be deleted and answers go here: http://stackoverflow.com/questions/24744294/pattern-matching-on-rank-2-type – jberryman Jul 14 '14 at 20:32
  • @jberryman It's not obvious to me that problems in these two questions are relate (though some subset of the code is in fact the same). That's why I posted as two questions. – crockeea Jul 14 '14 at 20:38
  • Use scoped type variables to fix the type of the first argument. Also, try factoring the `forall` out to global scope in the type for `runFun`. – nomen Jul 14 '14 at 20:58
  • 2
    This is possibly an impredicative polymorphism problem. You could maybe get away by wrapping your universally quantified type up in a container. – J. Abrahamson Jul 14 '14 at 20:59
  • @nomen Where specifically are you referring to? I've got an explicit signature on the first argument of `funFun` in `f`. `runFun` itself doesn't compile without a rank-2 argument: we are running the computation in a specific ST monad. – crockeea Jul 14 '14 at 21:09
  • @J.Abrahamson I tried your suggestion and got it to work. Of course I'd rather not have to explicitly wrap the rank-2 type. Although I don't understand much about impredicative types, adding the extension didn't fix the problem on its own. – crockeea Jul 14 '14 at 21:41
  • Just adding the extension merely allows impredicative types, but most likely inference still can't function in presence of them. You'll most likely need more annotations. – J. Abrahamson Jul 14 '14 at 21:51
  • 1
    @J.Abrahamson I'd rather have more annontations than using a wrapper. Where would the annotations go, and what might they look like? – crockeea Jul 14 '14 at 21:53
  • 1
    @Eric Once you see how many annotations you need to make it work, you'll probably change your mind. – Carl Jul 14 '14 at 22:02
  • @Eric To first approximation the inferencer just gives up whenever it encounters an impredicative type. You'll have to annotate every variable. – J. Abrahamson Jul 14 '14 at 23:20

1 Answers1

4

One solution is to move the PrimMonad constraint inside the DimFun datatype.

data DimFun v r = DimFun 
   { dim  :: Int
   , func :: forall s . PrimMonad s => v (PrimState s) r -> s ()
   }

The rest of your code compiles as-is, removing the s parameter from DimFun:

runFun :: Vector v r => DimFun (Mutable v) r -> v r -> v r
runFun = ...

evalFun :: (PrimMonad s, MVector v r) => DimFun v r -> v (PrimState s) r -> s () 
evalFun = ...

fm :: (MVector v r, Num r, Monad m) => m (DimFun v r)
fm = ...

f :: (Vector v r, Num r, Monad m) => m (v r -> v r)
f = liftM runFun fm

Moving the class constraint into the datatype may seem scary to you, but in reality, you already had the class constraint there anyways. PrimState is an associated type family of PrimMonad, so in order to produce or consume a v (PrimState s) r, you need the PrimMonad constraint.

If you want to avoid it nevertheless, you will have to change the type of something. To see why the function you have is illtyped, consider the following (which requires ImpredictiveTypes):

fm :: (MVector v r, PrimMonad s, Num r, Monad m) => m (DimFun v s r)
fm = error ""

g :: (Vector v r, Monad m) 
  => m (forall s . PrimMonad s => DimFun (Mutable v) s r) -> m (v r -> v r)
g = liftM runFun 

It should be cleared why g fm is illtyped: g expects something where the forall s . PrimMonad s => is inside the m, which is not the case for fm. You will have to write a function of type:

fm' :: (MVector v r, Monad m, Num r) => m (forall s . PrimMonad s => DimFun v s r)
fm' = error ""

f :: forall v r m . (Vector v r, Num r, Monad m) => m (v r -> v r)
f = g fm'
user2407038
  • 13,827
  • 2
  • 25
  • 39
  • Both excellent solutions. I just wish it was more obvious that that was what I needed to do! – crockeea Jul 15 '14 at 02:44
  • This also answers [this question](http://stackoverflow.com/questions/24744294/pattern-matching-on-rank-2-type), since I no longer need to pattern match on a rank-2 type. The only other thing I could ask for is a tip about how I should know this is the right thing to do in the future. Why should I prefer rank-2 types inside a data instead of over a data? – crockeea Jul 15 '14 at 03:00
  • 1
    In my opinion, you should always pick universally quantified fields in datatypes over impredictive types. With impredictive types, it is almost always not easy to tell what the correct type should be, and as you can see, the difference between a correct and incorrect type is often very small. More importantly, the typechecker is of no use to you, since it cannot infer impredictive types, and type errors you get will be horrible. – user2407038 Jul 15 '14 at 04:51