Re: [GHC] #2222: Template Haskell: reify returns incorrect types when ommiting type signatures

2008-04-24 Thread GHC
#: Template Haskell: reify returns incorrect types when ommiting type
signatures
--+-
 Reporter:  fons  |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone:  _|_
Component:  Template Haskell  |Version:  6.8.2  
 Severity:  major | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Multiple  |  
--+-
Changes (by igloo):

  * milestone:  => _|_

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2222: Template Haskell: reify returns incorrect types when ommiting type signatures

2008-04-16 Thread GHC
#: Template Haskell: reify returns incorrect types when ommiting type
signatures
--+-
 Reporter:  fons  |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone: 
Component:  Template Haskell  |Version:  6.8.2  
 Severity:  major | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Multiple  |  
--+-
Changes (by simonpj):

  * difficulty:  => Unknown

Comment:

 OK, so there are several things going on here.

 1.  For `a`, you are hitting the Monomorphism Restriction.  Since `a` is
 monomorphic, it gets type `t0`, where `t0` is a unification variable.
 Right at the very end of the module we might see `(f a)` where `f :: Int
 -> Int`, and then (but only then) we'd discover that `t0` is really `Int`.
 The difficulty is that reification (for local variables) can ask for the
 type of a variable before all the evidence is in. A much more direct
 examples would be
 {{{
   \x. ... $( ...reify 'x'... ) ...
 }}}
 The type of `x` may not be determined by the time the splice runs.  I
 can't see a way round this, except by making reification illegal for local
 variables, or perhaps for non-rigid ones, or something.

 2.  Although you wrote your definitions in order `b,c,d`, and they are not
 recursive, GHC is treating them as a mutually recursive group, and, as
 luck would have it, checks `d` first.  So the reification inside `d` see's
 `c`'s type before `c`'s right hand side has been examined, and we are back
 in situation (1).

 Why are they treated as mutually recursive?  Here's the comment from
 `RnSource`:
 {{{
 Note [Splices]
 ~~
 Consider
 f = ...
 h = ...$(thing "f")...

 The splice can expand into literally anything, so when we do dependency
 analysis we must assume that it might mention 'f'.  So we simply treat
 all locally-defined names as mentioned by any splice.  This is terribly
 brutal, but I don't see what else to do.  For example, it'll mean
 that every locally-defined thing will appear to be used, so no unused-
 binding
 warnings.  But if we miss the dependency, then we might typecheck
 'h' before 'f', and that will crash the type checker because 'f' isn't
 in scope.

 Currently, I'm not treating a splice as also mentioning every import,
 which is a bit inconsistent -- but there are a lot of them.  We might
 thereby get some bogus unused-import warnings, but we won't crash the
 type checker.  Not very satisfactory really.
 }}}
 Remember that TH allows dynamic binding!

 Again, I don't see a good way around this either.

 You might say that you expect TH splices to be run top-to-bottom, but what
 if one at the bottom is used further up:
 {{{
   f = ...g...
   ...
   h = $(bar 4)
   g = $(foo 3)
 }}}
 Now we have to run the splice for `g` before we can get a type for `g`;
 and we need a type for `g` before we can typecheck `f`.


 Anyway I hope that explains some of what is going on.  The real issues
 here are ones of design, rather than bugs of implementation.  Good design
 ideas would be very welcome -- the TH design is clearly warty in places.

 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2222: Template Haskell: reify returns incorrect types when ommiting type signatures

2008-04-14 Thread GHC
#: Template Haskell: reify returns incorrect types when ommiting type
signatures
+---
Reporter:  fons |   Owner:  
Type:  bug  |  Status:  new 
Priority:  normal   |   Component:  Template Haskell
 Version:  6.8.2|Severity:  major   
Keywords:   |Testcase:  
Architecture:  Unknown  |  Os:  Multiple
+---
 Replicable with GHC versions 6.8.2 and 6.9 (20080219 snapshot).

 Workaround: supply type signatures.

 See the following examples:


 `ReifyPlusTypeInferenceBugs.hs`
 {{{
 {-# LANGUAGE TemplateHaskell #-}
 module ReifyPlusTypeInferenceBugs where

 import Language.Haskell.TH

 -- First problem:
 --  * reify doesn't return the expected type of names binded to
 --polymorphic expressions

 -- a :: Num a => a
 -- uncommenting the line above fixes the problem
 a = 1

 -- The following splice should print
 -- "inside b: forall a_0 . GHC.Num.Num a_0 => a_0"
 -- but instead, it merely prints a type variable "inside b: t_0"
 b = $(do VarI _ t _ _ <- reify 'a
  runIO $ putStrLn ("inside b: " ++ pprint t)
  [| undefined |])


 -- Second problem:
 --  * reify doesn't return the expected type of names binded to
 --TH-spliced expressions if no explicit type signature
 --declaration is provided.


 -- c :: Bool
 -- uncommenting the line above fixes the problem
 c = $([| True |])


 -- this splice should print "inside d: GHC.Base.Bool"
 -- but, again, it prints just a type variable: "inside d: t_0"
 d = $(do VarI _ t _ _ <- reify 'c
  runIO $ putStrLn ("inside d: " ++ pprint t)
  [| undefined |] )

 -- Strangely enough, reify works differently if called inside a
 declaration
 -- splice. This time, the type returned is closer to be right
 -- but unnecesary type variables are included:
 -- "type of c: forall a_0 a_1 . GHC.Base.Bool"
 $(do VarI _ t _ _ <- reify 'c
  runIO $ putStrLn ("type of c: " ++ pprint t)
  return [] )


 -- Even more strange is the fact that the order of declaration of
 -- splices seems to matter. Declaring the exact example again 

 -- e :: Bool
 -- uncommenting the line above solves the problem
 e = $([| True |])

 -- this splice works as expected!!! ???
 -- "inside f: GHC.Base.Bool"
 f = $(do VarI _ t _ _ <- reify 'e
  runIO $ putStrLn ("inside f: " ++ pprint t)
  [| undefined |] )

 -- Here, we still get unnecesary variables, but, for some reason,
 -- _just_ one in this case:
 -- "type of e: forall a_0 . GHC.Base.Bool"
 $(do VarI _ t _ _ <- reify 'e
  runIO $ putStrLn ("type of e: " ++ pprint t)
  return [] )
 }}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs