55{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
66{-# LANGUAGE Unsafe #-}
77{-# LANGUAGE TemplateHaskellQuotes #-}
8+ {-# LANGUAGE PatternSynonyms #-}
9+ {-# LANGUAGE GeneralizedNewtypeDeriving #-}
10+ #if MIN_VERSION_base(4,10,0)
11+ {-# LANGUAGE DerivingStrategies #-}
12+ #endif
13+
814{-# OPTIONS_HADDOCK not-home #-}
915
16+ #define BYTEARRAY_IN_BASE MIN_VERSION_base(4,17,0)
17+
1018-- |
1119-- Module : Data.ByteString.Short.Internal
1220-- Copyright : (c) Duncan Coutts 2012-2013
@@ -22,6 +30,9 @@ module Data.ByteString.Short.Internal (
2230
2331 -- * The @ShortByteString@ type and representation
2432 ShortByteString (.. ),
33+ #if BYTEARRAY_IN_BASE
34+ pattern SBS ,
35+ #endif
2536
2637 -- * Conversions
2738 toShort ,
@@ -45,15 +56,21 @@ module Data.ByteString.Short.Internal (
4556 useAsCStringLen
4657 ) where
4758
59+ #if BYTEARRAY_IN_BASE
60+ import Data.ByteArray
61+ #else
62+ import Data.Typeable (Typeable )
63+ import Data.Semigroup (Semigroup ((<>) ))
64+ import Control.DeepSeq (NFData (.. ))
65+ #endif
66+
4867import Data.ByteString.Internal (ByteString (.. ), accursedUnutterablePerformIO )
4968import qualified Data.ByteString.Internal as BS
5069
51- import Data.Typeable (Typeable )
5270import Data.Data (Data (.. ), mkNoRepType )
53- import Data.Semigroup (Semigroup ((<>) ))
5471import Data.Monoid (Monoid (.. ))
72+ import Data.Semigroup (Semigroup )
5573import Data.String (IsString (.. ))
56- import Control.DeepSeq (NFData (.. ))
5774import qualified Data.List as List (length )
5875import Foreign.C.String (CString , CStringLen )
5976import Foreign.C.Types (CSize (.. ), CInt (.. ))
@@ -107,8 +124,17 @@ import qualified Language.Haskell.TH.Syntax as TH
107124-- The 'ByteString' type is usually more suitable for use in interfaces; it is
108125-- more flexible and it supports a wide range of operations.
109126--
127+ #if BYTEARRAY_IN_BASE
128+ newtype ShortByteString = ShortByteString { unShortByteString :: ByteArray }
129+ deriving newtype (Eq , Semigroup , Monoid )
130+
131+ pattern SBS :: ByteArray # -> ShortByteString
132+ pattern SBS x = ShortByteString (ByteArray x)
133+ {-# COMPLETE SBS #-}
134+ #else
110135data ShortByteString = SBS ByteArray #
111136 deriving Typeable
137+ #endif
112138
113139-- | @since 0.11.2.0
114140instance TH. Lift ShortByteString where
@@ -137,13 +163,16 @@ instance TH.Lift ShortByteString where
137163-- the 0--3 trailing bytes undefined. This means we can use word-sized writes,
138164-- but we have to be careful with reads, see equateBytes and compareBytes below.
139165
140-
166+ #if !BYTEARRAY_IN_BASE
141167instance Eq ShortByteString where
142168 (==) = equateBytes
169+ #endif
143170
171+ -- | Lexicographic order.
144172instance Ord ShortByteString where
145173 compare = compareBytes
146174
175+ #if !BYTEARRAY_IN_BASE
147176instance Semigroup ShortByteString where
148177 (<>) = append
149178
@@ -154,6 +183,7 @@ instance Monoid ShortByteString where
154183
155184instance NFData ShortByteString where
156185 rnf SBS {} = ()
186+ #endif
157187
158188instance Show ShortByteString where
159189 showsPrec p ps r = showsPrec p (unpackChars ps) r
@@ -164,8 +194,13 @@ instance Read ShortByteString where
164194-- | @since 0.10.12.0
165195instance GHC.Exts. IsList ShortByteString where
166196 type Item ShortByteString = Word8
197+ #if BYTEARRAY_IN_BASE
198+ fromList = ShortByteString . GHC.Exts. fromList
199+ toList = GHC.Exts. toList . unShortByteString
200+ #else
167201 fromList = packBytes
168202 toList = unpackBytes
203+ #endif
169204
170205-- | Beware: 'fromString' truncates multi-byte characters to octets.
171206-- e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�
@@ -392,13 +427,15 @@ unpackAppendBytesStrict !sbs off len = go (off-1) (off-1 + len)
392427------------------------------------------------------------------------
393428-- Eq and Ord implementations
394429
430+ #if !BYTEARRAY_IN_BASE
395431equateBytes :: ShortByteString -> ShortByteString -> Bool
396432equateBytes sbs1 sbs2 =
397433 let ! len1 = length sbs1
398434 ! len2 = length sbs2
399435 in len1 == len2
400436 && 0 == accursedUnutterablePerformIO
401437 (memcmp_ByteArray (asBA sbs1) (asBA sbs2) len1)
438+ #endif
402439
403440compareBytes :: ShortByteString -> ShortByteString -> Ordering
404441compareBytes sbs1 sbs2 =
@@ -413,10 +450,10 @@ compareBytes sbs1 sbs2 =
413450 | len2 < len1 -> GT
414451 | otherwise -> EQ
415452
416-
417453------------------------------------------------------------------------
418454-- Appending and concatenation
419455
456+ #if !BYTEARRAY_IN_BASE
420457append :: ShortByteString -> ShortByteString -> ShortByteString
421458append src1 src2 =
422459 let ! len1 = length src1
@@ -438,7 +475,7 @@ concat sbss =
438475 let ! len = length src
439476 copyByteArray (asBA src) 0 dst off len
440477 copy dst (off + len) sbss
441-
478+ #endif
442479
443480------------------------------------------------------------------------
444481-- Exported low level operations
0 commit comments