diff options
author | John MacFarlane <jgm@berkeley.edu> | 2019-11-27 21:27:46 -0800 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2019-11-27 21:31:53 -0800 |
commit | 0d0ec98dd5657ac6679fc2cfb326601950e5c760 (patch) | |
tree | 490d416e250e9162fb8ff7d74b240a7e8c82c618 /src/Text/Pandoc/Emoji | |
parent | bd175d13b6004086ccd3862822f97c7f090cadb4 (diff) | |
download | pandoc-0d0ec98dd5657ac6679fc2cfb326601950e5c760.tar.gz |
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.
Diffstat (limited to 'src/Text/Pandoc/Emoji')
-rw-r--r-- | src/Text/Pandoc/Emoji/TH.hs | 40 |
1 files changed, 40 insertions, 0 deletions
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 <jgm@berkeley.edu> + 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" |