[GHC] #8335: Create more specialized entries to GC
GHC
ghc-devs at haskell.org
Tue Oct 6 16:15:47 UTC 2015
#8335: Create more specialized entries to GC
-------------------------------------+-------------------------------------
Reporter: jstolarek | Owner: bgamari
Type: task | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
-------------------------------------+-------------------------------------
Changes (by bgamari):
* status: new => closed
* resolution: => fixed
Comment:
I think this may be fixed (at least in the current state of `master`,
a3c78abcbdfe5025dc704acdcd0a85c78cabbd6b).
This program (taken from #8326),
{{{#!hs
{-# LANGUAGE MagicHash #-}
module Test where
import GHC.Prim
import GHC.Types
f :: Int# -> Int
f x | isTrue# (x ># 0#) = I# x
| otherwise = -(I# x)
}}}
produces this Core,
{{{#!hs
f :: Int# -> Int
f =
\ (x_anw :: Int#) ->
case tagToEnum# @ Bool (># x_anw 0#) of _ [Occ=Dead] {
False -> I# (negateInt# x_anw);
True -> I# x_anw
}
}}}
which is ultimately lowered to this C--,
{{{
Test.f_entry() // [R2]
{ info_tbl: [(cyv,
label: Test.f_info
rep:HeapRep static { Fun {arity: 1 fun_type:
ArgSpec 4} })]
stack_info: arg_space: 8 updfr_space: Just 8
}
{offset
cyv:
Hp = Hp + 16;
if (Hp > HpLim) goto cyz; else goto cyy;
cyz:
HpAlloc = 16;
R2 = R2;
R1 = Test.f_closure;
call (stg_gc_fun)(R2, R1) args: 8, res: 0, upd: 8;
cyy:
if (%MO_S_Gt_W64(R2, 0)) goto cyL; else goto cyI;
cyL:
I64[Hp - 8] = GHC.Types.I#_con_info;
I64[Hp] = R2;
R1 = Hp - 7;
call (P64[Sp])(R1) args: 8, res: 0, upd: 8;
cyI:
I64[Hp - 8] = GHC.Types.I#_con_info;
I64[Hp] = -R2;
R1 = Hp - 7;
call (P64[Sp])(R1) args: 8, res: 0, upd: 8;
}
}]
}}}
Jan, would you agree that all looks okay here?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8335#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list