88{-# LANGUAGE  UnliftedFFITypes #-}
99{-# LANGUAGE  ViewPatterns #-}
1010
11+ #include  "bytestring-cpp-macros.h"
12+ 
1113--  | 
1214--  Module      : Data.ByteString.Internal.Type 
1315--  Copyright   : (c) Don Stewart 2006-2008 
@@ -143,10 +145,7 @@ import Data.Maybe               (fromMaybe)
143145import  Control.Monad             ((<$!>) )
144146#endif 
145147
146- #if  !MIN_VERSION_base(4,13,0)
147- import  Data.Semigroup            (Semigroup  ((<>) ))
148- #endif 
149- import  Data.Semigroup            (Semigroup  (sconcat , stimes ))
148+ import  Data.Semigroup            (Semigroup  (.. ))
150149import  Data.List.NonEmpty        (NonEmpty  ((:|) ))
151150
152151import  Control.DeepSeq           (NFData (rnf ))
@@ -159,18 +158,15 @@ import Data.Bits                ((.&.))
159158import  Data.Char                 (ord )
160159import  Data.Word 
161160
162- import  Data.Data                 (Data (.. ), mkConstr  , mkDataType , Constr , DataType , Fixity (Prefix ), constrIndex )
161+ import  Data.Data                 (Data (.. ), mkConstr ,  mkDataType , Constr , DataType , Fixity (Prefix ), constrIndex )
163162
164- import  GHC.Base                  (nullAddr #,realWorld #,unsafeChr )
165- import  GHC.Exts                  (IsList (.. ), Addr #, minusAddr #, ByteArray #)
166- import  GHC.CString               (unpackCString #)
167- import  GHC.Magic                 (runRW #, lazy )
163+ import  GHC.Base                  (nullAddr #,realWorld #,unsafeChr ,unpackCString #)
164+ import  GHC.Exts                  (IsList (.. ), Addr #, minusAddr #, ByteArray #, runRW #, lazy )
168165
169- #define  TIMES_INT_2_AVAILABLE MIN_VERSION_ghc_prim(0,7,0)
170- #if  TIMES_INT_2_AVAILABLE
171- import  GHC.Prim                 (timesInt2 #)
166+ #if  HS_timesInt2_PRIMOP_AVAILABLE
167+ import  GHC.Exts                 (timesInt2 #)
172168#else 
173- import  GHC.Prim                  ( timesWord2 #
169+ import  GHC.Exts                  ( timesWord2 #
174170                               , or #
175171                               , uncheckedShiftRL #
176172                               , int2Word #
@@ -181,60 +177,37 @@ import Data.Bits               (finiteBitSize)
181177
182178import  GHC.IO                    (IO  (IO ))
183179import  GHC.ForeignPtr            (ForeignPtr (ForeignPtr )
184- #if  __GLASGOW_HASKELL__ < 900 
180+ #if  !HS_cstringLength_AND_FinalPtr_AVAILABLE 
185181                                , newForeignPtr_ 
186182#endif 
187183                                , mallocPlainForeignPtrBytes )
188184
189- #if  MIN_VERSION_base(4,10,0)
190185import  GHC.ForeignPtr            (plusForeignPtr )
191- #else 
192- import  GHC.Prim                  (plusAddr #)
193- #endif 
194186
195- #if  __GLASGOW_HASKELL__ >= 811 
196- import  GHC.CString                (cstringLength #)
187+ #if  HS_cstringLength_AND_FinalPtr_AVAILABLE 
188+ import  GHC.Exts                    (cstringLength #)
197189import  GHC.ForeignPtr            (ForeignPtrContents (FinalPtr ))
198190#else 
199191import  GHC.Ptr                   (Ptr (.. ))
200192#endif 
201193
202- import  GHC.Types                  (Int   (.. ))
194+ import  GHC.Int                     (Int   (.. ))
203195
204- #if  MIN_VERSION_base(4,15,0) 
196+ #if  HS_unsafeWithForeignPtr_AVAILABLE 
205197import  GHC.ForeignPtr            (unsafeWithForeignPtr )
206198#endif 
207199
208200import  qualified  Language.Haskell.TH.Lib  as  TH 
209201import  qualified  Language.Haskell.TH.Syntax  as  TH 
210202
211- #if  !MIN_VERSION_base(4,15,0) 
203+ #if  !HS_unsafeWithForeignPtr_AVAILABLE 
212204unsafeWithForeignPtr  ::  ForeignPtr  a  ->  (Ptr  a  ->  IO   b ) ->  IO   b 
213205unsafeWithForeignPtr =  withForeignPtr
214206#endif 
215207
216208--  CFILES stuff is Hugs only
217209{-# CFILES  cbits/fpstring.c #-}
218210
219- #if  !MIN_VERSION_base(4,10,0)
220- --  | Advances the given address by the given offset in bytes. 
221- -- 
222- --  The new 'ForeignPtr' shares the finalizer of the original, 
223- --  equivalent from a finalization standpoint to just creating another 
224- --  reference to the original. That is, the finalizer will not be 
225- --  called before the new 'ForeignPtr' is unreachable, nor will it be 
226- --  called an additional time due to this call, and the finalizer will 
227- --  be called with the same address that it would have had this call 
228- --  not happened, *not* the new address. 
229- plusForeignPtr  ::  ForeignPtr  a  ->  Int   ->  ForeignPtr  b 
230- plusForeignPtr (ForeignPtr  addr guts) (I #  offset) =  ForeignPtr  (plusAddr#  addr offset) guts
231- {-# INLINE  [0] plusForeignPtr #-}
232- {-# RULES 
233- "ByteString plusForeignPtr/0" forall fp .
234-    plusForeignPtr fp 0 = fp
235-  #-}
236- #endif 
237- 
238211minusForeignPtr  ::  ForeignPtr  a  ->  ForeignPtr  b  ->  Int 
239212minusForeignPtr (ForeignPtr  addr1 _) (ForeignPtr  addr2 _)
240213  =  I #  (minusAddr#  addr1 addr2)
@@ -332,9 +305,7 @@ type StrictByteString = ByteString
332305pattern  PS  ::  ForeignPtr  Word8  ->  Int   ->  Int   ->  ByteString 
333306pattern  PS  fp zero len <-  BS  fp ((0 ,) ->  (zero, len)) where 
334307  PS  fp o len =  BS  (plusForeignPtr fp o) len
335- #if  __GLASGOW_HASKELL__ >= 802
336308{-# COMPLETE  PS #-}
337- #endif 
338309
339310instance  Eq    ByteString  where 
340311    (==)     =  eq
@@ -391,6 +362,7 @@ byteStringDataType = mkDataType "Data.ByteString.ByteString" [packConstr]
391362--  |  @since 0.11.2.0 
392363instance  TH. Lift  ByteString  where 
393364#if  MIN_VERSION_template_haskell(2,16,0)
365+ --  template-haskell-2.16 first ships with ghc-8.10
394366  lift (BS  ptr len) =  [|  unsafePackLenLiteral | ]
395367    `TH.appE`  TH. litE (TH. integerL (fromIntegral  len))
396368    `TH.appE`  TH. litE (TH. BytesPrimL  $  TH. Bytes  ptr 0  (fromIntegral  len))
@@ -401,8 +373,10 @@ instance TH.Lift ByteString where
401373#endif 
402374
403375#if  MIN_VERSION_template_haskell(2,17,0)
376+ --  template-haskell-2.17 first ships with ghc-9.0
404377  liftTyped =  TH. unsafeCodeCoerce .  TH. lift
405378#elif  MIN_VERSION_template_haskell(2,16,0)
379+ --  template-haskell-2.16 first ships with ghc-8.10
406380  liftTyped =  TH. unsafeTExpCoerce .  TH. lift
407381#endif 
408382
@@ -478,7 +452,7 @@ unsafePackLenChars len cs0 =
478452-- 
479453unsafePackAddress  ::  Addr #  ->  IO   ByteString 
480454unsafePackAddress addr#  =  do 
481- #if  __GLASGOW_HASKELL__ >= 811 
455+ #if  HS_cstringLength_AND_FinalPtr_AVAILABLE 
482456    unsafePackLenAddress (I #  (cstringLength#  addr# )) addr# 
483457#else 
484458    l <-  c_strlen (Ptr  addr# )
@@ -494,7 +468,7 @@ unsafePackAddress addr# = do
494468--  @since 0.11.2.0 
495469unsafePackLenAddress  ::  Int   ->  Addr #  ->  IO   ByteString 
496470unsafePackLenAddress len addr#  =  do 
497- #if  __GLASGOW_HASKELL__ >= 811 
471+ #if  HS_cstringLength_AND_FinalPtr_AVAILABLE 
498472    return  (BS  (ForeignPtr  addr#  FinalPtr ) len)
499473#else 
500474    p <-  newForeignPtr_ (Ptr  addr# )
@@ -511,7 +485,7 @@ unsafePackLenAddress len addr# = do
511485--  @since 0.11.1.0 
512486unsafePackLiteral  ::  Addr #  ->  ByteString 
513487unsafePackLiteral addr#  = 
514- #if  __GLASGOW_HASKELL__ >= 811 
488+ #if  HS_cstringLength_AND_FinalPtr_AVAILABLE 
515489  unsafePackLenLiteral (I #  (cstringLength#  addr# )) addr# 
516490#else 
517491  let  len =  accursedUnutterablePerformIO (c_strlen (Ptr  addr# ))
@@ -528,7 +502,7 @@ unsafePackLiteral addr# =
528502--  @since 0.11.2.0 
529503unsafePackLenLiteral  ::  Int   ->  Addr #  ->  ByteString 
530504unsafePackLenLiteral len addr#  = 
531- #if  __GLASGOW_HASKELL__ >= 811 
505+ #if  HS_cstringLength_AND_FinalPtr_AVAILABLE 
532506  BS  (ForeignPtr  addr#  FinalPtr ) len
533507#else 
534508  --  newForeignPtr_ allocates a MutVar# internally. If that MutVar#
@@ -621,7 +595,7 @@ unpackAppendCharsStrict (BS fp len) xs =
621595
622596--  |  The 0 pointer. Used to indicate the empty Bytestring. 
623597nullForeignPtr  ::  ForeignPtr  Word8 
624- #if  __GLASGOW_HASKELL__ >= 811 
598+ #if  HS_cstringLength_AND_FinalPtr_AVAILABLE 
625599nullForeignPtr =  ForeignPtr  nullAddr#  FinalPtr 
626600#else 
627601nullForeignPtr =  ForeignPtr  nullAddr#  (error  " nullForeignPtr"  )
@@ -1039,7 +1013,7 @@ checkedAdd fun x y
10391013checkedMultiply  ::  String   ->  Int   ->  Int   ->  Int 
10401014{-# INLINE  checkedMultiply #-}
10411015checkedMultiply fun ! x@ (I #  x# ) ! y@ (I #  y# ) =  assert (min  x y >=  0 ) $ 
1042- #if  TIMES_INT_2_AVAILABLE 
1016+ #if  HS_timesInt2_PRIMOP_AVAILABLE 
10431017  case  timesInt2#  x#  y#  of 
10441018    (#  0 # , _, result # ) ->  I #  result
10451019    _ ->  overflowError fun
0 commit comments