[GHC] #14967: Optimizer Casting Caf with nominal type

GHC ghc-devs at haskell.org
Sat Mar 24 04:46:43 UTC 2018


#14967: Optimizer Casting Caf with nominal type
-------------------------------------+-------------------------------------
           Reporter:  etn            |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.4.1
           Keywords:  coerce,        |  Operating System:  Unknown/Multiple
  nominal                            |
       Architecture:                 |   Type of failure:  Incorrect result
  Unknown/Multiple                   |  at runtime
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 When you make a function with a constant result, the optimizer will turn
 it into a cast of a CAF, even if doing so coerces a nominal parameter into
 a different one.

 Minimal Example program:

 {{{#!hs
 {-# LANGUAGE RoleAnnotations #-}
 import Debug.Trace (trace)
 type role Nom nominal
 data Nom a = Nom Int deriving Show
 class Gen g where
  gen :: g
 instance Gen (Nom a) where
  gen = trace "genD" $ Nom 0

 main = print (gen :: Nom Int) >> print (gen :: Nom ()) >> print (gen ::
 Nom Char)
 }}}

 This program shows that only one value of type Nom is created and shared,
 even though doing so requires coercing a nominal role

 I discovered this while checking core for sharing after creating a
 constraint result caching mechanism.  An IOref ended up being shared for
 multiple different constraint result holders

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


More information about the ghc-tickets mailing list