diff --git a/Data/Text.hs b/Data/Text.hs index 039cc487ea6bf8403453f36be92a1150b42f3dd4..b9182a77cc5de4ee5e1cac3e7f89b786cd448af8 100644 --- a/Data/Text.hs +++ b/Data/Text.hs @@ -605,7 +605,7 @@ isSingleton = S.isSingleton . stream -- Subject to fusion. length :: Text -> Int length t = S.length (stream t) -{-# INLINE [0] length #-} +{-# INLINE [1] length #-} -- length needs to be phased after the compareN/length rules otherwise -- it may inline before the rules have an opportunity to fire. @@ -702,7 +702,7 @@ intersperse c t = unstream (S.intersperse (safe c) (stream t)) -- >>> T.reverse "desrever" -- "reversed" -- --- Subject to fusion. +-- Subject to fusion (fuses with its argument). reverse :: Text -> Text reverse t = S.reverse (stream t) {-# INLINE reverse #-} @@ -1033,8 +1033,7 @@ scanl f z t = unstream (S.scanl g z (stream t)) {-# INLINE scanl #-} -- | /O(n)/ 'scanl1' is a variant of 'scanl' that has no starting --- value argument. Subject to fusion. Performs replacement on --- invalid scalar values. +-- value argument. Performs replacement on invalid scalar values. -- -- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...] scanl1 :: (Char -> Char -> Char) -> Text -> Text @@ -1052,8 +1051,7 @@ scanr f z = S.reverse . S.reverseScanr g z . reverseStream {-# INLINE scanr #-} -- | /O(n)/ 'scanr1' is a variant of 'scanr' that has no starting --- value argument. Subject to fusion. Performs replacement on --- invalid scalar values. +-- value argument. Performs replacement on invalid scalar values. scanr1 :: (Char -> Char -> Char) -> Text -> Text scanr1 f t | null t = empty | otherwise = scanr f (last t) (init t) @@ -1237,7 +1235,7 @@ takeWhile p t@(Text arr off len) = loop 0 -- | /O(n)/ 'takeWhileEnd', applied to a predicate @p@ and a 'Text', -- returns the longest suffix (possibly empty) of elements that --- satisfy @p@. Subject to fusion. +-- satisfy @p@. -- Examples: -- -- >>> takeWhileEnd (=='o') "foo" @@ -1252,13 +1250,6 @@ takeWhileEnd p t@(Text arr off len) = loop (len-1) len where (c,d) = reverseIter t i {-# INLINE [1] takeWhileEnd #-} -{-# RULES -"TEXT takeWhileEnd -> fused" [~1] forall p t. - takeWhileEnd p t = S.reverse (S.takeWhile p (S.reverseStream t)) -"TEXT takeWhileEnd -> unfused" [1] forall p t. - S.reverse (S.takeWhile p (S.reverseStream t)) = takeWhileEnd p t - #-} - -- | /O(n)/ 'dropWhile' @p@ @t@ returns the suffix remaining after -- 'takeWhile' @p@ @t@. Subject to fusion. dropWhile :: (Char -> Bool) -> Text -> Text @@ -1278,7 +1269,7 @@ dropWhile p t@(Text arr off len) = loop 0 0 -- | /O(n)/ 'dropWhileEnd' @p@ @t@ returns the prefix remaining after -- dropping characters that satisfy the predicate @p@ from the end of --- @t@. Subject to fusion. +-- @t@. -- -- Examples: -- @@ -1292,13 +1283,6 @@ dropWhileEnd p t@(Text arr off len) = loop (len-1) len where (c,d) = reverseIter t i {-# INLINE [1] dropWhileEnd #-} -{-# RULES -"TEXT dropWhileEnd -> fused" [~1] forall p t. - dropWhileEnd p t = S.reverse (S.dropWhile p (S.reverseStream t)) -"TEXT dropWhileEnd -> unfused" [1] forall p t. - S.reverse (S.dropWhile p (S.reverseStream t)) = dropWhileEnd p t - #-} - -- | /O(n)/ 'dropAround' @p@ @t@ returns the substring remaining after -- dropping characters that satisfy the predicate @p@ from both the -- beginning and end of @t@. Subject to fusion. @@ -1311,7 +1295,7 @@ dropAround p = dropWhile p . dropWhileEnd p -- > dropWhile isSpace stripStart :: Text -> Text stripStart = dropWhile isSpace -{-# INLINE [1] stripStart #-} +{-# INLINE stripStart #-} -- | /O(n)/ Remove trailing white space from a string. Equivalent to: -- @@ -1482,7 +1466,7 @@ chunksOf k = go -- | /O(n)/ The 'find' function takes a predicate and a 'Text', and -- returns the first element matching the predicate, or 'Nothing' if --- there is no such element. +-- there is no such element. Subject to fusion. find :: (Char -> Bool) -> Text -> Maybe Char find p t = S.findBy p (stream t) {-# INLINE find #-} @@ -1598,7 +1582,7 @@ breakOnAll pat src@(Text arr off slen) -- searching for the index of @\"::\"@ and taking the substrings -- before and after that index, you would instead use @breakOnAll \"::\"@. --- | /O(n)/ 'Text' index (subscript) operator, starting from 0. +-- | /O(n)/ 'Text' index (subscript) operator, starting from 0. Subject to fusion. index :: Text -> Int -> Char index t n = S.index (stream t) n {-# INLINE index #-} diff --git a/Data/Text/Lazy.hs b/Data/Text/Lazy.hs index 63840af01f4bac5d7fb253ebc329d3de366bf553..8f36f1581b83ed3a6e7296b93b29b84ed3e3e912 100644 --- a/Data/Text/Lazy.hs +++ b/Data/Text/Lazy.hs @@ -793,7 +793,7 @@ replace s d = intercalate d . splitOn s -- itself. toCaseFold :: Text -> Text toCaseFold t = unstream (S.toCaseFold (stream t)) -{-# INLINE [0] toCaseFold #-} +{-# INLINE toCaseFold #-} -- | /O(n)/ Convert a string to lower case, using simple case -- conversion. Subject to fusion. @@ -936,8 +936,7 @@ scanl f z t = unstream (S.scanl g z (stream t)) {-# INLINE scanl #-} -- | /O(n)/ 'scanl1' is a variant of 'scanl' that has no starting --- value argument. Subject to fusion. Performs replacement on --- invalid scalar values. +-- value argument. Performs replacement on invalid scalar values. -- -- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...] scanl1 :: (Char -> Char -> Char) -> Text -> Text @@ -1034,6 +1033,8 @@ replicateChar n c = unstream (S.replicateCharI n (safe c)) {-# RULES "LAZY TEXT replicate/singleton -> replicateChar" [~1] forall n c. replicate n (singleton c) = replicateChar n c +"LAZY TEXT replicate/unstream/singleton -> replicateChar" [~1] forall n c. + replicate n (unstream (S.singleton c)) = replicateChar n c #-} -- | /O(n)/, where @n@ is the length of the result. The 'unfoldr' @@ -1041,8 +1042,9 @@ replicateChar n c = unstream (S.replicateCharI n (safe c)) -- 'Text' from a seed value. The function takes the element and -- returns 'Nothing' if it is done producing the 'Text', otherwise -- 'Just' @(a,b)@. In this case, @a@ is the next 'Char' in the --- string, and @b@ is the seed value for further production. Performs --- replacement on invalid scalar values. +-- string, and @b@ is the seed value for further production. +-- Subject to fusion. +-- Performs replacement on invalid scalar values. unfoldr :: (a -> Maybe (Char,a)) -> a -> Text unfoldr f s = unstream (S.unfoldr (firstf safe . f) s) {-# INLINE unfoldr #-} @@ -1052,6 +1054,7 @@ unfoldr f s = unstream (S.unfoldr (firstf safe . f) s) -- first argument to 'unfoldrN'. This function is more efficient than -- 'unfoldr' when the maximum length of the result is known and -- correct, otherwise its performance is similar to 'unfoldr'. +-- Subject to fusion. -- Performs replacement on invalid scalar values. unfoldrN :: Int64 -> (a -> Maybe (Char,a)) -> a -> Text unfoldrN n f s = unstream (S.unfoldrN n (firstf safe . f) s) @@ -1228,7 +1231,7 @@ dropWhileEnd p = go -- | /O(n)/ 'dropAround' @p@ @t@ returns the substring remaining after -- dropping characters that satisfy the predicate @p@ from both the --- beginning and end of @t@. Subject to fusion. +-- beginning and end of @t@. dropAround :: (Char -> Bool) -> Text -> Text dropAround p = dropWhile p . dropWhileEnd p {-# INLINE [1] dropAround #-} @@ -1238,7 +1241,7 @@ dropAround p = dropWhile p . dropWhileEnd p -- > dropWhile isSpace stripStart :: Text -> Text stripStart = dropWhile isSpace -{-# INLINE [1] stripStart #-} +{-# INLINE stripStart #-} -- | /O(n)/ Remove trailing white space from a string. Equivalent to: -- @@ -1656,7 +1659,7 @@ filter p t = unstream (S.filter p (stream t)) -- | /O(n)/ The 'find' function takes a predicate and a 'Text', and -- returns the first element in matching the predicate, or 'Nothing' --- if there is no such element. +-- if there is no such element. Subject to fusion. find :: (Char -> Bool) -> Text -> Maybe Char find p t = S.findBy p (stream t) {-# INLINE find #-} @@ -1671,6 +1674,7 @@ partition p t = (filter p t, filter (not . p) t) {-# INLINE partition #-} -- | /O(n)/ 'Text' index (subscript) operator, starting from 0. +-- Subject to fusion. index :: Text -> Int64 -> Char index t n = S.index (stream t) n {-# INLINE index #-} diff --git a/Data/Text/Show.hs b/Data/Text/Show.hs index 04d2a28b661f5587771cf26c25a69abe6f956365..2a003b5b4d9bd79adf20ef72ecd709dbf0f7767c 100644 --- a/Data/Text/Show.hs +++ b/Data/Text/Show.hs @@ -42,8 +42,7 @@ unpack :: Text -> String unpack = S.unstreamList . stream {-# INLINE [1] unpack #-} --- | /O(n)/ Convert a literal string into a 'Text'. Subject to --- fusion. +-- | /O(n)/ Convert a literal string into a 'Text'. -- -- This is exposed solely for people writing GHC rewrite rules. --