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,386
    • Issues 4,386
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 373
    • Merge Requests 373
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #5689

Closed
Open
Opened Dec 08, 2011 by nicolast@trac-nicolast

The 'impossible' happened: type-inference succeeds somehow in code which isn't type-safe

While trying to figure out how Haskell handles OCaml's value restriction, I created some code which I thought shouldn't type-check.

It did, though, and makes GHCi panic on execution, or makes GHC fail during compilation.

Minor changes to the code makes it no longer type-check, as expected.

Here's the code, including some comments which show when compilation does fail as expected:

{-# LANGUAGE ScopedTypeVariables #-}

import Data.IORef

main :: IO ()
main = do
    (r :: IORef (t -> t)) <- newIORef id
    -- r <- newIORef i -- => Type-check error

    writeIORef r (\v -> if v then False else True)

    c <- readIORef r

    print $ c True

    print $ c 1234

    -- print $ c Nothing -- => Type-check error
    -- print $ c (1 :: Int) -- => Type-check error

When replacing the "print $ c 1234" line with one of the last 2 lines, type-checking fails. When removing the explicit type-annotation on 'r', type-checking fails when "print $ c 1234" is left in place.

Here's the GHCi and GHC output:

Prelude> :load demo1.hs
[1 of 1] Compiling Main             ( demo1.hs, interpreted )
Ok, modules loaded: Main.
*Main> main
ghc: panic! (the 'impossible' happened)
  (GHC version 7.0.4 for x86_64-unknown-linux):
	nameModule $dNum{v ann}

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
$ ghc --make demo1.hs
[1 of 1] Compiling Main             ( demo1.hs, demo1.o )
ghc: panic! (the 'impossible' happened)
  (GHC version 7.0.4 for x86_64-unknown-linux):
	initC: srt_lbl

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
Trac metadata
Trac field Value
Version 7.0.4
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler (Type checker)
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Assignee
Assign to
None
Milestone
None
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#5689