I have a Lift
instance that works with template-haskell 2.14, but won't compile with later versions. Can someone explain what changes are needed?
{-# LANGUAGE FlexibleInstances, TemplateHaskell #-}
module LiftBS where
import Data.ByteString as B (ByteString, length, unpack)
import Data.ByteString.Unsafe (unsafePackAddressLen)
import Language.Haskell.TH (runIO, litE, stringPrimL)
import Language.Haskell.TH.Lift (Lift(lift))
instance Lift (IO B.ByteString) where
lift bsio = do
bs <- runIO bsio
[|unsafePackAddressLen $(lift (B.length bs)) $(litE (stringPrimL (B.unpack bs))) :: IO ByteString|]