@@ -423,19 +423,19 @@ head (BS x l)
423423-- 
424424--  This is a partial function, consider using 'uncons' instead. 
425425tail  ::  HasCallStack  =>  ByteString  ->  ByteString 
426- tail  ( BS  p l) 
427-     |  l  <=  0      =  errorEmptyList " tail" 
428-     |  otherwise  =  BS  (plusForeignPtr p  1 ) (l - 1 ) 
426+ tail  ps 
427+     |  length  ps  <=  0  =  errorEmptyList " tail" 
428+     |  otherwise  =  unsafeDrop  1  ps 
429429{-# INLINE  tail #-}
430430
431431--  |  /O(1)/ Extract the 'head' and 'tail' of a ByteString, returning 'Nothing' 
432432--  if it is empty. 
433433uncons  ::  ByteString  ->  Maybe   (Word8 , ByteString )
434- uncons (BS  x l)
434+ uncons ps @ (BS  x l)
435435    |  l <=  0     =  Nothing 
436436    |  otherwise  =  Just  (accursedUnutterablePerformIO $  unsafeWithForeignPtr x
437437                                                     $  \ p ->  peek p,
438-                         BS  (plusForeignPtr x  1 ) (l - 1 ) )
438+                         unsafeDrop  1  ps )
439439{-# INLINE  uncons #-}
440440
441441--  |  /O(1)/ Extract the last element of a ByteString, which must be finite and non-empty. 
@@ -454,17 +454,17 @@ last ps@(BS x l)
454454-- 
455455--  This is a partial function, consider using 'unsnoc' instead. 
456456init  ::  HasCallStack  =>  ByteString  ->  ByteString 
457- init  ps@ ( BS  p l) 
457+ init  ps
458458    |  null  ps   =  errorEmptyList " init" 
459-     |  otherwise  =  BS  p (l - 1 ) 
459+     |  otherwise  =  unsafeDropEnd  1  ps 
460460{-# INLINE  init #-}
461461
462462--  |  /O(1)/ Extract the 'init' and 'last' of a ByteString, returning 'Nothing' 
463463--  if it is empty. 
464464unsnoc  ::  ByteString  ->  Maybe   (ByteString , Word8 )
465- unsnoc (BS  x l)
465+ unsnoc ps @ (BS  x l)
466466    |  l <=  0     =  Nothing 
467-     |  otherwise  =  Just  (BS  x (l - 1 ) ,
467+     |  otherwise  =  Just  (unsafeDropEnd  1  ps ,
468468                        accursedUnutterablePerformIO $ 
469469                          unsafeWithForeignPtr x $  \ p ->  peekByteOff p (l- 1 ))
470470{-# INLINE  unsnoc #-}
@@ -921,10 +921,10 @@ unfoldrN i f x0
921921--  |  /O(1)/ 'take' @n@, applied to a ByteString @xs@, returns the prefix 
922922--  of @xs@ of length @n@, or @xs@ itself if @n > 'length' xs@. 
923923take  ::  Int   ->  ByteString  ->  ByteString 
924- take  n ps@ (BS  x  l)
924+ take  n ps@ (BS  _  l)
925925    |  n <=  0     =  empty
926926    |  n >=  l    =  ps
927-     |  otherwise  =  BS  x n 
927+     |  otherwise  =  unsafeTake n ps 
928928{-# INLINE  take #-}
929929
930930--  |  /O(1)/ @'takeEnd' n xs@ is equivalent to @'drop' ('length' xs - n) xs@. 
@@ -939,19 +939,19 @@ take n ps@(BS x l)
939939-- 
940940--  @since 0.11.1.0 
941941takeEnd  ::  Int   ->  ByteString  ->  ByteString 
942- takeEnd n ps@ (BS  x  len)
942+ takeEnd n ps@ (BS  _  len)
943943  |  n >=  len  =  ps
944944  |  n <=  0     =  empty
945-   |  otherwise  =  BS  (plusForeignPtr x (len  -  n)) n 
945+   |  otherwise  =  unsafeTakeEnd n ps 
946946{-# INLINE  takeEnd #-}
947947
948948--  |  /O(1)/ 'drop' @n xs@ returns the suffix of @xs@ after the first @n@ 
949949--  elements, or 'empty' if @n > 'length' xs@. 
950950drop   ::  Int   ->  ByteString  ->  ByteString 
951- drop  n ps@ (BS  x  l)
951+ drop  n ps@ (BS  _  l)
952952    |  n <=  0     =  ps
953953    |  n >=  l    =  empty
954-     |  otherwise  =  BS  (plusForeignPtr x n) (l - n) 
954+     |  otherwise  =  unsafeDrop n ps 
955955{-# INLINE  drop #-}
956956
957957--  |  /O(1)/ @'dropEnd' n xs@ is equivalent to @'take' ('length' xs - n) xs@. 
@@ -966,18 +966,18 @@ drop n ps@(BS x l)
966966-- 
967967--  @since 0.11.1.0 
968968dropEnd  ::  Int   ->  ByteString  ->  ByteString 
969- dropEnd n ps@ (BS  x  len)
969+ dropEnd n ps@ (BS  _  len)
970970    |  n <=  0     =  ps
971971    |  n >=  len  =  empty
972-     |  otherwise  =  BS  x (len  -  n) 
972+     |  otherwise  =  unsafeDropEnd n ps 
973973{-# INLINE  dropEnd #-}
974974
975975--  |  /O(1)/ 'splitAt' @n xs@ is equivalent to @('take' n xs, 'drop' n xs)@. 
976976splitAt  ::  Int   ->  ByteString  ->  (ByteString , ByteString )
977- splitAt  n ps@ (BS  x  l)
977+ splitAt  n ps@ (BS  _  l)
978978    |  n <=  0     =  (empty, ps)
979979    |  n >=  l    =  (ps, empty)
980-     |  otherwise  =  (BS  x n,  BS  (plusForeignPtr x n) (l - n) )
980+     |  otherwise  =  (unsafeTake n ps, unsafeDrop n ps )
981981{-# INLINE  splitAt #-}
982982
983983--  |  Similar to 'Prelude.takeWhile', 
@@ -1151,18 +1151,17 @@ splitWith _ (BS _  0) = []
11511151splitWith predicate (BS  fp len) =  splitWith0 0  len fp
11521152  where  splitWith0 ! off' ! len' ! fp' = 
11531153          accursedUnutterablePerformIO $ 
1154-               splitLoop fp  0  off' len' fp'
1154+               splitLoop 0  off' len' fp'
11551155
1156-         splitLoop  ::  ForeignPtr  Word8 
1157-                   ->  Int   ->  Int   ->  Int 
1156+         splitLoop  ::  Int   ->  Int   ->  Int 
11581157                  ->  ForeignPtr  Word8 
11591158                  ->  IO   [ByteString ]
1160-         splitLoop p  idx2 off' len' fp' =  go idx2
1159+         splitLoop idx2 off' len' fp' =  go idx2
11611160          where 
11621161            go idx'
11631162                |  idx' >=  len'  =  return  [BS  (plusForeignPtr fp' off') idx']
11641163                |  otherwise  =  do 
1165-                     w <-  peekFpByteOff p  (off'+ idx')
1164+                     w <-  peekFpByteOff fp  (off'+ idx')
11661165                    if  predicate w
11671166                       then  return  (BS  (plusForeignPtr fp' off') idx' : 
11681167                                  splitWith0 (off'+ idx'+ 1 ) (len'- idx'- 1 ) fp')
@@ -1188,19 +1187,22 @@ splitWith predicate (BS fp len) = splitWith0 0 len fp
11881187-- 
11891188split  ::  Word8  ->  ByteString  ->  [ByteString ]
11901189split _ (BS  _ 0 ) =  [] 
1191- split w (BS  x l) =  loop 0 
1190+ split w ps @ (BS  x l) =  loop 0 
11921191    where 
11931192        loop ! n = 
11941193            let  q =  accursedUnutterablePerformIO $  unsafeWithForeignPtr x $  \ p -> 
11951194                      memchr (p `plusPtr`  n)
11961195                             w (fromIntegral  (l- n))
11971196            in  if  q ==  nullPtr
1198-                 then  [BS  (plusForeignPtr x n) (l - n) ]
1197+                 then  [unsafeDrop n ps ]
11991198                else  let  i =  q `minusPtr`  unsafeForeignPtrToPtr x
1200-                       in  BS  (plusForeignPtr x n) (i - n)  :  loop (i+ 1 )
1199+                       in  unsafeSlice n i ps  :  loop (i+ 1 )
12011200
12021201{-# INLINE  split #-}
12031202
1203+ unsafeSlice   ::  Int   ->  Int   ->  ByteString  ->  ByteString 
1204+ unsafeSlice a b (BS  x _) =  BS  (plusForeignPtr x a) (b -  a)
1205+ {-# INLINE  unsafeSlice #-}
12041206
12051207--  |  The 'group' function takes a ByteString and returns a list of 
12061208--  ByteStrings such that the concatenation of the result is equal to the 
@@ -1716,7 +1718,7 @@ inits bs = NE.toList $! initsNE bs
17161718--  @since 0.11.4.0 
17171719initsNE  ::  ByteString  ->  NonEmpty  ByteString 
17181720--  see Note [Avoid NonEmpty combinators]
1719- initsNE ( BS  x len)  =  empty :|  [BS  x n  |  n <-  [1 .. len ]]
1721+ initsNE ps  =  empty :|  [unsafeTake n ps  |  n <-  [1 .. length  ps ]]
17201722
17211723--  |  /O(n)/ Returns all final segments of the given 'ByteString', longest first. 
17221724tails  ::  ByteString  ->  [ByteString ]
0 commit comments