#2110: Rules to eliminate casted id's
---------------------------------+------------------------------------------
    Reporter:  igloo             |       Owner:                  
        Type:  feature request   |      Status:  new             
    Priority:  lowest            |   Milestone:  7.6.2           
   Component:  Compiler          |     Version:  6.8.2           
    Keywords:                    |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
  Difficulty:  Unknown           |    Testcase:                  
   Blockedby:                    |    Blocking:                  
     Related:                    |  
---------------------------------+------------------------------------------

Comment(by nomeata):

 Thanks for bearing with my spam. I found another reason why a programmer
 might already expect this to work via RULES, and an indication to a
 possible implementation. Consider this code:

 {{{
 newtype X = X Int
 b :: [Int] -> [X]
 b = map X
 c :: [Int] -> [X]
 c = map unsafeCoerce#
 }}}

 Both functions generate almost identical core code, they even share the
 same „identitiy“ function:

 {{{
 Test.b1 :: GHC.Types.Int -> GHC.Types.Int
 [GblId,
  Arity=1,
  Caf=NoCafRefs,
  Str=DmdType S,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=1, Value=True,
          ConLike=True, Cheap=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=True)}]
 Test.b1 = \ (tpl_B1 :: GHC.Types.Int) -> tpl_B1

 Test.b :: [GHC.Types.Int] -> [Test.X]
 [GblId,
  Arity=1,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
          ConLike=True, Cheap=True, Expandable=True,
          Guidance=IF_ARGS [] 20 60}]
 Test.b =
   GHC.Base.map
     @ GHC.Types.Int
     @ Test.X
     (Test.b1
      `cast` (<GHC.Types.Int> -> Sym (Test.NTCo:X)
              :: (GHC.Types.Int -> GHC.Types.Int) ~# (GHC.Types.Int ->
 Test.X)))

 Test.c :: [GHC.Types.Int] -> [Test.X]
 [GblId,
  Arity=1,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
          ConLike=True, Cheap=True, Expandable=True,
          Guidance=IF_ARGS [] 20 60}]
 Test.c =
   GHC.Base.map
     @ GHC.Types.Int
     @ Test.X
     (Test.b1
      `cast` (<GHC.Types.Int> -> UnsafeCo GHC.Types.Int Test.X
              :: (GHC.Types.Int -> GHC.Types.Int) ~# (GHC.Types.Int ->
 Test.X)))
 }}}

 The only difference is how the coercion is being constructed. Now a the
 author of the list data type might have added this rule:

 {{{
 {-# RULES
 "map/coerce" map unsafeCoerce# = unsafeCoerce#
   #-}
 }}}

 Then assuming the rule fires on ```c``` (and I could swear that it did
 just an hour ago, but I cannot reproduce it now, it seems that now the
 inlining of ```unsafeCoerce#``` happens too soon), then would it not make
 sense to have it also fire on ```b```, giving us the desired result?

 I tried to create a quick hack that would unfold ```unsafeCoerce#``` on
 the LHS of a rule so that the "map/coerce" rule would fire on both the
 inlined ```c``` as well as on ```b```, but my GHC foo is not strong enough
 yet.

 Nevertheless I think letting unsafeCoerce# in a RULE match also functions
 known to be just specializations of it (namely newtype constructors and
 deconstructors) seems to be a reasonably clean way to achieve this,
 without exposing any Core details (casts, equality types) to the surface
 syntax.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2110#comment:25>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to