[GHC] #14195: Generalize makeStableName#

GHC ghc-devs at haskell.org
Thu Sep 7 15:12:30 UTC 2017


#14195: Generalize makeStableName#
-------------------------------------+-------------------------------------
           Reporter:  andrewthad     |             Owner:  (none)
               Type:  feature        |            Status:  new
  request                            |
           Priority:  low            |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The function `makeStableName#` has the following type:

 {{{
 makeStableName# :: a -> State# RealWorld -> (#State# RealWorld,
 StableName# a#)
 }}}

 I believe that it could safely be changed to:

 {{{
 makeStableName# :: a -> State# s -> (#State# s, StableName# a#)
 }}}

 Currently, I have some code that looks like this:

 {{{
 {-# LANGUAGE MagicHash #-}
 {-# LANGUAGE UnboxedTuples #-}
 module Example
   ( Stable
   , stabilize
   , destabilize
   ) where

 import GHC.Prim
 import GHC.ST

 data Stable s a = Stable (StableName# a) a

 stabilize :: a -> ST s (Stable s a)
 stabilize a = ST $ \ s ->
   case makeStableName# a (unsafeCoerce# s) of (# s', sn #) -> (#
 unsafeCoerce# s', Stable sn a #)

 destabilize :: Stable s a -> a
 destabilize (Stable _ a) = a

 instance Eq a => Eq (Stable s a) where
   Stable sn1 a1 == Stable sn2 a2 = case eqStableName# sn1 sn2 of
     0# -> a1 == a2
     _  -> True
 }}}

 I want to be working in `ST`, not in `IO`, and I believe that this use of
 `unsafeCoerce#` is safe. However, it would be nice to not have to use it
 at all.

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


More information about the ghc-tickets mailing list