{-|
  Copyright   :  (C) 2022-2023, Peter Lebbing
  License     :  BSD2 (see the file LICENSE)
  Maintainer  :  Peter Lebbing <peter@digitalbrains.com>

  =Efficient interpolation for "Prettyprinter"

  This module provides efficient interpolation of
  [@string-interpolate@](https://hackage.haskell.org/package/string-interpolate)
  quasi quoters when used with
  [@prettyprinter@s](https://hackage.haskell.org/package/prettyprinter)
  'Prettyprinter.Doc'uments.

  The normal quasi quoters from @string-interpolate@ do work when used as a
  @Doc@. Newlines are even converted to @Prettyprinter.@'Prettyprinter.line'.
  However, this method is inefficient. The following code functions correctly:

  @
  {\-\# LANGUAGE OverloadedStrings \#-\}
  {\-\# LANGUAGE QuasiQuotes \#-\}

  module Main where

  import Data.String.Interpolate
  import Data.Text (Text)
  import Prettyprinter

  f :: 'Text'
  f = "world"

  g :: Doc ()
  g = ['i'|Hello #{f}!|]

  main :: IO ()
  main = print g
  @

  However, what happens under the hood is that @f@ is converted to 'String', the
  interpolated string is built manipulating @String@s, and then the output is
  converted to 'Data.Text.Text' in
  [@prettyprinter@](https://hackage.haskell.org/package/prettyprinter). The
  following code is much better:

  @
  g = 'pretty' ([i|Hello #{f}!|] :: Text)
  @

  Now, the interpolated string is constructed as @Text@, and this is passed
  cleanly into @Doc@ which also uses @Text@ as its underlying type for
  representation of text. At no point is @f@ converted to @String@, and the
  string construction benefits from the performance of @Text@. And again,
  newlines are converted to 'Prettyprinter.line'.

  This module defines wrapper quasi quoters that automatically perform the
  @pretty@ invocation, and can simply be used as:

  @
  g = ['di'|Hello #{f}!|]
  @
-}

{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}

module Prettyprinter.Interpolate
  ( di
  , __di
  , diii
  , __di'E
  , __di'L
  , diii'E
  , diii'L
    -- ** Deprecated
  , d__i'E
  , d__i'L
  ) where

#if MIN_VERSION_prettyprinter(1,7,0)
import Prettyprinter (Pretty(pretty))
#else
import Data.Text.Prettyprint.Doc (Pretty(pretty))
#endif

import Data.String.Interpolate
import Data.Text (Text)
import Language.Haskell.TH (Q)
import Language.Haskell.TH.Quote (QuasiQuoter(..))
import Language.Haskell.TH.Syntax (Name)

wrapper :: Name -> QuasiQuoter -> QuasiQuoter
wrapper :: Name -> QuasiQuoter -> QuasiQuoter
wrapper Name
nm QuasiQuoter
wrapped = QuasiQuoter
  { quoteExp :: String -> Q Exp
quoteExp = \String
s -> [| pretty ($(QuasiQuoter -> String -> Q Exp
quoteExp QuasiQuoter
wrapped String
s) :: Text) |]
  , quotePat :: String -> Q Pat
quotePat = Q Pat -> String -> Q Pat
forall a b. a -> b -> a
const (Q Pat -> String -> Q Pat) -> Q Pat -> String -> Q Pat
forall a b. (a -> b) -> a -> b
$ Name -> String -> Q Pat
forall a. Name -> String -> Q a
errQQType Name
nm String
"pattern"
  , quoteType :: String -> Q Type
quoteType = Q Type -> String -> Q Type
forall a b. a -> b -> a
const (Q Type -> String -> Q Type) -> Q Type -> String -> Q Type
forall a b. (a -> b) -> a -> b
$ Name -> String -> Q Type
forall a. Name -> String -> Q a
errQQType Name
nm String
"type"
  , quoteDec :: String -> Q [Dec]
quoteDec = Q [Dec] -> String -> Q [Dec]
forall a b. a -> b -> a
const (Q [Dec] -> String -> Q [Dec]) -> Q [Dec] -> String -> Q [Dec]
forall a b. (a -> b) -> a -> b
$ Name -> String -> Q [Dec]
forall a. Name -> String -> Q a
errQQType Name
nm String
"declaration"
  }

-- | Wrapper around the 'i' quasi quoter, producing a t'Prettyprinter.Doc'
--
-- Newlines in the text are converted to 'Prettyprinter.line'.
di :: QuasiQuoter
di :: QuasiQuoter
di = Name -> QuasiQuoter -> QuasiQuoter
wrapper 'di QuasiQuoter
i

-- | Wrapper around the '__i' quasi quoter, producing a t'Prettyprinter.Doc'
--
-- Newlines in the text are converted to 'Prettyprinter.line'.
__di :: QuasiQuoter
__di :: QuasiQuoter
__di = Name -> QuasiQuoter -> QuasiQuoter
wrapper '__di QuasiQuoter
__i

-- | Wrapper around the 'iii' quasi quoter, producing a t'Prettyprinter.Doc'
--
-- Newlines in the text are converted to 'Prettyprinter.line'.
diii :: QuasiQuoter
diii :: QuasiQuoter
diii = Name -> QuasiQuoter -> QuasiQuoter
wrapper 'diii QuasiQuoter
iii

-- | Wrapper around the '__i'E' quasi quoter, producing a t'Prettyprinter.Doc'
--
-- Newlines in the text are converted to 'Prettyprinter.line'.
__di'E :: QuasiQuoter
__di'E :: QuasiQuoter
__di'E = Name -> QuasiQuoter -> QuasiQuoter
wrapper '__di'E QuasiQuoter
__i'E

-- | Wrapper around the '__i'L' quasi quoter, producing a t'Prettyprinter.Doc'
--
-- Newlines in the text are converted to 'Prettyprinter.line'.
__di'L :: QuasiQuoter
__di'L :: QuasiQuoter
__di'L = Name -> QuasiQuoter -> QuasiQuoter
wrapper '__di'L QuasiQuoter
__i'L

-- | Wrapper around the 'iii'E' quasi quoter, producing a t'Prettyprinter.Doc'
--
-- Newlines in the text are converted to 'Prettyprinter.line'.
diii'E :: QuasiQuoter
diii'E :: QuasiQuoter
diii'E = Name -> QuasiQuoter -> QuasiQuoter
wrapper 'diii'E QuasiQuoter
iii'E

-- | Wrapper around the 'iii'L' quasi quoter, producing a t'Prettyprinter.Doc'
--
-- Newlines in the text are converted to 'Prettyprinter.line'.
diii'L :: QuasiQuoter
diii'L :: QuasiQuoter
diii'L = Name -> QuasiQuoter -> QuasiQuoter
wrapper 'diii'L QuasiQuoter
iii'L

d__i'E :: QuasiQuoter
d__i'E :: QuasiQuoter
d__i'E = Name -> QuasiQuoter -> QuasiQuoter
wrapper 'd__i'E QuasiQuoter
__i'E
{-# DEPRECATED d__i'E "'d__i'E' is a deprecated alias for '__di'E' and will be removed in prettyprinter-interp 0.3" #-}

d__i'L :: QuasiQuoter
d__i'L :: QuasiQuoter
d__i'L = Name -> QuasiQuoter -> QuasiQuoter
wrapper 'd__i'L QuasiQuoter
__i'L
{-# DEPRECATED d__i'L "'d__i'L' is a deprecated alias for '__di'L' and will be removed in prettyprinter-interp 0.3" #-}

errQQ :: Name -> String -> Q a
errQQ :: forall a. Name -> String -> Q a
errQQ Name
nm String
msg = String -> Q a
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q a) -> String -> Q a
forall a b. (a -> b) -> a -> b
$ Name -> String
forall a. Show a => a -> String
show Name
nm String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
": " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
msg

errQQType :: Name -> String -> Q a
errQQType :: forall a. Name -> String -> Q a
errQQType Name
nm String
ty = Name -> String -> Q a
forall a. Name -> String -> Q a
errQQ Name
nm (String -> Q a) -> String -> Q a
forall a b. (a -> b) -> a -> b
$ String
"This QuasiQuoter cannot be used as a " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
ty