[Haskell-cafe] Hints for Euler Problem 11
Ketil Malde
ketil at ii.uib.no
Fri Aug 17 03:46:41 EDT 2007
On Thu, 2007-08-16 at 12:50 -0700, Kim-Ee Yeoh wrote:
>
> Aaron Denney wrote:
> >
> > On 2007-08-15, Pekka Karjalainen <p3k at iki.fi> wrote:
> >> A little style issue here on the side, if I may. You don't need to use
> >> (++) to join multiline string literals.
> >>
> >> text = "If you want to have multiline string literals \
> >> \in your source code, you can break them up with \
> >> \backslashes. Any whitespace characters between \
> >> \two backslashes will be ignored."
> >
> > I find the first far more readable. The compiler should be able to
> > assemble it all at compile time, right?
> >
>
> 'Course not. The (++) function like all Haskell functions is only a
> /promise/ to do its job. What does "assembling at compile time"
> mean here:
>
> s = "I will not write infinite loops " ++ s
Let's check, shall we? I've never used core before, but there's a first
time for everything:
% cat C.hs
module Test where
x = "Foo" ++ "Bar"
y = "Zot" ++ y
% ghc -ddump-simpl C.hs
==================== Tidy Core ====================
Test.x :: [GHC.Base.Char]
[GlobalId]
[]
Test.x =
GHC.Base.++
@ GHC.Base.Char (GHC.Base.unpackCString# "Foo") (GHC.Base.unpackCString# "Bar")
Rec {
Test.y :: [GHC.Base.Char]
[GlobalId]
[]
Test.y = GHC.Base.++ @ GHC.Base.Char (GHC.Base.unpackCString# "Zot") Test.y
end Rec }
If I interpret it correctly, the compiler does approximately nothing -
reasonably enough, since we didn't ask for optimization. With -O:
% ghc -ddump-simpl C.hs -O
==================== Tidy Core ====================
Rec {
Test.y :: [GHC.Base.Char]
[GlobalId]
[Str: DmdType]
Test.y = GHC.Base.unpackAppendCString# "Zot" Test.y
end Rec }
Test.x :: [GHC.Base.Char]
[GlobalId]
[Str: DmdType]
Test.x = GHC.Base.unpackCString# "FooBar"
y gets turned into an unpackAppendCString#, which I can only presume is
a sensible way to represent a cyclic list, while x gets concatenated
compile-time.
-k
More information about the Haskell-Cafe
mailing list