[GHC] #2110: Rules to eliminate casted id's
GHC
ghc-devs at haskell.org
Sun Sep 15 21:32:37 CEST 2013
#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
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by nomeata):
I have a first working prototype, pushed to the wip/nomeata-T2110 branch.
Comments how to do that properly and non-hacky are welcome.
I ended up implementing the first idea, and this is what works: In the
file
{{{
module Test where
import GHC.Exts
import Unsafe.Coerce
{-# RULES
"map/coerce" map coerce = coerce
#-}
newtype Age = Age Int
foo :: [Int] -> [Age]
foo = map Age
bar :: [Int] -> [Age]
bar = map coerce
baz :: [Int] -> [Age]
baz = map unsafeCoerce
}}}
the rule will be desugared to
{{{
------ Local rules for imported ids --------
"map/coerce" [ALWAYS]
forall (@ a_aET)
(@ b_aEU)
($dCoercible_aEO :: a_aET GHC.Prim.~R# b_aEU).
GHC.Base.map @ a_aET
@ b_aEU
((\ (tpl_B1 :: a_aET) -> tpl_B1)
`cast` (<a_aET>_R -> ($dCoercible_aEO)
:: (a_aET -> a_aET) ~# (a_aET -> b_aEU)))
= GHC.Prim.coerce
@ [a_aET]
@ [b_aEU]
(GHC.Types.MkCoercible
@ [a_aET] @ [b_aEU] @~ [($dCoercible_aEO)]_R)
}}}
and this indeed matches all three calls to `map`:
{{{
Test.bar1 :: [GHC.Types.Int] -> [GHC.Types.Int]
Test.bar1 = \ (tpl_B2 :: [GHC.Types.Int]) -> tpl_B2
Test.foo :: [GHC.Types.Int] -> [Test.Age]
Test.foo =
Test.bar1
`cast` (<[GHC.Types.Int]>_R -> [Sym Test.NTCo:Age[0]]_R
:: ([GHC.Types.Int] -> [GHC.Types.Int])
~#
([GHC.Types.Int] -> [Test.Age]))
Test.bar :: [GHC.Types.Int] -> [Test.Age]
Test.bar =
Test.bar1
`cast` (<[GHC.Types.Int]>_R -> [Sym Test.NTCo:Age[0]]_R
:: ([GHC.Types.Int] -> [GHC.Types.Int])
~#
([GHC.Types.Int] -> [Test.Age]))
}}}
It does not work yet for `unsafeCoerce`, as for some reason that function
is not unfolded:
{{{
Test.baz =
GHC.Base.map
@ GHC.Types.Int
@ Test.Age
((Unsafe.Coerce.unsafeCoerce1 @ GHC.Types.Int @ Test.Age)
`cast` (<GHC.Types.Int>_R -> UnivCo R GHC.Types.Int Test.Age
:: (GHC.Types.Int -> GHC.Types.Int)
~#
(GHC.Types.Int -> Test.Age)))
}}}
but if it were, it would work as well :-)
I find this is quite a nice result so far, the user-facing part is slick
and simple, and it shows that the `Coercible` design is at least usable.
Should this direction be further pursued?
(PS: Special-casing `coerce` in `Rules.match` is difficult, as `Rules` is
a very basic module, imported for example in `MkId` which defines
`coerceId`.)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/2110#comment:38>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list