Skip to content

Commit

Permalink
Make 'length' fusible
Browse files Browse the repository at this point in the history
This change makes fusible 'Data.Vector.Generic.length',
which currently can be inlined but doesn't fuse well.
Before this revision, 'length' uses non-fusible 'stream''.
This revision replaces 'stream'' with fusible 'stream',
and at the same time substitute the mutually-recursive
occurrences of 'length' with 'basicLength'.

Rationale:
The current definition was introduced in the commit
a811a86.
Prior to that commit, 'length' could not even be inlined,
because GHC elected it to be a loop-breaker due to
the cyclic references among 'stream', 'clone', 'length', and
'unsafeCopy'.
This failure of inlining was reported as
haskell#97.

The commit a811a86 resolved this by replacing 'stream'
with 'stream'' in the definition of 'length'. The function
'stream' refers to 'clone' in its fusion rule, but 'stream''
doesn't possess any rule. This cuts open the cycle of references
and makes 'length' inlinable.

However, since 'stream'' doesn't possess any rule, defining
'length' = 'Bundle.length' . 'stream''
is all the same as setting
'length' = 'basicLength'.
This prevents any stream fusion from
happening.

This commit resolves this problem by resetting 'length' back
to be 'Bundle.length' . 'stream', and instead replacing
cyclic occurrence of 'length' with 'basicLength'
(Just *inlined the simplification result of the definition*).
Now 'length' is both inlinable and fusible.

Fixes: haskell#306
See also: haskell#97
  • Loading branch information
gksato committed Jun 3, 2020
1 parent eeb42ad commit 50c0ff0
Showing 1 changed file with 5 additions and 11 deletions.
16 changes: 5 additions & 11 deletions Data/Vector/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -222,7 +222,7 @@ import qualified Data.Traversable as T (Traversable(mapM))
-- | /O(1)/ Yield the length of the vector
length :: Vector v a => v a -> Int
{-# INLINE length #-}
length = Bundle.length . stream'
length = Bundle.length . stream

-- | /O(1)/ Test whether a vector is empty
null :: Vector v a => v a -> Bool
Expand Down Expand Up @@ -1986,7 +1986,7 @@ copy
:: (PrimMonad m, Vector v a) => Mutable v (PrimState m) a -> v a -> m ()
{-# INLINE copy #-}
copy dst src = BOUNDS_CHECK(check) "copy" "length mismatch"
(M.length dst == length src)
(M.length dst == basicLength src)
$ unsafeCopy dst src

-- | /O(n)/ Copy an immutable vector into a mutable one. The two vectors must
Expand All @@ -1995,7 +1995,7 @@ unsafeCopy
:: (PrimMonad m, Vector v a) => Mutable v (PrimState m) a -> v a -> m ()
{-# INLINE unsafeCopy #-}
unsafeCopy dst src = UNSAFE_CHECK(check) "unsafeCopy" "length mismatch"
(M.length dst == length src)
(M.length dst == basicLength src)
$ (dst `seq` src `seq` basicUnsafeCopy dst src)

-- Conversions to/from Bundles
Expand All @@ -2004,13 +2004,7 @@ unsafeCopy dst src = UNSAFE_CHECK(check) "unsafeCopy" "length mismatch"
-- | /O(1)/ Convert a vector to a 'Bundle'
stream :: Vector v a => v a -> Bundle v a
{-# INLINE_FUSED stream #-}
stream v = stream' v

-- Same as 'stream', but can be used to avoid having a cycle in the dependency
-- graph of functions, which forces GHC to create a loop breaker.
stream' :: Vector v a => v a -> Bundle v a
{-# INLINE stream' #-}
stream' v = Bundle.fromVector v
stream v = Bundle.fromVector v

{-
stream v = v `seq` n `seq` (Bundle.unfoldr get 0 `Bundle.sized` Exact n)
Expand Down Expand Up @@ -2133,7 +2127,7 @@ clone :: Vector v a => v a -> New v a
{-# INLINE_FUSED clone #-}
clone v = v `seq` New.create (
do
mv <- M.new (length v)
mv <- M.new (basicLength v)
unsafeCopy mv v
return mv)

Expand Down

0 comments on commit 50c0ff0

Please sign in to comment.