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.
This commit is contained in:
John MacFarlane 2019-11-27 21:27:46 -08:00
parent bd175d13b6
commit 0d0ec98dd5
7 changed files with 10410 additions and 1830 deletions

View file

@ -196,3 +196,30 @@ The file data/jats.csl is derived from a csl file by Martin Fenner,
revised by Martin Paul Eve and then John MacFarlane.
"This work is licensed under a Creative Commons Attribution-ShareAlike 3.0
License. Originally by Martin Fenner."
------------------------------------------------------------------------
The file data/emoji.json is derived from https://github.com/github/gemoji.
Copyright (c) 2019 GitHub, Inc.
Permission is hereby granted, free of charge, to any person
obtaining a copy of this software and associated documentation
files (the "Software"), to deal in the Software without
restriction, including without limitation the rights to use,
copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the
Software is furnished to do so, subject to the following
conditions:
The above copyright notice and this permission notice shall be
included in all copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
OTHER DEALINGS IN THE SOFTWARE.

View file

@ -120,6 +120,9 @@ download_stats:
curl https://api.github.com/repos/jgm/pandoc/releases | \
jq -r '.[] | .assets | .[] | "\(.download_count)\t\(.name)"'
data/emoji.json:
curl https://raw.githubusercontent.com/github/gemoji/master/db/emoji.json | jq '[.[] | {emoji: .emoji, aliases: .aliases}]' > $@
pandoc-templates:
rm ../pandoc-templates/default.* ; \
cp data/templates/default.* ../pandoc-templates/ ; \

10334
data/emoji.json Normal file

File diff suppressed because it is too large Load diff

View file

@ -427,7 +427,8 @@ library
doclayout >= 0.2.0.1 && < 0.3,
ipynb >= 0.1 && < 0.2,
attoparsec >= 0.12 && < 0.14,
text-conversions >= 0.3 && < 0.4
text-conversions >= 0.3 && < 0.4,
template-haskell > 2
if os(windows) && arch(i386)
build-depends: basement >= 0.0.10,
foundation >= 0.0.23
@ -621,6 +622,7 @@ library
Text.Pandoc.UUID,
Text.Pandoc.Translations,
Text.Pandoc.Slides,
Text.Pandoc.Emoji.TH,
Paths_pandoc
autogen-modules: Paths_pandoc
buildable: True

File diff suppressed because it is too large Load diff

View file

@ -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"

View file

@ -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