Skip to content

Instantly share code, notes, and snippets.

@PkmX
Last active January 24, 2019 09:13
Show Gist options
  • Save PkmX/1a78f337f3f82153755847e16e2bea94 to your computer and use it in GitHub Desktop.
Save PkmX/1a78f337f3f82153755847e16e2bea94 to your computer and use it in GitHub Desktop.
GHC Source Plugin for Data.String.Interpolate
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Interpolate (plugin) where
import GhcPlugins
import HsSyn
import qualified Data.Generics as SYB
plugin :: Plugin
plugin = defaultPlugin
{ parsedResultAction = parsedPlugin
}
parsedPlugin :: [CommandLineOption] -> ModSummary -> HsParsedModule -> Hsc HsParsedModule
parsedPlugin _ _ HsParsedModule{..} = do
let hpm_module' = SYB.mkT transform `SYB.everywhere` hpm_module
return $ HsParsedModule{ hpm_module = hpm_module', .. }
transform :: HsExpr GhcPs -> HsExpr GhcPs
transform (HsLit _ (HsString _ fs)) = HsSpliceE NoExt $ mkHsQuasiQuote (mkVarUnqual "i") noSrcSpan fs
transform expr = expr
{-# OPTIONS_GHC -fplugin=Interpolate #-}
module Main where
import Data.String.Interpolate
a :: Int
a = 42
s :: String
s = "#{a} * #{a} = #{a * a}"
main :: IO ()
main = putStrLn s -- 42 * 42 = 1764
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment