module Text.Authoring.TH (rawQ, escQ, declareLabels) where
import Control.Applicative
import Control.Monad
import Data.Char (isSpace, toUpper, toLower)
import Data.Typeable (Typeable)
import Data.Monoid
import qualified Data.Text as T
import qualified Language.Haskell.Meta.Parse.Careful as Meta
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Text.Trifecta
import Text.Trifecta.Delta
import Text.Parser.LookAhead
import Text.PrettyPrint.ANSI.Leijen as Pretty hiding (line, (<>), (<$>), empty, string)
import Text.Printf
import Safe (readMay)
import System.IO
import Text.Authoring.Combinator.Writer (raw, esc)
import Text.Authoring.Label (Label, fromValue)
escQ = rawQ {quoteExp = parseE (QQConfig { escaper = appE (varE 'esc)})}
rawQ :: QuasiQuoter
rawQ = QuasiQuoter {
quoteExp = parseE (QQConfig { escaper = appE (varE 'raw)}),
quotePat = error "Authoring QuasiQuotes are only for expression context" ,
quoteType = error "Authoring QuasiQuotes are only for expression context" ,
quoteDec = error "Authoring QuasiQuotes are only for expression context"
}
data QQConfig = QQConfig
{ escaper :: ExpQ -> ExpQ }
parseE :: QQConfig -> String -> ExpQ
parseE cfg str = do
let res = parseString parseLang (Columns 0 0) str
case res of
Failure xs -> do
runIO $ do
displayIO stdout $ renderPretty 0.8 80 $ xs <> linebreak
putStrLn "Due to parse failure entire quote will be processed as a string."
joinE $ map (cvtE cfg) $ [StrPart str]
Success x -> joinE $ map (cvtE cfg) x
cvtE :: QQConfig -> Component -> ExpQ
cvtE cfg (StrPart x) = escaper cfg $ appE (varE 'T.pack) $ stringE x
cvtE cfg (EmbedShow x) =
either (fallback "#" x)
(escaper cfg . appE [| T.pack . showJoin |] . return) $
Meta.parseExp x
cvtE _ (EmbedMonad x) =
either (fallback "@" x) return $
Meta.parseExp x
fallback :: String -> String -> String -> ExpQ
fallback sym str _ = [| esc . T.pack |] `appE`
(stringE $ printf "%s{%s}" sym str)
trim :: String -> String
trim = T.unpack . T.strip . T.pack
showJoin :: Show a => a -> String
showJoin x = maybe sx id rsx
where
sx :: String
sx = show x
rsx :: Maybe String
rsx = readMay sx
joinE :: [ExpQ] -> ExpQ
joinE = foldl ap [e| return () |]
where
ap a b = appE (appE (varE '(>>) ) a ) b
data Component
= StrPart String
| EmbedMonad String
| EmbedShow String deriving (Eq,Show)
parseLang :: Parser [Component]
parseLang = (many $ choice [try parseEmbedMonad, try parseEmbedShow, parseStrPart]) <* eof
parseStrPart :: Parser Component
parseStrPart = StrPart <$> go <?> "String Part"
where
go = do
notFollowedBy $ choice [string "#{", string "@{"]
h <- anyChar
t <- manyTill anyChar (lookAhead $ choice [string "#{", string "@{", eof >> return ""])
return $ h:t
parseEmbedMonad :: Parser Component
parseEmbedMonad = EmbedMonad <$> between (string "@{") (string "}") (some $ noneOf "}")
<?> "Embed MonadAuthoring @{...}"
parseEmbedShow :: Parser Component
parseEmbedShow = EmbedShow <$> between (string "#{") (string "}") (some $ noneOf "}")
<?> "Embed an instance of Show #{...}"
declareLabels =
QuasiQuoter {
quoteExp = error "defineLabel QuasiQuote is only for declaration context" ,
quotePat = error "defineLabel QuasiQuote is only for declaration context" ,
quoteType = error "defineLabel QuasiQuote is only for declaration context" ,
quoteDec = decLabelsQ
}
decLabelsQ :: String -> DecsQ
decLabelsQ str = fmap concat $ mapM decLabelQ names
where
names =
map T.unpack $
map T.strip $
T.splitOn "," $ T.pack str
decLabelQ :: String -> DecsQ
decLabelQ theName = do
let (hName:tName) = theName
theTypeName = mkName (toUpper hName : tName)
theConName = mkName (toUpper hName : tName)
theValName = mkName (toLower hName : tName)
let decTheType = dataD (cxt []) theTypeName [] [normalC theConName []] [''Eq, ''Show, ''Typeable]
typeTheVal = sigD theValName (conT ''Label)
decTheVal = funD theValName [clause [] (normalB theBody) []]
theBody = appE (varE 'fromValue) (conE theConName)
sequence [decTheType, typeTheVal, decTheVal]