{-# LANGUAGE TemplateHaskellQuotes #-}

{-|
Module      : GHCup.Utils.String.QQ
Description : String quasi quoters
Copyright   : (c) Audrey Tang <audreyt@audreyt.org> 2019, Julian Ospald <hasufell@posteo.de> 2020
License     : LGPL-3.0
Maintainer  : hasufell@hasufell.de
Stability   : experimental
Portability : portable

QuasiQuoter for non-interpolated strings, texts and bytestrings.

The "s" quoter contains a multi-line string with no interpolation at all,
except that the leading newline is trimmed and carriage returns stripped.

@
{-\# LANGUAGE QuasiQuotes #-}
import Data.Text (Text)
import Data.String.QQ
foo :: Text -- "String", "ByteString" etc also works
foo = [s|
Well here is a
    multi-line string!
|]
@

Any instance of the IsString type is permitted.

(For GHC versions 6, write "[$s||]" instead of "[s||]".)

-}
module GHCup.Prelude.String.QQ
  ( s
  )
where


import           Data.Char
import           GHC.Exts                       ( IsString(..) )
import           Language.Haskell.TH.Quote

-- | QuasiQuoter for a non-interpolating ASCII IsString literal.
-- The pattern portion is undefined.
s :: QuasiQuoter
s :: QuasiQuoter
s = ([Char] -> Q Exp)
-> ([Char] -> Q Pat)
-> ([Char] -> Q Type)
-> ([Char] -> Q [Dec])
-> QuasiQuoter
QuasiQuoter
  (\[Char]
s' -> case (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isAscii [Char]
s' of
    Bool
True  -> (\[Char]
a -> [|fromString a|]) ([Char] -> Q Exp) -> ([Char] -> [Char]) -> [Char] -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
trimLeadingNewline ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
removeCRs ([Char] -> Q Exp) -> [Char] -> Q Exp
forall a b. (a -> b) -> a -> b
$ [Char]
s'
    Bool
False -> [Char] -> Q Exp
forall a. [Char] -> Q a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"Not ascii"
  )
  ([Char] -> [Char] -> Q Pat
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot use s as a pattern")
  ([Char] -> [Char] -> Q Type
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot use s as a type")
  ([Char] -> [Char] -> Q [Dec]
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot use s as a dec")
 where
  removeCRs :: [Char] -> [Char]
removeCRs = (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\r')
  trimLeadingNewline :: [Char] -> [Char]
trimLeadingNewline (Char
'\n' : [Char]
xs) = [Char]
xs
  trimLeadingNewline [Char]
xs          = [Char]
xs