3
3
4
4
{-# OPTIONS_HADDOCK not-home #-}
5
5
6
+ {-# LANGUAGE ConstraintKinds #-}
6
7
{-# LANGUAGE TemplateHaskellQuotes #-}
7
8
{-# LANGUAGE TypeFamilies #-}
8
9
{-# LANGUAGE UnliftedFFITypes #-}
@@ -199,6 +200,10 @@ import GHC.ForeignPtr (unsafeWithForeignPtr)
199
200
200
201
import qualified Language.Haskell.TH.Lib as TH
201
202
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
202
207
203
208
#if !HS_unsafeWithForeignPtr_AVAILABLE
204
209
unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b ) -> IO b
@@ -361,7 +366,7 @@ byteStringDataType :: DataType
361
366
byteStringDataType = mkDataType " Data.ByteString.ByteString" [packConstr]
362
367
363
368
-- | @since 0.11.2.0
364
- instance TH. Lift ByteString where
369
+ instance Lift ByteString where
365
370
#if MIN_VERSION_template_haskell(2,16,0)
366
371
-- template-haskell-2.16 first ships with ghc-8.10
367
372
lift (BS ptr len) = [| unsafePackLenLiteral | ]
@@ -532,21 +537,21 @@ packUptoLenChars len cs0 =
532
537
go ! p (c: cs) = pokeFp p (c2w c) >> go (p `plusForeignPtr` 1 ) cs
533
538
in go p0 cs0
534
539
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
537
544
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)
539
547
liftTyped = TH. liftTyped
540
548
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
542
550
liftCode = TH. liftCode
543
551
#else
544
- type THLift a = TH. Q (TH. TExp a )
545
-
546
- liftTyped :: forall a . TH. Lift a => a -> TH. Q (TH. TExp a )
547
552
liftTyped = TH. unsafeTExpCoerce . TH. lift
548
553
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
550
555
liftCode = TH. unsafeTExpCoerce
551
556
#endif
552
557
@@ -573,7 +578,7 @@ data H2W = Hex {-# UNPACK #-} !Int [Word8]
573
578
-- > ehloCmd :: ByteString
574
579
-- > ehloCmd = $$(literalFromChar8 "EHLO")
575
580
--
576
- literalFromChar8 :: String -> THLift ByteString
581
+ literalFromChar8 :: ( MonadFail m , Quote m ) => String -> Code m ByteString
577
582
literalFromChar8 " " = [|| empty|| ]
578
583
literalFromChar8 s = case foldr' op (Octets 0 [] ) s of
579
584
Octets n ws -> liftTyped (unsafePackLenBytes n ws)
@@ -597,7 +602,7 @@ literalFromChar8 s = case foldr' op (Octets 0 []) s of
597
602
-- > ehloCmd :: ByteString
598
603
-- > ehloCmd = $$(literalFromHex "45484c4F")
599
604
--
600
- literalFromHex :: String -> THLift ByteString
605
+ literalFromHex :: ( MonadFail m , Quote m ) => String -> Code m ByteString
601
606
literalFromHex " " = [|| empty|| ]
602
607
literalFromHex s =
603
608
case foldr' op (Hex 0 [] ) s of
0 commit comments