#7542: GHC doesn't optimize (strict) composition with id
---------------------------------+------------------------------------------
    Reporter:  shachaf           |       Owner:                         
        Type:  bug               |      Status:  new                    
    Priority:  normal            |   Milestone:                         
   Component:  Compiler          |     Version:  7.6.1                  
    Keywords:                    |          Os:  Unknown/Multiple       
Architecture:  Unknown/Multiple  |     Failure:  Runtime performance bug
  Difficulty:  Unknown           |    Testcase:                         
   Blockedby:                    |    Blocking:                         
     Related:                    |  
---------------------------------+------------------------------------------
Changes (by shachaf):

  * status:  infoneeded => new


Comment:

 Here's an example of the sort of context this comes up in:

 {{{
 module T7542 where

 import Unsafe.Coerce

 newtype Id a = MkId { unId :: a }

 -- Think of `mapped` as `mapM`, but restricted to Id (we could make it
 work
 -- with any Functor, rather than just []). `over` takes the Id wrappers
 back
 -- off. The goal is to make it easy to compose mapped with other functions
 of
 -- the same form. The wrapper should be "free" because it's just newtype
 noise.

 mapped1 :: (a -> Id b) -> [a] -> Id [b]
 mapped1 f = MkId . map (unId . f)

 over1 :: ((a -> Id b) -> s -> Id t) -> (a -> b) -> s -> t
 over1 l f = unId . l (MkId . f)

 map1 :: (a -> b) -> [a] -> [b]
 map1 f xs = over1 mapped1 f xs
 -- Core: map1 = \f xs -> map (\x -> f x) xs

 -- over1 mapped1 = unId . MkId . map (unId . MkId . f)
 --               ~ map
 -- However, if f = ⊥, unId . MkId . f /= f!
 -- Therefore `over1 mapped1` must turn into \f -> map (\x -> f x)
 -- We can't expect GHC to compile it to `map` because it has different
 strictness.

 -- Let's define strict versions of (MkId .) and (unId .):
 mkIdDot2 :: (a -> b) -> a -> Id b
 mkIdDot2 f = f `seq` \x -> MkId (f x)

 unIdDot2 :: (a -> Id b) -> a -> b
 unIdDot2 f = f `seq` \x -> unId (f x)

 mapped2 :: (a -> Id b) -> [a] -> Id [b]
 mapped2 f = mkIdDot2 (map (unIdDot2 f))

 over2 :: ((a -> Id b) -> s -> Id t) -> (a -> b) -> s -> t
 over2 l f = unIdDot2 (l (mkIdDot2 f))

 map2 :: (a -> b) -> [a] -> [b]
 map2 f xs = over2 mapped2 f xs
 -- map2 should have the same semantics as map. But the Core isn't the
 same:
 -- Without -fpedantic-bottoms: map2 = \f xs -> map (\e -> f e) xs
 -- With -fpedantic-bottoms:
 -- map2 = \f xs -> map (case f of g { __DEFAULT -> \x -> g x }) xs
 -- Ideally, (case f of g { __DEFAULT -> \x -> g x }) would simply be f.

 -- Let's try manually telling GHC that our newtype compositions are
 coercions:
 -- (Ideally, this is what mkIdDot2 and unIdDot2 would compile into.)
 mkIdDot3 :: (a -> b) -> a -> Id b
 mkIdDot3 = unsafeCoerce

 unIdDot3 :: (a -> Id b) -> a -> b
 unIdDot3 = unsafeCoerce
 -- (Note: Due to #7398, we couldn't define a strict composition operator
 and
 -- rely on RULES to turn (MkId `dot`) into unsafeCoerce -- the `MkId`
 itself
 -- gets turned into a coercion before any RULES have a chance to fire.)

 mapped3 :: (a -> Id b) -> [a] -> Id [b]
 mapped3 f = mkIdDot3 (map (unIdDot3 f))

 over3 :: ((a -> Id b) -> s -> Id t) -> (a -> b) -> s -> t
 over3 l f = unIdDot3 (l (mkIdDot3 f))

 map3 :: (a -> b) -> [a] -> [b]
 map3 f xs = over3 mapped3 f xs
 -- Core: map3 = map
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7542#comment:2>
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