Skip to content

Commit

Permalink
Disable implicit fusion rules (haskell#348)
Browse files Browse the repository at this point in the history
A cherry-pick of haskell#348
onto 1.2.3.2, with some quick conflict fixes
  • Loading branch information
Bodigrim authored and jberryman committed Sep 1, 2021
1 parent 212d591 commit 874c316
Show file tree
Hide file tree
Showing 9 changed files with 121 additions and 446 deletions.
208 changes: 55 additions & 153 deletions Data/Text.hs

Large diffs are not rendered by default.

2 changes: 0 additions & 2 deletions Data/Text/Encoding.hs
Original file line number Diff line number Diff line change
Expand Up @@ -348,8 +348,6 @@ streamDecodeUtf8With onErr = decodeChunk B.empty 0 0
decodeUtf8 :: ByteString -> Text
decodeUtf8 = decodeUtf8With strictDecode
{-# INLINE[0] decodeUtf8 #-}
{-# RULES "STREAM stream/decodeUtf8 fusion" [1]
forall bs. F.stream (decodeUtf8 bs) = E.streamUtf8 strictDecode bs #-}

-- | Decode a 'ByteString' containing UTF-8 encoded text.
--
Expand Down
7 changes: 2 additions & 5 deletions Data/Text/Internal/Fusion/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -217,7 +217,6 @@ append (Stream next0 s01 len1) (Stream next1 s02 len2) =
{-# INLINE [0] append #-}

-- | /O(1)/ Returns the first character of a Text, which must be non-empty.
-- Subject to array fusion.
head :: Stream Char -> Char
head (Stream next s0 _len) = loop_head s0
where
Expand All @@ -232,7 +231,7 @@ head_empty = streamError "head" "Empty stream"
{-# NOINLINE head_empty #-}

-- | /O(1)/ Returns the first character and remainder of a 'Stream
-- Char', or 'Nothing' if empty. Subject to array fusion.
-- Char', or 'Nothing' if empty.
uncons :: Stream Char -> Maybe (Char, Stream Char)
uncons (Stream next s0 len) = loop_uncons s0
where
Expand Down Expand Up @@ -311,7 +310,6 @@ lengthI (Stream next s0 _len) = loop_length 0 s0
{-# INLINE[0] lengthI #-}

-- | /O(n)/ Compares the count of characters in a string to a number.
-- Subject to fusion.
--
-- This function gives the same answer as comparing against the result
-- of 'lengthI', but can short circuit if the count of characters is
Expand Down Expand Up @@ -565,7 +563,6 @@ foldr f z (Stream next s0 _len) = loop_foldr s0

-- | foldr1 is a variant of 'foldr' that has no starting value argument,
-- and thus must be applied to non-empty streams.
-- Subject to array fusion.
foldr1 :: (Char -> Char -> Char) -> Stream Char -> Char
foldr1 f (Stream next s0 _len) = loop0_foldr1 s0
where
Expand All @@ -587,7 +584,7 @@ intercalate s = concat . (L.intersperse s)
-- ----------------------------------------------------------------------------
-- ** Special folds

-- | /O(n)/ Concatenate a list of streams. Subject to array fusion.
-- | /O(n)/ Concatenate a list of streams.
concat :: [Stream Char] -> Stream Char
concat = L.foldr append empty
{-# INLINE [0] concat #-}
Expand Down
Loading

0 comments on commit 874c316

Please sign in to comment.