#5037: TH mkName bug
---------------------------------+------------------------------------------
    Reporter:  igloo             |        Owner:              
        Type:  bug               |       Status:  new         
    Priority:  normal            |    Milestone:              
   Component:  Template Haskell  |      Version:  7.0.2       
    Keywords:                    |     Testcase:              
   Blockedby:                    |   Difficulty:              
          Os:  Unknown/Multiple  |     Blocking:              
Architecture:  Unknown/Multiple  |      Failure:  None/Unknown
---------------------------------+------------------------------------------
 This is accepted:
 {{{
 {-# LANGUAGE TemplateHaskell #-}

 import Language.Haskell.TH

 f :: Maybe Int -> Int
 f Nothing = 3
 f (Just x) = $(varE (mkName "x"))
 }}}
 but this fails:
 {{{
 {-# LANGUAGE TemplateHaskell #-}

 import Language.Haskell.TH

 $( do ds <- [d|
                 f :: Maybe Int -> Int
                 f Nothing = 3
                 f (Just x) = $(varE (mkName "x"))
               |]
       runIO $ putStrLn $ pprint ds
       return ds )
 }}}
 with:
 {{{
 f :: Data.Maybe.Maybe GHC.Types.Int -> GHC.Types.Int
 f (Data.Maybe.Nothing) = 3
 f (Data.Maybe.Just x_0) = x

 q.hs:5:4: Not in scope: `x'
 }}}
 I expect it to be accepted.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5037>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to