[GHC] #14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2

GHC ghc-devs at haskell.org
Thu Sep 28 16:08:18 UTC 2017


#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2
---------------------------------+--------------------------------------
        Reporter:  j.waldmann    |                Owner:  (none)
            Type:  bug           |               Status:  new
        Priority:  normal        |            Milestone:
       Component:  Compiler      |              Version:  8.2.1
      Resolution:                |             Keywords:
Operating System:  Linux         |         Architecture:  x86_64 (amd64)
 Type of failure:  None/Unknown  |            Test Case:
      Blocked By:                |             Blocking:
 Related Tickets:                |  Differential Rev(s):
       Wiki Page:                |
---------------------------------+--------------------------------------

Comment (by simonpj):

 I know what is going on. It's extremely annoying.  In module `Foo` we get
 this after demand analysis:
 {{{
 pre_images [InlPrag=INLINABLE] :: forall a k k. Enum a => a -> Rel k k ->
 Set k
 [Str=<S(LLLC(S(S))LLLL),1*U(A,A,A,1*C1(U(U)),A,A,A,A)>
      <L,U>
      <S(LS),1*U(A,U)>,        <----------- NB
  Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 0 20] 120 0
          Tmpl= \ (@ a_a52c) (@ k_a52e) (@ k_a52d)
                  ($dEnum_a52n [Occ=Once] :: Enum a_a52c)
                  (x_a2k0 [Occ=Once] :: a_a52c)
                  (rel_a2k1 [Occ=Once!] :: Rel k_a52e k_a52d) ->
                  case rel_a2k1 of { Rel f_a2k2 [Occ=Once] g_a2k3
 [Occ=Once] ->
 NB ------->      case T14285a.$WRel @ k_a52d @ k_a52e g_a2k3 f_a2k2 of
                  { Rel f_a2jY [Occ=Once] _ [Occ=Dead] ->
                  IM.findWithDefault
                    @ (Set k_a52e)
                    (empty @ k_a52e)
                    (fromEnum @ a_a52c $dEnum_a52n x_a2k0)
                    (f_a2jY
                     `cast` (T14285a.N:Map[0] <k_a52d>_P <Set k_a52e>_N
                             :: (Map k_a52d (Set k_a52e) :: *)
                                ~R# (IM.IntMap (Set k_a52e) :: *)))
                  }
                  }}]
 pre_images
   = \ (@ a_a52c) (@ k_a52e) (@ k_a52d)
       ($dEnum_a52n [Dmd=<S(LLLC(S(S))LLLL),1*U(A,A,A,1*C1(U(U)),A,A,A,A)>]
          :: Enum a_a52c)
       (x_a2k0 :: a_a52c)
       (rel_a2k1 [Dmd=<S(LS),1*U(A,U)>] :: Rel k_a52e k_a52d) ->
       case rel_a2k1 of { Rel f_a2k2 [Dmd=<L,A>] g_a2k3 [Dmd=<S,1*U>] ->
       case fromEnum @ a_a52c $dEnum_a52n x_a2k0 of
       { GHC.Types.I# ww1_a57r [Dmd=<S,U>] ->
       Data.IntMap.Internal.$wfindWithDefault
         @ (Set k_a52e)
         (empty @ k_a52e)
         ww1_a57r
         (g_a2k3
          `cast` (T14285a.N:Map[0] <k_a52d>_P <Set k_a52e>_N
                  :: (Map k_a52d (Set k_a52e) :: *)
                     ~R# (IM.IntMap (Set k_a52e) :: *)))
       }
       }
 }}}
 Note that

 * The third arg is marked `<S(LS),1*U(A,U)>`, and so is strict, but its
 first component is unused.

 * And indeed `f_a2k2` is unsed in the body of `pre_images`

 * But alas, in the stable-unfolding, `f_a2k2` '''is''' used.  It is passed
 to `$WRel`, the wrapper for the strict data contructor `Rel`; it evaluates
 both arguments.

 * So if we w/w this function, we won't pass the first component; instead
 we'll make up `absentError "blah"` to fill the hole, expecting it not to
 be used.

 * Alas, when we do the same thing to the stable unfolding (see `Note
 [Worker-wrapper for INLINABLE functions]` in `WorkWrap.hs`) we ''do''
 evaluate that `absentError` call. Sigh.

 I'm not at all clear what to do about this, but at least we can see what
 is going on.  It's very much a corner case, so I don't want to harm
 mainstream cases for the sake of this one.

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


More information about the ghc-tickets mailing list