Skip to content

Commit

Permalink
Scale back changes to ShortByteString to pattern synonym only
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed Mar 22, 2022
1 parent e51ede3 commit 8b962e8
Showing 1 changed file with 9 additions and 22 deletions.
31 changes: 9 additions & 22 deletions Data/ByteString/Short/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiWayIf #-}
Expand All @@ -16,10 +15,6 @@
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE Unsafe #-}

#if MIN_VERSION_base(4,10,0)
{-# LANGUAGE DerivingStrategies #-}
#endif

{-# OPTIONS_GHC -fno-warn-name-shadowing -fexpose-all-unfoldings #-}
{-# OPTIONS_HADDOCK not-home #-}

Expand Down Expand Up @@ -191,10 +186,16 @@ import Data.Data
)
import Data.Monoid
( Monoid(..) )
import Data.Semigroup
( Semigroup((<>)) )
import Data.String
( IsString(..) )
import Data.Typeable
( Typeable )
import Control.Applicative
( pure )
import Control.DeepSeq
( NFData(..) )
import Control.Exception
( assert )
import Control.Monad
Expand Down Expand Up @@ -275,11 +276,6 @@ import Prelude

#if BYTEARRAY_IN_BASE
import Data.Array.Byte
import Data.Semigroup (Semigroup)
#else
import Data.Typeable (Typeable)
import Data.Semigroup (Semigroup((<>)))
import Control.DeepSeq (NFData(..))
#endif

import qualified Data.ByteString.Internal as BS
Expand All @@ -305,7 +301,7 @@ import qualified Language.Haskell.TH.Syntax as TH
--
#if BYTEARRAY_IN_BASE
newtype ShortByteString = ShortByteString { unShortByteString :: ByteArray }
deriving newtype (Eq, Semigroup, Monoid)
deriving Typeable

pattern SBS :: ByteArray# -> ShortByteString
pattern SBS x = ShortByteString (ByteArray x)
Expand Down Expand Up @@ -342,16 +338,14 @@ instance TH.Lift ShortByteString where
-- the 0--3 trailing bytes undefined. This means we can use word-sized writes,
-- but we have to be careful with reads, see equateBytes and compareBytes below.

#if !BYTEARRAY_IN_BASE

instance Eq ShortByteString where
(==) = equateBytes
#endif

-- | Lexicographic order.
instance Ord ShortByteString where
compare = compareBytes

#if !BYTEARRAY_IN_BASE
instance Semigroup ShortByteString where
(<>) = append

Expand All @@ -362,7 +356,6 @@ instance Monoid ShortByteString where

instance NFData ShortByteString where
rnf SBS{} = ()
#endif

instance Show ShortByteString where
showsPrec p ps r = showsPrec p (unpackChars ps) r
Expand All @@ -373,13 +366,8 @@ instance Read ShortByteString where
-- | @since 0.10.12.0
instance GHC.Exts.IsList ShortByteString where
type Item ShortByteString = Word8
#if BYTEARRAY_IN_BASE
fromList = ShortByteString . GHC.Exts.fromList
toList = GHC.Exts.toList . unShortByteString
#else
fromList = packBytes
toList = unpackBytes
#endif

-- | Beware: 'fromString' truncates multi-byte characters to octets.
-- e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�
Expand Down Expand Up @@ -666,14 +654,12 @@ unpackAppendBytesStrict !sbs off len = go (off-1) (off-1 + len)
------------------------------------------------------------------------
-- Eq and Ord implementations

#if !BYTEARRAY_IN_BASE
equateBytes :: ShortByteString -> ShortByteString -> Bool
equateBytes sbs1 sbs2 =
let !len1 = length sbs1
!len2 = length sbs2
in len1 == len2
&& 0 == compareByteArrays (asBA sbs1) (asBA sbs2) len1
#endif

compareBytes :: ShortByteString -> ShortByteString -> Ordering
compareBytes sbs1 sbs2 =
Expand All @@ -687,6 +673,7 @@ compareBytes sbs1 sbs2 =
| len2 < len1 -> GT
| otherwise -> EQ


------------------------------------------------------------------------
-- Appending and concatenation

Expand Down

0 comments on commit 8b962e8

Please sign in to comment.