Constant folding unpackAppendCString
Consider:
{-# LANGUAGE MagicHash #-}
{-# OPTIONS_GHC -ddump-simpl -dsuppress-all -dno-typeable-binds -O2 #-}
module Test (foobar, foobar2, foobar3) where
import GHC.Exts
bar :: String
bar = unpackCString# "bar"#
foobar :: String
foobar = unpackAppendCString# "foo"# bar
foobar2 :: String
foobar2 = unpackAppendCString# "foo"# (unpackCString# "bar"#)
foobar3 :: String
foobar3 = unpackAppendCString# "foo"# (unpackAppendCString# "bar"# [])
We would expect appending of string literals to happen at compile time but currently we get:
==================== Tidy Core ====================
Result size of Tidy Core
= {terms: 21, types: 10, coercions: 0, joins: 0/0}
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
foobar6 = "foo"#
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
foobar5 = "bar"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
foobar1 = unpackCString# foobar5
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
foobar = unpackAppendCString# foobar6 foobar1
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
foobar2 = foobar
-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
foobar7 = unpackAppendCString# foobar5 []
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
foobar3 = unpackAppendCString# foobar6 foobar7
The example is contrived but the real case happened in the GHC's LLVM codegen where we fail to build shared FastStrings because of this (e.g. fsLit $ "xyz" ++ suf
).
Patch coming.