Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,246
    • Issues 4,246
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 397
    • Merge Requests 397
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
  • Security & Compliance
    • Security & Compliance
    • Dependency List
    • License Compliance
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Collapse sidebar
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #13837

Closed
Open
Opened Jun 16, 2017 by Ryan Scott@RyanGlScottMaintainer

Calling qReifyInstances on out-of-scope Name leads to GHC internal error

{-# LANGUAGE TemplateHaskell #-}
module Bug where

import Language.Haskell.TH.Lib
import Language.Haskell.TH.Syntax

test_local_tyfam_expansion :: String
test_local_tyfam_expansion =
  $(do fam_name <- newName "Fam"
       stringE . show =<< qReifyInstances fam_name [])
$ /opt/ghc/8.2.1/bin/ghci Bug2.hs
GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/  :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug              ( Bug2.hs, interpreted )

Bug2.hs:9:5: error:
    • The exact Name ‘Fam_a4pX’ is not in scope
        Probable cause: you used a unique Template Haskell name (NameU), 
        perhaps via newName, but did not bind it
        If that's it, then -ddump-splices might be useful
    • In the argument of reifyInstances: Fam_0
      In the untyped splice:
        $(do fam_name <- newName "Fam"
             stringE . show =<< qReifyInstances fam_name [])
  |
9 |   $(do fam_name <- newName "Fam"
  |     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...

Bug2.hs:9:5: error:
    • GHC internal error: ‘Fam_a4pX’ is not in scope during type checking, but it passed the renamer
      tcl_env of environment: []
    • In the type ‘Fam_a4pX’
      In the argument of reifyInstances: Fam_0
      In the untyped splice:
        $(do fam_name <- newName "Fam"
             stringE . show =<< qReifyInstances fam_name [])
  |
9 |   $(do fam_name <- newName "Fam"
  |     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...

This appears to have started happening in GHC 7.10, since with 7.8, you only get this:

GHCi, version 7.8.4: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Bug              ( Bug2.hs, interpreted )
Loading package array-0.5.0.0 ... linking ... done.
Loading package deepseq-1.3.0.2 ... linking ... done.
Loading package containers-0.5.5.1 ... linking ... done.
Loading package pretty-1.1.1.1 ... linking ... done.
Loading package template-haskell ... linking ... done.

Bug2.hs:9:5:
    The exact Name ‘Fam_a2gK’ is not in scope
      Probable cause: you used a unique Template Haskell name (NameU), 
      perhaps via newName, but did not bind it
      If that's it, then -ddump-splices might be useful
    In the argument of reifyInstances: Fam_0
    In the splice:
      $(do { fam_name <- newName "Fam";
             stringE . show =<< qReifyInstances fam_name [] })

This problem appears to be somewhat specific to qReifyInstances, since switching it out with qReify does not trigger the internal error:

{-# LANGUAGE TemplateHaskell #-}
module Bug where

import Language.Haskell.TH.Lib
import Language.Haskell.TH.Syntax

test_local_tyfam_expansion :: String
test_local_tyfam_expansion =
  $(do fam_name <- newName "Fam"
       stringE . show =<< qReify fam_name)
GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/  :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug              ( Bug2.hs, interpreted )

Bug2.hs:9:5: error:
    • The exact Name ‘Fam_a4od’ is not in scope
        Probable cause: you used a unique Template Haskell name (NameU), 
        perhaps via newName, but did not bind it
        If that's it, then -ddump-splices might be useful
    • In the untyped splice:
        $(do fam_name <- newName "Fam"
             stringE . show =<< qReify fam_name)
  |
9 |   $(do fam_name <- newName "Fam"
  |     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...

Bug2.hs:9:5: error:
    • The exact Name ‘Fam_a4od’ is not in scope
        Probable cause: you used a unique Template Haskell name (NameU), 
        perhaps via newName, but did not bind it
        If that's it, then -ddump-splices might be useful
    • In the untyped splice:
        $(do fam_name <- newName "Fam"
             stringE . show =<< qReify fam_name)
  |
9 |   $(do fam_name <- newName "Fam"
  |     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...

Bug2.hs:9:5: error:
    • ‘Fam_a4od’ is not in the type environment at a reify
    • In the untyped splice:
        $(do fam_name <- newName "Fam"
             stringE . show =<< qReify fam_name)
  |
9 |   $(do fam_name <- newName "Fam"
  |     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
Trac metadata
Trac field Value
Version 8.0.1
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Template Haskell
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Assignee
Assign to
8.4.1
Milestone
8.4.1 (Past due)
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#13837