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. --- tools/emojis.hs | 36 ------------------------------------ 1 file changed, 36 deletions(-) delete mode 100755 tools/emojis.hs (limited to 'tools') diff --git a/tools/emojis.hs b/tools/emojis.hs deleted file mode 100755 index 9926a9047..000000000 --- a/tools/emojis.hs +++ /dev/null @@ -1,36 +0,0 @@ --- Script to generate the list of emojis in T.P.Emoji.hs. --- to run: --- curl https://raw.githubusercontent.com/github/gemoji/master/db/emoji.json -o emoji.json --- stack script --resolver lts-13.17 --package aeson --package bytestring --package text --package containers tools/emojis.hs < emoji.json - -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE OverloadedStrings #-} -import Data.Aeson -import qualified Data.ByteString.Lazy as B -import Data.Text (Text) -import Data.Map as M - -data Emoji = Emoji Text [Text] - deriving Show - -instance FromJSON Emoji where - parseJSON = withObject "Emoji" $ \v -> Emoji - <$> v .: "emoji" - <*> v .: "aliases" - -main :: IO () -main = do - bs <- B.getContents - case eitherDecode bs of - Left e -> error e - Right (emoji :: [Emoji]) -> do - let emojis = M.fromList $ - [(alias, txt) | Emoji txt aliases <- emoji, alias <- aliases] - putStrLn $ prettify $ dropWhile (/='[') $ show emojis - -prettify :: String -> String -prettify [] = "" -prettify ('[':xs) = '\n':' ':' ':'[':prettify xs -prettify (']':xs) = '\n':' ':' ':']':prettify xs -prettify (',':'(':xs) = '\n':' ':' ':',':'(':prettify xs -prettify (x:xs) = x:prettify xs -- cgit v1.2.3