Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Let-renaming function breaks code

Tags:

haskell

ghc

While iterating my code towards a correct version, I came across the following curiosity:

{-# LANGUAGE RankNTypes #-}

module Foo where

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

-- an in-place vector function with dimension
data DimFun v m r = 
  DimFun Int (v (PrimState m) r -> m ())

eval :: (PrimMonad m, MVector v r) => DimFun v m r -> v (PrimState m) r -> m ()
eval = error ""

iterateFunc :: (PrimMonad m, MVector v r)
            => (forall v' . (MVector v' r) => DimFun v' m r) -> DimFun v m r
iterateFunc = error ""

f :: (PrimMonad m, MVector v r)
      => DimFun v m r
f = error ""

iteratedF :: (MVector v r, PrimMonad m) 
           => v (PrimState m) r -> m ()
iteratedF y = 
    let f' = f
    in eval (iterateFunc f') y

This code does not compile:

Testing/Foo.hs:87:14:
    Could not deduce (MVector v0 r) arising from a use of ‘f’
    from the context (MVector v r, PrimMonad m)
      bound by the type signature for
                 iteratedF :: (MVector v r, PrimMonad m) =>
                              v (PrimState m) r -> m ()
      at Testing/Foo.hs:(84,14)-(85,39)
    The type variable ‘v0’ is ambiguous
    Relevant bindings include
      f' :: DimFun v0 m r (bound at Testing/Foo.hs:87:9)
      y :: v (PrimState m) r (bound at Testing/Foo.hs:86:11)
      iteratedF :: v (PrimState m) r -> m ()
        (bound at Testing/Foo.hs:86:1)
    In the expression: f
    In an equation for ‘f'’: f' = f
    In the expression: let f' = f in eval (iterateFunc f') y

Testing/Foo.hs:88:26:
    Couldn't match type ‘v0’ with ‘v'’
      because type variable ‘v'’ would escape its scope
    This (rigid, skolem) type variable is bound by
      a type expected by the context: MVector v' r => DimFun v' m r
      at Testing/Foo.hs:88:14-27
    Expected type: DimFun v' m r
      Actual type: DimFun v0 m r
    Relevant bindings include
      f' :: DimFun v0 m r (bound at Testing/Foo.hs:87:9)
    In the first argument of ‘iterateFunc’, namely ‘f'’
    In the first argument of ‘eval’, namely ‘(iterateFunc f')’
Failed, modules loaded: none.

However, if I change the definition of iteratedF to

iteratedF y = eval (iterateFunc f) y

the code compiles wtih GHC 7.8.2. This question is not about the strange-looking signatures or data types, it is simply this: why does renaming f to f' break the code? This seems like it has to be a bug to me.

like image 307
crockeea Avatar asked Jul 13 '14 16:07

crockeea


People also ask

Is renaming variable refactoring?

Refactoring variable names involves renaming the variable and then updating usages of the variable that occur elsewhere, such as in the pipeline, other flow services, or document types.

How do I Rename a function in Visual Studio?

Select Edit > Refactor > Rename. Right-click the code and select Rename.

How do I Rename a function?

Right-click the function you wish to rename and select Rename. Enter the function's new name.

How do I Rename or code a file?

Right-click the code, select the Quick Actions and Refactorings menu, and select Rename file to TypeName.


Video Answer


2 Answers

Disabling the monomorphism restriction, I can compile your code. So, just add

{-# LANGUAGE NoMonomorphismRestriction #-}

at the beginning of your file.

The reason for the type error is that the definition

let f' = f

does not use a function pattern (e.g. f' x y = ...), so the monomorphism restriction kicks in and forces f' to be monomorphic, while iterateFunc requires a polymorphic function.

Alternatively, add a type annotation

let f' :: (PrimMonad m, MVector v r) => DimFun v m r
    f' = f
like image 113
chi Avatar answered Sep 21 '22 01:09

chi


The problem is of course not the renaming, but the binding to a new variable. Since iterateFunc is Rank-2, it needs a polymorphic argument function. Of course, f is polymorphic in v, so it can be used. But when you write f' = f, it's not clear what type f' should be: the same polymorphic type as f, or some monomorphic type, possibly depending some relation to another type variable in iteratedF which the compiler hasn't deduced yet.

The compiler defaults to the monomorphic option; as chi says this is the monomorphism restriction's fault here so if you turn it off your code actually compiles.

Still, the same problem can turn up even without the monomorphism restriction in RankNTypes code, it can't be avoided completely. The only reliable fix is a local signature, usually necessitating ScopedTypeVariables.

like image 30
leftaroundabout Avatar answered Sep 19 '22 01:09

leftaroundabout