Skip to content

Commit

Permalink
Tweak documentation (#523)
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed Jul 2, 2022
1 parent 4e62154 commit 2b9416d
Show file tree
Hide file tree
Showing 3 changed files with 39 additions and 23 deletions.
14 changes: 12 additions & 2 deletions Data/ByteString.hs
Original file line number Diff line number Diff line change
Expand Up @@ -389,6 +389,8 @@ snoc (BS x l) c = unsafeCreate (l+1) $ \p -> unsafeWithForeignPtr x $ \f -> do

-- | /O(1)/ Extract the first element of a ByteString, which must be non-empty.
-- An exception will be thrown in the case of an empty ByteString.
--
-- This is a partial function, consider using 'uncons' instead.
head :: HasCallStack => ByteString -> Word8
head (BS x l)
| l <= 0 = errorEmptyList "head"
Expand All @@ -397,13 +399,15 @@ head (BS x l)

-- | /O(1)/ Extract the elements after the head of a ByteString, which must be non-empty.
-- An exception will be thrown in the case of an empty ByteString.
--
-- This is a partial function, consider using 'uncons' instead.
tail :: HasCallStack => ByteString -> ByteString
tail (BS p l)
| l <= 0 = errorEmptyList "tail"
| otherwise = BS (plusForeignPtr p 1) (l-1)
{-# INLINE tail #-}

-- | /O(1)/ Extract the head and tail of a ByteString, returning Nothing
-- | /O(1)/ Extract the 'head' and 'tail' of a ByteString, returning 'Nothing'
-- if it is empty.
uncons :: ByteString -> Maybe (Word8, ByteString)
uncons (BS x l)
Expand All @@ -415,6 +419,8 @@ uncons (BS x l)

-- | /O(1)/ Extract the last element of a ByteString, which must be finite and non-empty.
-- An exception will be thrown in the case of an empty ByteString.
--
-- This is a partial function, consider using 'unsnoc' instead.
last :: HasCallStack => ByteString -> Word8
last ps@(BS x l)
| null ps = errorEmptyList "last"
Expand All @@ -424,13 +430,15 @@ last ps@(BS x l)

-- | /O(1)/ Return all the elements of a 'ByteString' except the last one.
-- An exception will be thrown in the case of an empty ByteString.
--
-- This is a partial function, consider using 'unsnoc' instead.
init :: HasCallStack => ByteString -> ByteString
init ps@(BS p l)
| null ps = errorEmptyList "init"
| otherwise = BS p (l-1)
{-# INLINE init #-}

-- | /O(1)/ Extract the 'init' and 'last' of a ByteString, returning Nothing
-- | /O(1)/ Extract the 'init' and 'last' of a ByteString, returning 'Nothing'
-- if it is empty.
unsnoc :: ByteString -> Maybe (ByteString, Word8)
unsnoc (BS x l)
Expand Down Expand Up @@ -1227,6 +1235,8 @@ intercalate (BS fSepPtr sepLen) (BS fhPtr hLen : t) =
-- Indexing ByteStrings

-- | /O(1)/ 'ByteString' index (subscript) operator, starting from 0.
--
-- This is a partial function, consider using 'indexMaybe' instead.
index :: HasCallStack => ByteString -> Int -> Word8
index ps n
| n < 0 = moduleError "index" ("negative index: " ++ show n)
Expand Down
14 changes: 12 additions & 2 deletions Data/ByteString/Lazy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -342,12 +342,14 @@ snoc cs w = foldrChunks Chunk (singleton w) cs
{-# INLINE snoc #-}

-- | /O(1)/ Extract the first element of a ByteString, which must be non-empty.
--
-- This is a partial function, consider using 'uncons' instead.
head :: HasCallStack => ByteString -> Word8
head Empty = errorEmptyList "head"
head (Chunk c _) = S.unsafeHead c
{-# INLINE head #-}

-- | /O(1)/ Extract the head and tail of a ByteString, returning Nothing
-- | /O(1)/ Extract the 'head' and 'tail' of a ByteString, returning 'Nothing'
-- if it is empty.
uncons :: ByteString -> Maybe (Word8, ByteString)
uncons Empty = Nothing
Expand All @@ -358,6 +360,8 @@ uncons (Chunk c cs)

-- | /O(1)/ Extract the elements after the head of a ByteString, which must be
-- non-empty.
--
-- This is a partial function, consider using 'uncons' instead.
tail :: HasCallStack => ByteString -> ByteString
tail Empty = errorEmptyList "tail"
tail (Chunk c cs)
Expand All @@ -367,6 +371,8 @@ tail (Chunk c cs)

-- | /O(n\/c)/ Extract the last element of a ByteString, which must be finite
-- and non-empty.
--
-- This is a partial function, consider using 'unsnoc' instead.
last :: HasCallStack => ByteString -> Word8
last Empty = errorEmptyList "last"
last (Chunk c0 cs0) = go c0 cs0
Expand All @@ -375,14 +381,16 @@ last (Chunk c0 cs0) = go c0 cs0
-- XXX Don't inline this. Something breaks with 6.8.2 (haven't investigated yet)

-- | /O(n\/c)/ Return all the elements of a 'ByteString' except the last one.
--
-- This is a partial function, consider using 'unsnoc' instead.
init :: HasCallStack => ByteString -> ByteString
init Empty = errorEmptyList "init"
init (Chunk c0 cs0) = go c0 cs0
where go c Empty | S.length c == 1 = Empty
| otherwise = Chunk (S.unsafeInit c) Empty
go c (Chunk c' cs) = Chunk c (go c' cs)

-- | /O(n\/c)/ Extract the 'init' and 'last' of a ByteString, returning Nothing
-- | /O(n\/c)/ Extract the 'init' and 'last' of a ByteString, returning 'Nothing'
-- if it is empty.
--
-- * It is no faster than using 'init' and 'last'
Expand Down Expand Up @@ -1123,6 +1131,8 @@ intercalate s = concat . List.intersperse s
-- Indexing ByteStrings

-- | /O(c)/ 'ByteString' index (subscript) operator, starting from 0.
--
-- This is a partial function, consider using 'indexMaybe' instead.
index :: HasCallStack => ByteString -> Int64 -> Word8
index _ i | i < 0 = moduleError "index" ("negative index: " ++ show i)
index cs0 i = index' cs0 i
Expand Down
34 changes: 15 additions & 19 deletions Data/ByteString/Short/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ module Data.ByteString.Short.Internal (
any,
concat,

-- ** Generating and unfolding ByteStrings
-- ** Generating and unfolding ShortByteStrings
replicate,
unfoldr,
unfoldrN,
Expand Down Expand Up @@ -280,12 +280,6 @@ import qualified Language.Haskell.TH.Syntax as TH
-- 'ByteString' (at the cost of copying the string data). It supports very few
-- other operations.
--
-- It is suitable for use as an internal representation for code that needs
-- to keep many short strings in memory, but it /should not/ be used as an
-- interchange type. That is, it should not generally be used in public APIs.
-- The 'ByteString' type is usually more suitable for use in interfaces; it is
-- more flexible and it supports a wide range of operations.
--
data ShortByteString = SBS ByteArray#
deriving Typeable

Expand Down Expand Up @@ -373,6 +367,8 @@ null :: ShortByteString -> Bool
null sbs = length sbs == 0

-- | /O(1)/ 'ShortByteString' index (subscript) operator, starting from 0.
--
-- This is a partial function, consider using 'indexMaybe' instead.
index :: HasCallStack => ShortByteString -> Int -> Word8
index sbs i
| i >= 0 && i < length sbs = unsafeIndex sbs i
Expand Down Expand Up @@ -734,7 +730,7 @@ tail = \sbs ->
True -> errorEmptySBS "tail"
False -> create nl $ \mba -> copyByteArray (asBA sbs) 1 mba 0 nl

-- | /O(n)/ Extract the head and tail of a ByteString, returning Nothing
-- | /O(n)/ Extract the 'head' and 'tail' of a ShortByteString, returning 'Nothing'
-- if it is empty.
--
-- @since 0.11.3.0
Expand Down Expand Up @@ -774,7 +770,7 @@ init = \sbs ->
True -> errorEmptySBS "init"
False -> create nl $ \mba -> copyByteArray (asBA sbs) 0 mba 0 nl

-- | /O(n)/ Extract the 'init' and 'last' of a ByteString, returning Nothing
-- | /O(n)/ Extract the 'init' and 'last' of a ShortByteString, returning 'Nothing'
-- if it is empty.
--
-- @since 0.11.3.0
Expand Down Expand Up @@ -892,7 +888,7 @@ intercalate sep = \case


-- ---------------------------------------------------------------------
-- Reducing 'ByteString's
-- Reducing 'ShortByteString's

-- | 'foldl', applied to a binary operator, a starting value (typically
-- the left-identity of the operator), and a ShortByteString, reduces the
Expand Down Expand Up @@ -971,8 +967,8 @@ all k = \sbs ->
in go 0


-- | /O(n)/ Applied to a predicate and a ByteString, 'any' determines if
-- any element of the 'ByteString' satisfies the predicate.
-- | /O(n)/ Applied to a predicate and a 'ShortByteString', 'any' determines if
-- any element of the 'ShortByteString' satisfies the predicate.
--
-- @since 0.11.3.0
any :: (Word8 -> Bool) -> ShortByteString -> Bool
Expand Down Expand Up @@ -1235,7 +1231,7 @@ stripPrefix sbs1 = \sbs2 -> do
-- Unfolds and replicates


-- | /O(n)/ 'replicate' @n x@ is a ByteString of length @n@ with @x@
-- | /O(n)/ 'replicate' @n x@ is a ShortByteString of length @n@ with @x@
-- the value of every element. The following holds:
--
-- > replicate w c = unfoldr w (\u -> Just (u,u)) c
Expand Down Expand Up @@ -1430,8 +1426,8 @@ breakSubstring pat =
elem :: Word8 -> ShortByteString -> Bool
elem c = \sbs -> case elemIndex c sbs of Nothing -> False ; _ -> True

-- | /O(n)/ 'filter', applied to a predicate and a ByteString,
-- returns a ByteString containing those characters that satisfy the
-- | /O(n)/ 'filter', applied to a predicate and a ShortByteString,
-- returns a ShortByteString containing those characters that satisfy the
-- predicate.
--
-- @since 0.11.3.0
Expand Down Expand Up @@ -1460,7 +1456,7 @@ filter k = \sbs -> let l = length sbs
else
go' (br+1) bw

-- | /O(n)/ The 'find' function takes a predicate and a ByteString,
-- | /O(n)/ The 'find' function takes a predicate and a ShortByteString,
-- and returns the first element in matching the predicate, or 'Nothing'
-- if there is no such element.
--
Expand All @@ -1472,8 +1468,8 @@ find f = \sbs -> case findIndex f sbs of
Just n -> Just (sbs `index` n)
_ -> Nothing

-- | /O(n)/ The 'partition' function takes a predicate a ByteString and returns
-- the pair of ByteStrings with elements which do and do not satisfy the
-- | /O(n)/ The 'partition' function takes a predicate a ShortByteString and returns
-- the pair of ShortByteStrings with elements which do and do not satisfy the
-- predicate, respectively; i.e.,
--
-- > partition p bs == (filter p sbs, filter (not . p) sbs)
Expand Down Expand Up @@ -1539,7 +1535,7 @@ count w = \sbs@(SBS ba#) -> accursedUnutterablePerformIO $
fromIntegral <$> c_count ba# (fromIntegral $ length sbs) w

-- | /O(n)/ The 'findIndex' function takes a predicate and a 'ShortByteString' and
-- returns the index of the first element in the ByteString
-- returns the index of the first element in the ShortByteString
-- satisfying the predicate.
--
-- @since 0.11.3.0
Expand Down

0 comments on commit 2b9416d

Please sign in to comment.