diff options
author | John MacFarlane <jgm@berkeley.edu> | 2019-07-29 11:09:21 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2019-07-29 11:17:22 -0700 |
commit | c7c766440333cf5a2a1d54fd366e5c9aa9cf780b (patch) | |
tree | 59303ff755503049ef7bcd82096802d9617010ae /tools | |
parent | 82d94d1452d7f13d6cf5a86e937d3db44e4d4a45 (diff) | |
download | pandoc-c7c766440333cf5a2a1d54fd366e5c9aa9cf780b.tar.gz |
Update emoji list in Text.Pandoc.Emoji.
Done using tools/emojis.hs, which uses the list from the
gem GitHub uses. Future updates can be done with this tool.
Closes #5666.
Diffstat (limited to 'tools')
-rwxr-xr-x | tools/emojis.hs | 36 |
1 files changed, 36 insertions, 0 deletions
diff --git a/tools/emojis.hs b/tools/emojis.hs new file mode 100755 index 000000000..9926a9047 --- /dev/null +++ b/tools/emojis.hs @@ -0,0 +1,36 @@ +-- 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 |