Hi,

I noticed

+typeOf :: a -> PolyTypeRep a
+typeOf _ = typeRep

in the patch log.

Unfortunately typeRep returns a view of the type at compile time, not at runtime, so this will always return the type 'a'.

It would be nice to have a typeOf function, however it's a bit complicated ...

We might try and decide and compile time what the type of an expression is, and this generally works fine. However, if someone does ...

  let f :: a -> TypeRep a
      f x = typeOf x

  print (f (3::Int))

It will give 'a' and not 'Int', since the compile-time type of 'x' in 'f x' is a. This could be rather confusing to people ...


Instead of deciding at compile time we could defer the descision until runtime. However this doesn't always give you what you want:

  let x = "hello"
  print (typeOf x)

This would give '[a]', since when the runtime looks at x all it can see is that it is a (:), and thus has type '[a]'.

One could be clever and make the runtime try to track down the type of the type variable by looking at the arguments to (:), but this is foiled by something like:

  let x = "" :: [Char]
  print (typeOf x)

Since x is represented by [] in the heap the only thing that can be inferred about it is that it is type '[a]'. There is also a problem with newtypes ...

  newtype Foo = Foo Int

  let x = Foo 3
  print (typeOf x)

Will give 'Int' since newtypes (by their very nature) don't store anything in the heap.


Then there is the tricky question of whether typeOf should evaluate its argument or not. If yes then you can't do (useful) things like

   let x = undefined :: Int -> Int
   f <- loadPluginFunc "MyPlugin" "myFunction"
   f' <- castTo f (typeOf x)

... and if no then you can break referential transparency ...

  let f :: a -> String
      f _ = ""

      x = f ()

  print (typeOf x)
  print (x `seq` (typeOf x))

This will first print 'String' and then '[a]'. This is because in the first case the runtime will see that x is represented in the heap by a closure 'f ()'. It will note that f is type 'a -> String' and thus conclude that x is type 'String'. However once x has been evaluated it is represented in the heap by '[]', which has type '[a]'.

In my view the compile time option is preferable, however it is still not entirely satisfactory ...


Comments welcome.


Tom


Neil Mitchell wrote:
Can Samuel please have this email set as allowed for this list?

---------- Forwarded message ----------
From: Samuel Bronson <[EMAIL PROTECTED]>
Date: Sep 24, 2006 7:33 PM
Subject: darcs patch: Add not-yet-working typeOf function for YHC.Dynamic
To: [EMAIL PROTECTED]


Sun Sep 24 14:13:22 EDT 2006  Samuel Bronson <[EMAIL PROTECTED]>
 * Add not-yet-working typeOf function for YHC.Dynamic
 For instance, print (typeOf "Hello!") gave me this output:

 (TyGen "v300")

 This reminds me of the impossibility of putting type signatures on
 arbitrary subexpressions without scoped type variables. (Which
 wouldn't help here anyway, since data isn't scoped...)



_______________________________________________
Yhc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/yhc

Reply via email to