Skip to content

Commit 3626e62

Browse files
committed
fixup! fixup! fixup! Implemented TH splices for validated ByteString literals
tweak TH type signatures
1 parent 2f5671a commit 3626e62

File tree

1 file changed

+16
-11
lines changed

1 file changed

+16
-11
lines changed

Data/ByteString/Internal/Type.hs

Lines changed: 16 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33

44
{-# OPTIONS_HADDOCK not-home #-}
55

6+
{-# LANGUAGE ConstraintKinds #-}
67
{-# LANGUAGE TemplateHaskellQuotes #-}
78
{-# LANGUAGE TypeFamilies #-}
89
{-# LANGUAGE UnliftedFFITypes #-}
@@ -199,6 +200,10 @@ import GHC.ForeignPtr (unsafeWithForeignPtr)
199200

200201
import qualified Language.Haskell.TH.Lib as TH
201202
import qualified Language.Haskell.TH.Syntax as TH
203+
import Language.Haskell.TH.Syntax (Lift, TExp)
204+
#if __GLASGOW_HASKELL__ >= 900
205+
import Language.Haskell.TH.Syntax (Code, Quote)
206+
#endif
202207

203208
#if !HS_unsafeWithForeignPtr_AVAILABLE
204209
unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
@@ -361,7 +366,7 @@ byteStringDataType :: DataType
361366
byteStringDataType = mkDataType "Data.ByteString.ByteString" [packConstr]
362367

363368
-- | @since 0.11.2.0
364-
instance TH.Lift ByteString where
369+
instance Lift ByteString where
365370
#if MIN_VERSION_template_haskell(2,16,0)
366371
-- template-haskell-2.16 first ships with ghc-8.10
367372
lift (BS ptr len) = [| unsafePackLenLiteral |]
@@ -532,21 +537,21 @@ packUptoLenChars len cs0 =
532537
go !p (c:cs) = pokeFp p (c2w c) >> go (p `plusForeignPtr` 1) cs
533538
in go p0 cs0
534539

535-
#if MIN_VERSION_template_haskell(2,17,0)
536-
type THLift a = forall m. (MonadFail m, TH.Quote m) => TH.Code m a
540+
#if __GLASGOW_HASKELL__ < 900
541+
type Quote m = (TH.Q ~ m)
542+
type Code m a = m (TExp a)
543+
#endif
537544

538-
liftTyped :: forall a m. (MonadFail m, TH.Quote m, TH.Lift a) => a -> TH.Code m a
545+
liftTyped :: forall a m. (MonadFail m, Quote m, Lift a) => a -> Code m a
546+
#if MIN_VERSION_template_haskell(2,17,0)
539547
liftTyped = TH.liftTyped
540548

541-
liftCode :: forall a m. (MonadFail m, TH.Quote m) => m (TH.TExp a) -> TH.Code m a
549+
liftCode :: forall a m. (MonadFail m, Quote m) => m (TExp a) -> Code m a
542550
liftCode = TH.liftCode
543551
#else
544-
type THLift a = TH.Q (TH.TExp a)
545-
546-
liftTyped :: forall a. TH.Lift a => a -> TH.Q (TH.TExp a)
547552
liftTyped = TH.unsafeTExpCoerce . TH.lift
548553

549-
liftCode :: forall a. TH.Q TH.Exp -> TH.Q (TH.TExp a)
554+
liftCode :: forall a m. (MonadFail m, Quote m) => m TH.Exp -> Code m a
550555
liftCode = TH.unsafeTExpCoerce
551556
#endif
552557

@@ -573,7 +578,7 @@ data H2W = Hex {-# UNPACK #-} !Int [Word8]
573578
-- > ehloCmd :: ByteString
574579
-- > ehloCmd = $$(literalFromChar8 "EHLO")
575580
--
576-
literalFromChar8 :: String -> THLift ByteString
581+
literalFromChar8 :: (MonadFail m, Quote m) => String -> Code m ByteString
577582
literalFromChar8 "" = [||empty||]
578583
literalFromChar8 s = case foldr' op (Octets 0 []) s of
579584
Octets n ws -> liftTyped (unsafePackLenBytes n ws)
@@ -597,7 +602,7 @@ literalFromChar8 s = case foldr' op (Octets 0 []) s of
597602
-- > ehloCmd :: ByteString
598603
-- > ehloCmd = $$(literalFromHex "45484c4F")
599604
--
600-
literalFromHex :: String -> THLift ByteString
605+
literalFromHex :: (MonadFail m, Quote m) => String -> Code m ByteString
601606
literalFromHex "" = [||empty||]
602607
literalFromHex s =
603608
case foldr' op (Hex 0 []) s of

0 commit comments

Comments
 (0)