17

Here are some pragmas and some imports:

{-# LANGUAGE ScopedTypeVariables #-}

import Control.Monad.ST
import Data.Array.ST
import Data.Array

Now here's my problem. The following code typechecks:

foo :: forall a. a -> [a]
foo x = elems $ runSTArray $ do
    newListArray (1,10) (replicate 10 x) :: ST s (STArray s Int a)

However, when I replace the $ with composition:

foo :: forall a. a -> [a]
foo x = elems . runSTArray $ do
    newListArray (1,10) (replicate 10 x) :: ST s (STArray s Int a)

I get this error:

Couldn't match expected type `forall s. ST s (STArray s i0 e0)'
            with actual type `ST s0 (STArray s0 Int a)'
In the expression:
    newListArray (1, 10) (replicate 10 x) :: ST s (STArray s Int a)
In the second argument of `($)', namely
  `do { newListArray (1, 10) (replicate 10 x) ::
          ST s (STArray s Int a) }'
In the expression:
      elems . runSTArray
  $ do { newListArray (1, 10) (replicate 10 x) ::
           ST s (STArray s Int a) }

What's werid is, if I give the function composition its own name, then it typechecks again:

elemSTArray = elems . runSTArray

foo :: forall a. a -> [a]
foo x = elemSTArray $ do
    newListArray (1,10) (replicate 10 x) :: ST s (STArray s Int a)

I'm not sure what's going on here. I would expect the second piece of code to typecheck nicely. And I don't understand why it typechecks again if I give the composed function its own name.

This is a simplified version of some code that I had that broke when upgrading from GHC 6.2 to 7 and I'm trying to understand why this happens now. Thanks for helping!

Drekembe
  • 2,620
  • 2
  • 16
  • 13
  • I'm not really a Haskell programmer, but what is the precedence of composition relative to `$`? What happens if you parenthesise the sub-expression `elems . runSTArray`? – Gian Dec 01 '11 at 14:53
  • 1
    I can't reproduce this with GHC 6.12.1. – opqdonut Dec 01 '11 at 14:57
  • Gian: `$` has lower precedence than `.`, so if I parenthesise the sub-expression it behaves the same. opqdonut: This didn't happen to me either on GHC 6.2 but it does on GHC 7.0.3 – Drekembe Dec 01 '11 at 15:01
  • @EEVIAC: oh sorry, didn't catch the bit about upgrading. Definitely reproducible under 7. Have you filed a GHC bug already? – opqdonut Dec 01 '11 at 15:09
  • No, I haven't, since I wasn't sure that it's a bug, I just assumed it was an error in my understanding of the type system currently, since I haven't been following the development of GHC lately. So it's a bug? – Drekembe Dec 01 '11 at 15:31
  • Probably. The change in treatment of `runST` and friends with respect to `($)` and `(.)` may have been intentional, but I doubt it. If you file a bug, you'll get an authoritative answer. – Daniel Fischer Dec 01 '11 at 15:42
  • @Gian: `f . g . h $` being equivalent to `f $ g $ h $ x` is a common Haskell pattern; Them *not* being equivalent here it the weird thing. – hugomg Dec 01 '11 at 15:59
  • The reason why `($)` works but `(.)` doesn't is because GHC 7 has a special typing rule for infix uses of `($)` specifically to help with the common `runST $ do ...` pattern. See: [runST and function composition](http://stackoverflow.com/questions/9468963/runst-and-function-composition). – hammar Apr 13 '12 at 01:01

2 Answers2

15

As you already hint at in the title of your post, the problem has to do with runSTArray having a polymorphic type of rank 2.

runSTArray :: Ix i => (forall s. ST s (STArray s i e)) -> Array i e

With

elems :: Ix i => Array i e -> [e]

and

($) :: (a -> b) -> a -> b

writing runSTArray $ ... means that the type variable a in the type schema of ($) needs to be instantiated with a polymorphic type rather than a monomorphic type. This requires so-called impredicative polymorphism. How GHC implements impredicative polymorphism is explained in the ICFP 2008 paper by Dimitrios Vytiniotis, Stephanie Weirich, and Simon Peyton Jones: FPH : First-class Polymorphism for Haskell. The bottom line is that while FPH often gives you the behaviour that you expect, typeability is sometimes not preserved under simple transformations like the ones you describe in your question: see Section 6.2 of the aforementioned paper.

Stefan Holdermans
  • 7,990
  • 1
  • 26
  • 31
9

Stefan beat me to the answer -- the tricky bit is that it's not the $ vs . between elems and runSTArray that's the issue -- it's the $ following runSTArray. Since something $ rankNthing is so common, there's a clever bit (I forget the details) that tries to let you do that as a corner case. But somehow using the composition earlier on prevents this. The location of the issue is demonstrated by the fact that the following will typecheck:

foo x = (elems . runSTArray) (
    (newListArray (1,10) (replicate 10 x) :: ST s (STArray s Int String)))

I'm not sure this is a bug per se, but its certainly an unexpected behavior worth creating a ticket about, since there might still be a better algorithm to catch cases like the one you provided.

sclv
  • 38,665
  • 7
  • 99
  • 204