#4023: Inlining pragma fails to fire
---------------------------------+------------------------------------------
    Reporter:  LouisWasserman    |       Owner:          
        Type:  bug               |      Status:  new     
    Priority:  normal            |   Component:  Compiler
     Version:  6.12.2            |    Keywords:          
          Os:  Unknown/Multiple  |    Testcase:          
Architecture:  Unknown/Multiple  |     Failure:  Other   
---------------------------------+------------------------------------------
 In an attempt to ensure deforestation in Data.Map usage, toAscList was
 reimplemented as follows:

 {{{
 {-# INLINE toAscList #-}
 -- | /O(n)/. Convert to an ascending list.
 --
 -- > toAscList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
 toAscList :: Map k a -> [(k,a)]
 #ifdef __GLASGOW_HASKELL__
 toAscList t = GHC.build (\ c n -> foldrWithKey (curry c) n t)
 #else
 toAscList t   = foldrWithKey (\k x xs -> (k,x):xs) [] t
 #endif
 }}}

 As one might hope, ghc-core gives the following compilation result:

 {{{
 Data.Map.toAscList :: forall k_a8cF a_a8cG.
                       Data.Map.Map k_a8cF a_a8cG -> [(k_a8cF, a_a8cG)]
 GblId

 Data.Map.toAscList =
   __inline_me (\ (@ k_a8E0)
                  (@ a_a8E1)
                  (t_a8ot :: Data.Map.Map k_a8E0 a_a8E1) ->
                  build
                    @ (k_a8E0, a_a8E1)
                    (\ (@ b_a8E3)
                       (c_a8ou :: (k_a8E0, a_a8E1) -> b_a8E3 -> b_a8E3)
                       (n_a8ov :: b_a8E3) ->
                       Data.Map.foldrWithKey
                         @ k_a8E0
                         @ a_a8E1
                         @ b_a8E3
                         (Data.Tuple.curry @ k_a8E0 @ a_a8E1 @ (b_a8E3 ->
 b_a8E3) c_a8ou)
                         n_a8ov
                         t_a8ot))
 }}}

 But mapKeysWith is compiled -- in the very same file! -- to

 {{{
 Data.Map.mapKeysWith :: forall k2_a8dc a_a8dd k1_a8de.
                         (Ord k2_a8dc) =>
                         (a_a8dd -> a_a8dd -> a_a8dd)
                         -> (k1_a8de -> k2_a8dc)
                         -> Data.Map.Map k1_a8de a_a8dd
                         -> Data.Map.Map k2_a8dc a_a8dd
 GblId

 Data.Map.mapKeysWith =
   \ (@ k2_a8Qc)
     (@ a_a8Qd)
     (@ k1_a8Qe)
     ($dOrd_a8QE :: Ord k2_a8Qc)
     (c_a8nI :: a_a8Qd -> a_a8Qd -> a_a8Qd)
     (f_a8nJ :: k1_a8Qe -> k2_a8Qc)
     (eta_B1 :: Data.Map.Map k1_a8Qe a_a8Qd) ->
     Data.Map.fromListWithKey
       @ k2_a8Qc
       @ a_a8Qd
       $dOrd_a8QE
       (\ _ (x_a8ok :: a_a8Qd) (y_a8ol :: a_a8Qd) -> c_a8nI x_a8ok y_a8ol)
       (map
          @ (k1_a8Qe, a_a8Qd)
          @ (k2_a8Qc, a_a8Qd)
          (\ (ds_d9om :: (k1_a8Qe, a_a8Qd)) ->
             case ds_d9om of _ { (x_a8nL, y_a8nM) -> (f_a8nJ x_a8nL,
 y_a8nM) })
          (Data.Map.toAscList @ k1_a8Qe @ a_a8Qd eta_B1))
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4023>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to