#5752: <<loop>> when using variables in TH splice
---------------------------------+------------------------------------------
Reporter: srl | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.6.1
Component: Template Haskell | Version: 7.0.3
Keywords: | Os: Linux
Architecture: x86_64 (amd64) | Failure: Compile-time crash
Difficulty: Unknown | Testcase:
Blockedby: | Blocking:
Related: |
---------------------------------+------------------------------------------
Changes (by igloo):
* difficulty: => Unknown
* milestone: => 7.6.1
Comment:
Thanks for the report.
The code is:
{{{
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Language.Haskell.TH
main = undefined
x = 3
data A = A $( return . (\ts -> foldl AppT (TupleT (length ts)) ts) .
replicate x =<< [t| Double |] )
}}}
HEAD and 7.4 give:
{{{
q.hs:12:80:
GHC internal error: `x' is not in scope during type checking, but it
passed the renamer
tcl_env of environment: [(rfT, AThing *), (rfU, ANothing)]
In the first argument of `replicate', namely `x'
In the second argument of `(.)', namely `replicate x'
In the second argument of `(.)', namely
`(\ ts -> foldl AppT (TupleT (length ts)) ts) . replicate x'
}}}
It looks to me like the code is wrong, but we should get a proper error
that `x` can't be used in a splice in the module that defines it.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5752#comment:1>
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