Skip to content
GitLab
Projects Groups Snippets
  • /
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
  • GHC GHC
  • Project information
    • Project information
    • Activity
    • Labels
    • Members
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 5,357
    • Issues 5,357
    • List
    • Boards
    • Service Desk
    • Milestones
    • Iterations
  • Merge requests 567
    • Merge requests 567
  • CI/CD
    • CI/CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Deployments
    • Deployments
    • Releases
  • Analytics
    • Analytics
    • Value stream
    • CI/CD
    • Code review
    • Insights
    • Issue
    • Repository
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell CompilerGlasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #3845
Closed
Open
Issue created Jan 28, 2010 by JakeWheat@trac-JakeWheat

compiling template haskell internal error: ... not in scope during type checking, but it passed the renamer

example code:

{-# LANGUAGE TemplateHaskell #-}

module THBug1 where

import Language.Haskell.TH

data HCons a b = HCons a b
data HNil = HNil

mhlt :: [Type] -> Q Type
mhlt xss = [t| $(foldThing xss)|]
  where
    foldThing (x:xs) = [t| HCons $x $(foldThing xs)|]
    foldThing [] = [t| HNil |]

compiling gives:

~$ ghc -c THBug1.hs 

THBug1.hs:13:38:
    GHC internal error: `foldThing' is not in scope during type checking, but it passed the renamer
    tcg_type_env of environment: [(rge, Type constructor `HNil'),
                                  (rgg, Data constructor `HNil'), (rgi, Type constructor `HCons'),
                                  (rgk, Data constructor `HCons'), (rgJ, Identifier `THBug1.HNil'),
                                  (rgM, Identifier `THBug1.HCons')]
    In the expression: foldThing xs
    In the Template Haskell quotation [t| HCons $x $(foldThing xs) |]
    In the expression: [t| HCons $x $(foldThing xs) |]

ghc used is the latest ghc 6.12.1 from debian experimental (package version 6.1.12-3, which is latest as of 28 Jan)

further details:

~$ uname -a
Linux debiannew 2.6.32-trunk-686-bigmem #1 SMP Sun Jan 10 07:12:17 UTC 2010 i686 GNU/Linux
~$ gcc -v
Using built-in specs.
Target: i486-linux-gnu
Configured with: ../src/configure -v --with-pkgversion='Debian 4.4.3-1' 
--with-bugurl=file:///usr/share/doc/gcc-4.4/README.Bugs --enable-languages=c,c++,fortran,objc,obj-c++ 
--prefix=/usr --enable-shared --enable-multiarch --enable-linker-build-id 
--with-system-zlib --libexecdir=/usr/lib --without-included-gettext 
--enable-threads=posix --with-gxx-include-dir=/usr/include/c++/4.4 
--program-suffix=-4.4 --enable-nls --enable-clocale=gnu --enable-libstdcxx-debug 
--enable-objc-gc --enable-targets=all --with-arch-32=i486 --with-tune=generic 
--enable-checking=release --build=i486-linux-gnu --host=i486-linux-gnu --target=i486-linux-gnu
Thread model: posix
gcc version 4.4.3 (Debian 4.4.3-1) 
~$ ghc -c -v -dcore-lint THBug1.hs 
Glasgow Haskell Compiler, Version 6.12.1, for Haskell 98, stage 2 booted by GHC version 6.12.1
Using binary package database: /usr/lib/ghc-6.12.1/package.conf.d/package.cache
Using binary package database: /home/jake/.ghc/i386-linux-6.12.1/package.conf.d/package.cache
hiding package QuickCheck-1.2.0.0 to avoid conflict with later version QuickCheck-2.1.0.3
hiding package base-3.0.3.2 to avoid conflict with later version base-4.2.0.0
hiding package parsec-2.1.0.1 to avoid conflict with later version parsec-3.0.1
wired-in package ghc-prim mapped to ghc-prim-0.2.0.0-3fbcc20c802efcd7c82089ec77d92990
wired-in package integer-gmp mapped to integer-gmp-0.2.0.0-fa82a0df93dc30b4a7c5654dd7c68cf4
wired-in package base mapped to base-4.2.0.0-73995e854f236dc2acd577d7c791221d
wired-in package rts mapped to builtin_rts
wired-in package haskell98 mapped to haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6
wired-in package template-haskell mapped to template-haskell-2.4.0.0-92d419f5a3bd03d1c021561d3b29c041
wired-in package dph-seq mapped to dph-seq-0.4.0-1f5167ea371010387123b68e975177b2
wired-in package dph-par mapped to dph-par-0.4.0-4e569f28e047d67d87266113526bc6ec
Hsc static flags: -static
Created temporary directory: /tmp/ghc19231_0
*** Checking old interface for main:THBug1:
*** Parser:
*** Renamer/typechecker:

THBug1.hs:13:38:
    GHC internal error: `foldThing' is not in scope during type checking, but it passed the renamer
    tcg_type_env of environment: [(rge, Type constructor `HNil'),
                                  (rgg, Data constructor `HNil'), (rgi, Type constructor `HCons'),
                                  (rgk, Data constructor `HCons'), (rgJ, Identifier `THBug1.HNil'),
                                  (rgM, Identifier `THBug1.HCons')]
    In the expression: foldThing xs
    In the Template Haskell quotation [t| HCons $x $(foldThing xs) |]
    In the expression: [t| HCons $x $(foldThing xs) |]
*** Deleting temp files:
Deleting: /tmp/ghc19231_0/ghc19231_0.s
Warning: deleting non-existent /tmp/ghc19231_0/ghc19231_0.s
*** Deleting temp dirs:
Deleting: /tmp/ghc19231_0
Trac metadata
Trac field Value
Version 6.12.1
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Assignee
Assign to
Time tracking