I am trying to understand optimizations in ghc.
Consider the lexicographic list comparison.
To my mind, the most natural program is
lexListComp :: (a -> b -> Ordering) -> [a] -> [b] -> Ordering
lexListComp cp = lcp
where
lcp [] [] = EQ
lcp [] _ = LT
lcp _ [] = GT
lcp (x:xs) (y:ys) = case cp x y of EQ -> lcp xs ys
v -> v
{-# SPECIALIZE lexListComp :: (Z->Z->Ordering)->[Z]->[Z]->Ordering
#-} -- popular case
type Z = Int
I expected this to perform for [Z] as fast as the special function
for [Z]:
cpZ :: [Z] -> [Z] -> Ordering
cpZ [] [] = EQ
cpZ [] _ = LT
cpZ _ [] = GT
cpZ (x:xs) (y:ys) = case compare x y of EQ -> cpZ xs ys
v -> v
Why cp = lexListComp compare (for [Z]) occurs essentially slower
than cpZ ?
Substituting this equation for cp, the compiler has probably to
obtain the copy of the function cpZ - ?
Below the comparison is given by maxBy c $ sortBy c $ subLists xss
with c = cpZ,
= cp = lexListComp compare :: [Z] -> [Z] -> Ordering
--------------------------------------------------------------------
import List (sortBy)
Z, lexListComp, lpZ as above
cp = lexListComp compare :: [Z] -> [Z] -> Ordering
main = let xss = sublists [1,9,2,8,3,7,4,6,5,1,9,2,8,3,7] ::[[Z]]
ys = maxBy cpZ$ sortBy cpZ xss
ys' = maxBy cp $ sortBy cp xss
in
putStr$ shows ys' "\n" -- switch ys - ys'
maxBy :: (a -> a -> Ordering) -> [a] -> a
maxBy cp xs = m xs
where m [x] = x
m (x:y:xs) = case cp x y of LT -> m (y:xs)
_ -> m (x:xs)
sublists :: [a] -> [[a]]
sublists [] = [[]]
sublists (x:xs) = case sublists xs of ls -> (map (x:) ls)++ls
--------------------------------------------------------------------
ghc-4.04~June-20 -c -O Main.hs; ghc -o run Main.o; time ./run
gives the result [9,9,8,7] and the timing (on our machine)
cpZ 3.51 sec
cp - spec. 4.13
cp - no spec. 4.13
(comparing on faster machines might need adding a couple of elements
to xss).
The measured ratio here is more than 4.13/3.51 - because the program
consists not only of the list comparisons.
Further, i tried {-# INLINE lexListComp #-}, {-# INLINE cp #-}
- for curiosity.
And this slows down cp to 6 sec - ?
------------------
Sergey Mechveliani
[EMAIL PROTECTED]