{-# LANGUAGE TemplateHaskell, CPP #-}

-- | 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 Data.String.QQ (s) where
import GHC.Exts (IsString(..))
import qualified Language.Haskell.TH as TH
import Language.Haskell.TH.Quote

-- | QuasiQuoter for a non-interpolating 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]
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] -> [Char] -> Q Pat
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot use q as a pattern")
#if (__GLASGOW_HASKELL__ >= 700)
                 ([Char] -> [Char] -> Q Type
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot use q as a type")
                 ([Char] -> [Char] -> Q [Dec]
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot use q as a dec")
#endif
    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