[Haskell-cafe] Re: FASTER primes
Daniel Fischer
daniel.is.fischer at web.de
Wed Jan 13 06:33:22 EST 2010
Am Mittwoch 13 Januar 2010 10:43:42 schrieb Heinrich Apfelmus:
> I wonder whether it's really the liveness of pair in
>
> mergeSP (a,b) pair
> = let sm = spMerge b (fst pair)
> in (a ++ fst sm, merge (snd sm) (snd pair))
>
> that is responsible for the space leak, for chances are that Sparud's
> technique applies and pair is properly disposed of. Rather, it could
> be that we need the stronger property that forcing the second component
> will evaluate the first to NF.
I think that is responsible. At least that's how I understand the core:
mergeSP (a,b) ~(c,d) = (a ++ bc, merge b' d)
where
(bc, b') = spMerge b c
spMerge ...
----------------------------------------------------------------------
OldMerge.$wmergeSP :: [GHC.Types.Int]
-> [GHC.Types.Int]
-> ([GHC.Types.Int], [GHC.Types.Int])
-> (# [GHC.Types.Int], [GHC.Types.Int] #)
GblId
[Arity 3
Str: DmdType LLL]
OldMerge.$wmergeSP =
\ (ww_sny :: [GHC.Types.Int])
(ww1_snz :: [GHC.Types.Int])
(w_snB :: ([GHC.Types.Int], [GHC.Types.Int])) ->
let {
ds_so7 [ALWAYS Just D(SS)] :: ([GHC.Types.Int], [GHC.Types.Int])
LclId
[Str: DmdType]
ds_so7 =
case w_snB of _ { (c_adj, _) ->
case OldMerge.$wspMerge ww1_snz c_adj
of _ { (# ww3_snH, ww4_snI #) ->
(ww3_snH, ww4_snI)
}
} } in
(# GHC.Base.++
@ GHC.Types.Int
ww_sny
(case ds_so7 of _ { (bc_ajQ, _) -> bc_ajQ }),
case ds_so7 of _ { (_, b'_ajS) ->
case w_snB of _ { (_, d_adk) -> OldMerge.merge b'_ajS d_adk }
-- Here, in the second component of the result,
-- we reference the entire pair to get the dorks
} #)
OldMerge.mergeSP :: ([GHC.Types.Int], [GHC.Types.Int])
-> ([GHC.Types.Int], [GHC.Types.Int])
-> ([GHC.Types.Int], [GHC.Types.Int])
GblId
[Arity 2
Worker OldMerge.$wmergeSP
Str: DmdType U(LL)Lm]
OldMerge.mergeSP =
__inline_me (\ (w_snw :: ([GHC.Types.Int], [GHC.Types.Int]))
(w1_snB :: ([GHC.Types.Int], [GHC.Types.Int])) ->
case w_snw of _ { (ww_sny, ww1_snz) ->
case OldMerge.$wmergeSP ww_sny ww1_snz w1_snB
of _ { (# ww3_snN, ww4_snO #) ->
(ww3_snN, ww4_snO)
}
})
----------------------------------------------------------------------
vs.
mergeSP (a,b) ~(c,d) = (a ++ bc, m)
where
(bc,m) = spMerge b c d
spMerge ...
----------------------------------------------------------------------
NewMerge.$wmergeSP :: [GHC.Types.Int]
-> [GHC.Types.Int]
-> ([GHC.Types.Int], [GHC.Types.Int])
-> (# [GHC.Types.Int], [GHC.Types.Int] #)
GblId
[Arity 3
Str: DmdType LLL]
NewMerge.$wmergeSP =
\ (ww_snB :: [GHC.Types.Int])
(ww1_snC :: [GHC.Types.Int])
(w_snE :: ([GHC.Types.Int], [GHC.Types.Int])) ->
let {
ds_soa [ALWAYS Just D(SS)] :: ([GHC.Types.Int], [GHC.Types.Int])
LclId
[Str: DmdType]
ds_soa =
case w_snE of _ { (c_adj, d_adk) ->
-- There's no reference to the pair after this
case NewMerge.$wspMerge ww1_snC c_adj d_adk
of _ { (# ww3_snK, ww4_snL #) ->
(ww3_snK, ww4_snL)
}
} } in
(# GHC.Base.++
@ GHC.Types.Int
ww_snB
(case ds_soa of _ { (bc_ajT, _) -> bc_ajT }),
case ds_soa of _ { (_, b'_ajV) -> b'_ajV } #)
NewMerge.mergeSP :: ([GHC.Types.Int], [GHC.Types.Int])
-> ([GHC.Types.Int], [GHC.Types.Int])
-> ([GHC.Types.Int], [GHC.Types.Int])
GblId
[Arity 2
Worker NewMerge.$wmergeSP
Str: DmdType U(LL)Lm]
NewMerge.mergeSP =
__inline_me (\ (w_snz :: ([GHC.Types.Int], [GHC.Types.Int]))
(w1_snE :: ([GHC.Types.Int], [GHC.Types.Int])) ->
case w_snz of _ { (ww_snB, ww1_snC) ->
case NewMerge.$wmergeSP ww_snB ww1_snC w1_snE
of _ { (# ww3_snQ, ww4_snR #) ->
(ww3_snQ, ww4_snR)
}
})
----------------------------------------------------------------------
More information about the Haskell-Cafe
mailing list