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 (__GLASGOW_HASKELL__ >= 903)
17+ -- At the moment of writing GHC source tree has not yet bumped `base` version,
18+ -- so using __GLASGOW_HASKELL__ as a proxy instead of MIN_VERSION_base(4,17,0).
19+
1020-- |
1121-- Module : Data.ByteString.Short.Internal
1222-- Copyright : (c) Duncan Coutts 2012-2013
@@ -22,6 +32,9 @@ module Data.ByteString.Short.Internal (
2232
2333 -- * The @ShortByteString@ type and representation
2434 ShortByteString (.. ),
35+ #if BYTEARRAY_IN_BASE
36+ pattern SBS ,
37+ #endif
2538
2639 -- * Conversions
2740 toShort ,
@@ -45,15 +58,21 @@ module Data.ByteString.Short.Internal (
4558 useAsCStringLen
4659 ) where
4760
61+ #if BYTEARRAY_IN_BASE
62+ import Data.Array.Byte
63+ import Data.Semigroup (Semigroup )
64+ #else
65+ import Data.Typeable (Typeable )
66+ import Data.Semigroup (Semigroup ((<>) ))
67+ import Control.DeepSeq (NFData (.. ))
68+ #endif
69+
4870import Data.ByteString.Internal (ByteString (.. ), accursedUnutterablePerformIO )
4971import qualified Data.ByteString.Internal as BS
5072
51- import Data.Typeable (Typeable )
5273import Data.Data (Data (.. ), mkNoRepType )
53- import Data.Semigroup (Semigroup ((<>) ))
5474import Data.Monoid (Monoid (.. ))
5575import Data.String (IsString (.. ))
56- import Control.DeepSeq (NFData (.. ))
5776import qualified Data.List as List (length )
5877import Foreign.C.String (CString , CStringLen )
5978import Foreign.C.Types (CSize (.. ), CInt (.. ))
@@ -107,8 +126,17 @@ import qualified Language.Haskell.TH.Syntax as TH
107126-- The 'ByteString' type is usually more suitable for use in interfaces; it is
108127-- more flexible and it supports a wide range of operations.
109128--
129+ #if BYTEARRAY_IN_BASE
130+ newtype ShortByteString = ShortByteString { unShortByteString :: ByteArray }
131+ deriving newtype (Eq , Semigroup , Monoid )
132+
133+ pattern SBS :: ByteArray # -> ShortByteString
134+ pattern SBS x = ShortByteString (ByteArray x)
135+ {-# COMPLETE SBS #-}
136+ #else
110137data ShortByteString = SBS ByteArray #
111138 deriving Typeable
139+ #endif
112140
113141-- | @since 0.11.2.0
114142instance TH. Lift ShortByteString where
@@ -137,13 +165,16 @@ instance TH.Lift ShortByteString where
137165-- the 0--3 trailing bytes undefined. This means we can use word-sized writes,
138166-- but we have to be careful with reads, see equateBytes and compareBytes below.
139167
140-
168+ #if !BYTEARRAY_IN_BASE
141169instance Eq ShortByteString where
142170 (==) = equateBytes
171+ #endif
143172
173+ -- | Lexicographic order.
144174instance Ord ShortByteString where
145175 compare = compareBytes
146176
177+ #if !BYTEARRAY_IN_BASE
147178instance Semigroup ShortByteString where
148179 (<>) = append
149180
@@ -154,6 +185,7 @@ instance Monoid ShortByteString where
154185
155186instance NFData ShortByteString where
156187 rnf SBS {} = ()
188+ #endif
157189
158190instance Show ShortByteString where
159191 showsPrec p ps r = showsPrec p (unpackChars ps) r
@@ -164,8 +196,13 @@ instance Read ShortByteString where
164196-- | @since 0.10.12.0
165197instance GHC.Exts. IsList ShortByteString where
166198 type Item ShortByteString = Word8
199+ #if BYTEARRAY_IN_BASE
200+ fromList = ShortByteString . GHC.Exts. fromList
201+ toList = GHC.Exts. toList . unShortByteString
202+ #else
167203 fromList = packBytes
168204 toList = unpackBytes
205+ #endif
169206
170207-- | Beware: 'fromString' truncates multi-byte characters to octets.
171208-- e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�
@@ -393,13 +430,15 @@ unpackAppendBytesStrict !sbs off len = go (off-1) (off-1 + len)
393430------------------------------------------------------------------------
394431-- Eq and Ord implementations
395432
433+ #if !BYTEARRAY_IN_BASE
396434equateBytes :: ShortByteString -> ShortByteString -> Bool
397435equateBytes sbs1 sbs2 =
398436 let ! len1 = length sbs1
399437 ! len2 = length sbs2
400438 in len1 == len2
401439 && 0 == accursedUnutterablePerformIO
402440 (memcmp_ByteArray (asBA sbs1) (asBA sbs2) len1)
441+ #endif
403442
404443compareBytes :: ShortByteString -> ShortByteString -> Ordering
405444compareBytes sbs1 sbs2 =
@@ -414,10 +453,10 @@ compareBytes sbs1 sbs2 =
414453 | len2 < len1 -> GT
415454 | otherwise -> EQ
416455
417-
418456------------------------------------------------------------------------
419457-- Appending and concatenation
420458
459+ #if !BYTEARRAY_IN_BASE
421460append :: ShortByteString -> ShortByteString -> ShortByteString
422461append src1 src2 =
423462 let ! len1 = length src1
@@ -439,7 +478,7 @@ concat sbss =
439478 let ! len = length src
440479 copyByteArray (asBA src) 0 dst off len
441480 copy dst (off + len) sbss
442-
481+ #endif
443482
444483------------------------------------------------------------------------
445484-- Exported low level operations
0 commit comments