Skip to content

Commit 7c86915

Browse files
authored
Merge PR #241 (Address some of the fusion issues in #202)
2 parents 09971cf + 15d2070 commit 7c86915

File tree

3 files changed

+22
-35
lines changed

3 files changed

+22
-35
lines changed

Data/Text.hs

Lines changed: 9 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -605,7 +605,7 @@ isSingleton = S.isSingleton . stream
605605
-- Subject to fusion.
606606
length :: Text -> Int
607607
length t = S.length (stream t)
608-
{-# INLINE [0] length #-}
608+
{-# INLINE [1] length #-}
609609
-- length needs to be phased after the compareN/length rules otherwise
610610
-- it may inline before the rules have an opportunity to fire.
611611

@@ -702,7 +702,7 @@ intersperse c t = unstream (S.intersperse (safe c) (stream t))
702702
-- >>> T.reverse "desrever"
703703
-- "reversed"
704704
--
705-
-- Subject to fusion.
705+
-- Subject to fusion (fuses with its argument).
706706
reverse :: Text -> Text
707707
reverse t = S.reverse (stream t)
708708
{-# INLINE reverse #-}
@@ -1033,8 +1033,7 @@ scanl f z t = unstream (S.scanl g z (stream t))
10331033
{-# INLINE scanl #-}
10341034

10351035
-- | /O(n)/ 'scanl1' is a variant of 'scanl' that has no starting
1036-
-- value argument. Subject to fusion. Performs replacement on
1037-
-- invalid scalar values.
1036+
-- value argument. Performs replacement on invalid scalar values.
10381037
--
10391038
-- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
10401039
scanl1 :: (Char -> Char -> Char) -> Text -> Text
@@ -1052,8 +1051,7 @@ scanr f z = S.reverse . S.reverseScanr g z . reverseStream
10521051
{-# INLINE scanr #-}
10531052

10541053
-- | /O(n)/ 'scanr1' is a variant of 'scanr' that has no starting
1055-
-- value argument. Subject to fusion. Performs replacement on
1056-
-- invalid scalar values.
1054+
-- value argument. Performs replacement on invalid scalar values.
10571055
scanr1 :: (Char -> Char -> Char) -> Text -> Text
10581056
scanr1 f t | null t = empty
10591057
| otherwise = scanr f (last t) (init t)
@@ -1237,7 +1235,7 @@ takeWhile p t@(Text arr off len) = loop 0
12371235

12381236
-- | /O(n)/ 'takeWhileEnd', applied to a predicate @p@ and a 'Text',
12391237
-- returns the longest suffix (possibly empty) of elements that
1240-
-- satisfy @p@. Subject to fusion.
1238+
-- satisfy @p@.
12411239
-- Examples:
12421240
--
12431241
-- >>> takeWhileEnd (=='o') "foo"
@@ -1252,13 +1250,6 @@ takeWhileEnd p t@(Text arr off len) = loop (len-1) len
12521250
where (c,d) = reverseIter t i
12531251
{-# INLINE [1] takeWhileEnd #-}
12541252

1255-
{-# RULES
1256-
"TEXT takeWhileEnd -> fused" [~1] forall p t.
1257-
takeWhileEnd p t = S.reverse (S.takeWhile p (S.reverseStream t))
1258-
"TEXT takeWhileEnd -> unfused" [1] forall p t.
1259-
S.reverse (S.takeWhile p (S.reverseStream t)) = takeWhileEnd p t
1260-
#-}
1261-
12621253
-- | /O(n)/ 'dropWhile' @p@ @t@ returns the suffix remaining after
12631254
-- 'takeWhile' @p@ @t@. Subject to fusion.
12641255
dropWhile :: (Char -> Bool) -> Text -> Text
@@ -1278,7 +1269,7 @@ dropWhile p t@(Text arr off len) = loop 0 0
12781269

12791270
-- | /O(n)/ 'dropWhileEnd' @p@ @t@ returns the prefix remaining after
12801271
-- dropping characters that satisfy the predicate @p@ from the end of
1281-
-- @t@. Subject to fusion.
1272+
-- @t@.
12821273
--
12831274
-- Examples:
12841275
--
@@ -1292,13 +1283,6 @@ dropWhileEnd p t@(Text arr off len) = loop (len-1) len
12921283
where (c,d) = reverseIter t i
12931284
{-# INLINE [1] dropWhileEnd #-}
12941285

1295-
{-# RULES
1296-
"TEXT dropWhileEnd -> fused" [~1] forall p t.
1297-
dropWhileEnd p t = S.reverse (S.dropWhile p (S.reverseStream t))
1298-
"TEXT dropWhileEnd -> unfused" [1] forall p t.
1299-
S.reverse (S.dropWhile p (S.reverseStream t)) = dropWhileEnd p t
1300-
#-}
1301-
13021286
-- | /O(n)/ 'dropAround' @p@ @t@ returns the substring remaining after
13031287
-- dropping characters that satisfy the predicate @p@ from both the
13041288
-- beginning and end of @t@. Subject to fusion.
@@ -1311,7 +1295,7 @@ dropAround p = dropWhile p . dropWhileEnd p
13111295
-- > dropWhile isSpace
13121296
stripStart :: Text -> Text
13131297
stripStart = dropWhile isSpace
1314-
{-# INLINE [1] stripStart #-}
1298+
{-# INLINE stripStart #-}
13151299

13161300
-- | /O(n)/ Remove trailing white space from a string. Equivalent to:
13171301
--
@@ -1482,7 +1466,7 @@ chunksOf k = go
14821466

14831467
-- | /O(n)/ The 'find' function takes a predicate and a 'Text', and
14841468
-- returns the first element matching the predicate, or 'Nothing' if
1485-
-- there is no such element.
1469+
-- there is no such element. Subject to fusion.
14861470
find :: (Char -> Bool) -> Text -> Maybe Char
14871471
find p t = S.findBy p (stream t)
14881472
{-# INLINE find #-}
@@ -1598,7 +1582,7 @@ breakOnAll pat src@(Text arr off slen)
15981582
-- searching for the index of @\"::\"@ and taking the substrings
15991583
-- before and after that index, you would instead use @breakOnAll \"::\"@.
16001584

1601-
-- | /O(n)/ 'Text' index (subscript) operator, starting from 0.
1585+
-- | /O(n)/ 'Text' index (subscript) operator, starting from 0. Subject to fusion.
16021586
index :: Text -> Int -> Char
16031587
index t n = S.index (stream t) n
16041588
{-# INLINE index #-}

Data/Text/Lazy.hs

Lines changed: 12 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -793,7 +793,7 @@ replace s d = intercalate d . splitOn s
793793
-- itself.
794794
toCaseFold :: Text -> Text
795795
toCaseFold t = unstream (S.toCaseFold (stream t))
796-
{-# INLINE [0] toCaseFold #-}
796+
{-# INLINE toCaseFold #-}
797797

798798
-- | /O(n)/ Convert a string to lower case, using simple case
799799
-- conversion. Subject to fusion.
@@ -936,8 +936,7 @@ scanl f z t = unstream (S.scanl g z (stream t))
936936
{-# INLINE scanl #-}
937937

938938
-- | /O(n)/ 'scanl1' is a variant of 'scanl' that has no starting
939-
-- value argument. Subject to fusion. Performs replacement on
940-
-- invalid scalar values.
939+
-- value argument. Performs replacement on invalid scalar values.
941940
--
942941
-- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
943942
scanl1 :: (Char -> Char -> Char) -> Text -> Text
@@ -1034,15 +1033,18 @@ replicateChar n c = unstream (S.replicateCharI n (safe c))
10341033
{-# RULES
10351034
"LAZY TEXT replicate/singleton -> replicateChar" [~1] forall n c.
10361035
replicate n (singleton c) = replicateChar n c
1036+
"LAZY TEXT replicate/unstream/singleton -> replicateChar" [~1] forall n c.
1037+
replicate n (unstream (S.singleton c)) = replicateChar n c
10371038
#-}
10381039

10391040
-- | /O(n)/, where @n@ is the length of the result. The 'unfoldr'
10401041
-- function is analogous to the List 'L.unfoldr'. 'unfoldr' builds a
10411042
-- 'Text' from a seed value. The function takes the element and
10421043
-- returns 'Nothing' if it is done producing the 'Text', otherwise
10431044
-- 'Just' @(a,b)@. In this case, @a@ is the next 'Char' in the
1044-
-- string, and @b@ is the seed value for further production. Performs
1045-
-- replacement on invalid scalar values.
1045+
-- string, and @b@ is the seed value for further production.
1046+
-- Subject to fusion.
1047+
-- Performs replacement on invalid scalar values.
10461048
unfoldr :: (a -> Maybe (Char,a)) -> a -> Text
10471049
unfoldr f s = unstream (S.unfoldr (firstf safe . f) s)
10481050
{-# INLINE unfoldr #-}
@@ -1052,6 +1054,7 @@ unfoldr f s = unstream (S.unfoldr (firstf safe . f) s)
10521054
-- first argument to 'unfoldrN'. This function is more efficient than
10531055
-- 'unfoldr' when the maximum length of the result is known and
10541056
-- correct, otherwise its performance is similar to 'unfoldr'.
1057+
-- Subject to fusion.
10551058
-- Performs replacement on invalid scalar values.
10561059
unfoldrN :: Int64 -> (a -> Maybe (Char,a)) -> a -> Text
10571060
unfoldrN n f s = unstream (S.unfoldrN n (firstf safe . f) s)
@@ -1228,7 +1231,7 @@ dropWhileEnd p = go
12281231

12291232
-- | /O(n)/ 'dropAround' @p@ @t@ returns the substring remaining after
12301233
-- dropping characters that satisfy the predicate @p@ from both the
1231-
-- beginning and end of @t@. Subject to fusion.
1234+
-- beginning and end of @t@.
12321235
dropAround :: (Char -> Bool) -> Text -> Text
12331236
dropAround p = dropWhile p . dropWhileEnd p
12341237
{-# INLINE [1] dropAround #-}
@@ -1238,7 +1241,7 @@ dropAround p = dropWhile p . dropWhileEnd p
12381241
-- > dropWhile isSpace
12391242
stripStart :: Text -> Text
12401243
stripStart = dropWhile isSpace
1241-
{-# INLINE [1] stripStart #-}
1244+
{-# INLINE stripStart #-}
12421245

12431246
-- | /O(n)/ Remove trailing white space from a string. Equivalent to:
12441247
--
@@ -1656,7 +1659,7 @@ filter p t = unstream (S.filter p (stream t))
16561659

16571660
-- | /O(n)/ The 'find' function takes a predicate and a 'Text', and
16581661
-- returns the first element in matching the predicate, or 'Nothing'
1659-
-- if there is no such element.
1662+
-- if there is no such element. Subject to fusion.
16601663
find :: (Char -> Bool) -> Text -> Maybe Char
16611664
find p t = S.findBy p (stream t)
16621665
{-# INLINE find #-}
@@ -1671,6 +1674,7 @@ partition p t = (filter p t, filter (not . p) t)
16711674
{-# INLINE partition #-}
16721675

16731676
-- | /O(n)/ 'Text' index (subscript) operator, starting from 0.
1677+
-- Subject to fusion.
16741678
index :: Text -> Int64 -> Char
16751679
index t n = S.index (stream t) n
16761680
{-# INLINE index #-}

Data/Text/Show.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -42,8 +42,7 @@ unpack :: Text -> String
4242
unpack = S.unstreamList . stream
4343
{-# INLINE [1] unpack #-}
4444

45-
-- | /O(n)/ Convert a literal string into a 'Text'. Subject to
46-
-- fusion.
45+
-- | /O(n)/ Convert a literal string into a 'Text'.
4746
--
4847
-- This is exposed solely for people writing GHC rewrite rules.
4948
--

0 commit comments

Comments
 (0)