{-# LANGUAGE TemplateHaskell, TypeSynonymInstances, FlexibleInstances, UndecidableInstances, OverlappingInstances #-} -- | QuasiQuoter for interpolated strings using Perl 6 syntax. -- -- The "q" form does one thing and does it well: It contains a multi-line string with -- no interpolation at all: -- -- @ -- {-# LANGUAGE QuasiQuotes, ExtendedDefaultRules #-} -- import Text.InterpolatedString.Perl6 (q) -- foo :: String -- foo = [$q| -- -- Well here is a -- multi-line string! -- -- |] -- @ -- -- The "qc" form interpolates curly braces: Expressions inside {} will be -- directly interpolated if it's a String, or have 'show' called if it is not. -- -- Escaping of '{' is done with backslash. -- -- For interpolating numeric expressions without an explicit type signature, -- use the ExtendedDefaultRules language pragma, as shown below: -- -- @ -- {-# LANGUAGE QuasiQuotes, ExtendedDefaultRules #-} -- import Text.InterpolatedString.Perl6 (qc) -- bar :: String -- bar = [$qc| Well {\"hello\" ++ \" there\"} {6 * 7} |] -- @ -- -- bar will have the value \" Well hello there 42 \". -- -- If you want control over how 'show' works on your types, define a custom -- 'ShowQ' instance: -- -- @ -- import Text.InterpolatedString.Perl6 (qc, ShowQ(..)) -- instance ShowQ ByteString where -- showQ = unpack -- @ -- -- That way you interpolate bytestrings will not result in double quotes or -- character escapes. -- module Text.InterpolatedString.Perl6 (qc, q, ShowQ(..)) where import qualified Language.Haskell.TH as TH import Language.Haskell.TH.Quote import Language.Haskell.Meta.Parse class Show a => ShowQ a where showQ :: a -> String instance ShowQ Char where showQ = (:[]) instance ShowQ String where showQ = id instance (Show a) => ShowQ a where showQ = show data StringPart = Literal String | AntiQuote String deriving Show parseHaskell a [] = [Literal (reverse a)] parseHaskell a ('\\':x:xs) = parseHaskell (x:a) xs parseHaskell a ('\\':[]) = parseHaskell ('\\':a) [] parseHaskell a ('}':xs) = AntiQuote (reverse a) : parseStr [] xs parseHaskell a (x:xs) = parseHaskell (x:a) xs parseStr a [] = [Literal (reverse a)] parseStr a ('\\':x:xs) = parseStr (x:a) xs parseStr a ('\\':[]) = parseStr ('\\':a) [] parseStr a ('{':xs) = Literal (reverse a) : parseHaskell [] xs parseStr a (x:xs) = parseStr (x:a) xs makeExpr [] = [| "" |] makeExpr ((Literal a):xs) = TH.appE [| (++) a |] $ makeExpr xs makeExpr ((AntiQuote a):xs) = TH.appE [| (++) (showQ $(reify a)) |] $ makeExpr xs reify s = case parseExp s of Left s -> TH.report True s >> [| "" |] Right e -> return e -- | QuasiQuoter for interpolating Haskell values into a string literal. The pattern portion is undefined. qc :: QuasiQuoter qc = QuasiQuoter (makeExpr . parseStr [] . filter (/= '\r')) $ error "Cannot use qc as a pattern" q :: QuasiQuoter q = QuasiQuoter ((\a -> [|a|]) . filter (/= '\r')) $ error "Cannot use q as a pattern"