[GHC] #3606: The Ord instance for unboxed arrays is very inefficient
GHC
ghc-devs at haskell.org
Fri Nov 8 20:49:38 UTC 2013
#3606: The Ord instance for unboxed arrays is very inefficient
--------------------------------------------+------------------------------
Reporter: blarsen | Owner:
Type: bug | Status: new
Priority: lowest | Milestone: 7.10.1
Component: libraries (other) | Version: 6.10.4
Resolution: | Keywords: array
Operating System: Unknown/Multiple | Architecture: x86_64
Type of failure: Runtime performance bug | (amd64)
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Changes (by hvr):
* keywords: array, performance, Ord => array
* os: Linux => Unknown/Multiple
* milestone: 7.6.2 => 7.10.1
Old description:
> The Ord instance for unboxed arrays defined in Data.Array.Base results in
> code that makes lots of heap allocations and is very slow.
>
> For the record, the Ord instance is defined as so in Data.Array.Base:
>
> {{{
> instance (Ix ix, Ord e, IArray UArray e) => Ord (UArray ix e) where
> compare = cmpUArray
>
> {-# INLINE cmpUArray #-}
> cmpUArray :: (IArray UArray e, Ix i, Ord e) => UArray i e -> UArray i e
> -> Ordering
> cmpUArray arr1 arr2 = compare (assocs arr1) (assocs arr2)
> }}}
>
> The 'assocs' calls don't appear to be deforested away, and hence, when
> using the Ord functions on unboxed arrays, the performance is bad to the
> point of making them unusable.
>
> It seems reasonable to me that 'compare' for unboxed arrays could be
> implemented strictly, in a tight loop, without any heap allocations at
> all.
New description:
The Ord instance for unboxed arrays defined in `Data.Array.Base` results
in code that makes lots of heap allocations and is very slow.
For the record, the `Ord` instance is defined as so in `Data.Array.Base`:
{{{#!hs
instance (Ix ix, Ord e, IArray UArray e) => Ord (UArray ix e) where
compare = cmpUArray
{-# INLINE cmpUArray #-}
cmpUArray :: (IArray UArray e, Ix i, Ord e) => UArray i e -> UArray i e ->
Ordering
cmpUArray arr1 arr2 = compare (assocs arr1) (assocs arr2)
}}}
The `assocs` calls don't appear to be deforested away, and hence, when
using the `Ord` functions on unboxed arrays, the performance is bad to the
point of making them unusable.
It seems reasonable to me that `compare` for unboxed arrays could be
implemented strictly, in a tight loop, without any heap allocations at
all.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/3606#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list