[Haskell-cafe] fast Eucl. dist. - Haskell vs C
Don Stewart
dons at galois.com
Mon May 18 11:55:05 EDT 2009
claus.reinke:
>>> dist_fast :: UArr Double -> UArr Double -> Double
>>> dist_fast p1 p2 = sumDs `seq` sqrt sumDs
>>> where
>>> sumDs = sumU ds
>>> ds = zipWithU euclidean p1 p2
>>> euclidean x y = d*d
>>> where
>>> d = x-y
>>
>> You'll probably want to make sure that 'euclidian' is specialized to
>> the types you need (here 'Double'), not used overloaded for 'Num a=>a'
>> (check -ddump-tc, or -ddump-simpl output).
>
> Sorry about that misdirection - as it happened, I was looking at the tc
> output for 'dist_fast' (euclidean :: forall a. (Num a) => a -> a -> a),
> but the simpl output for 'dist_fast_inline' .., which uses things like
>
> __inline_me ..
> case Dist.sumU (Dist.$wzipWithU ..
> GHC.Num.- @ GHC.Types.Double GHC.Float.$f9 x_aLt y_aLv
>
> Once I actually add a 'dist_fast_inline_caller', that indirection
> disappears in the inlined code, just as it does for dist_fast itself.
>
> dist_fast_inlined_caller :: UArr Double -> UArr Double -> Bool
> dist_fast_inlined_caller p1 p2 = dist_fast_inlined p1 p2 > 2
>
> However, in the simpl output for 'dist_fast_inline_caller', the
> 'sumU' and 'zipWithU' still don't seem to be fused - Don?
All the 'seq's and so on should be unnecessary, and even so, I still get
the expected fusion:
import Control.Monad
import System.Environment
import System.IO
import Data.Array.Vector
{-
dist :: UArr Double -> UArr Double -> Double
dist p1 p2 = sumU (zipWithU euclidean p1 p2)
where
euclidean x y = d*d where d = x-y
-}
main = do
[dim] <- map read `fmap` getArgs
print $
dist_fast_inlined
(enumFromToFracU 1.0 dim)
(enumFromToFracU 1.0 dim)
dist_fast_inlined :: UArr Double -> UArr Double -> Double
{-# INLINE dist_fast_inlined #-}
dist_fast_inlined p1 p2 = sumDs `seq` sqrt sumDs
where
sumDs = sumU ds
ds = zipWithU euclidean p1 p2
euclidean x y = d*d
where
d = x-y
{-
19 RuleFired
2 /##
3 SC:$wfold0
5 int2Double#
1 map
1 mapList
3 streamU/unstreamU
2 truncate/Double->Int
1 unpack
1 unpack-list
$s$wfold_s1TB :: Double# -> Double# -> Double# -> Double#
-}
More information about the Haskell-Cafe
mailing list