From 0d0ec98dd5657ac6679fc2cfb326601950e5c760 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 27 Nov 2019 21:27:46 -0800 Subject: Generate Emoji module with TH. - Add Text.Pandoc.Emoji.TH. - Replace long literal list in Text.Pandoc.Emoji with one-liner generating it from data/emoji.json using TH. - Add Makefile target to download data/emoji.json. - Remove tools/emoji.hs. --- src/Text/Pandoc/Emoji/TH.hs | 40 ++++++++++++++++++++++++++++++++++++++++ 1 file changed, 40 insertions(+) create mode 100644 src/Text/Pandoc/Emoji/TH.hs (limited to 'src/Text/Pandoc/Emoji') diff --git a/src/Text/Pandoc/Emoji/TH.hs b/src/Text/Pandoc/Emoji/TH.hs new file mode 100644 index 000000000..a2e11e430 --- /dev/null +++ b/src/Text/Pandoc/Emoji/TH.hs @@ -0,0 +1,40 @@ +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Emoji.TH + Copyright : Copyright (C) 2019 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane + Stability : alpha + Portability : portable + +Code generation for emoji list in Text.Pandoc.Emoji. +-} +module Text.Pandoc.Emoji.TH ( genEmojis ) where +import Prelude +import Data.Aeson +import qualified Data.ByteString.Lazy as B +import Language.Haskell.TH +import Language.Haskell.TH.Syntax (addDependentFile) + +genEmojis :: FilePath -> Q Exp +genEmojis fp = do + addDependentFile fp + bs <- runIO $ B.readFile fp + case eitherDecode bs of + Left e -> error e + Right (emoji :: [Emoji]) -> + return $ ListE + [TupE [ LitE (StringL alias), + LitE (StringL txt) ] + | Emoji txt aliases <- emoji + , alias <- aliases] + +data Emoji = Emoji String [String] + deriving Show + +instance FromJSON Emoji where + parseJSON = withObject "Emoji" $ \v -> Emoji + <$> v .: "emoji" + <*> v .: "aliases" -- cgit v1.2.3