Use external emojis package.

Moved the emoji-specified code into an external package
we can depend on.
This commit is contained in:
John MacFarlane 2019-12-08 17:25:58 -08:00
parent 7f4154a8bb
commit 0bfe478a69
7 changed files with 10 additions and 10416 deletions

View file

@ -196,30 +196,3 @@ 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 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,9 +120,6 @@ download_stats:
curl https://api.github.com/repos/jgm/pandoc/releases | \
jq -r '.[] | .assets | .[] | "\(.download_count)\t\(.name)"'
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
emoji.json

File diff suppressed because it is too large Load diff

View file

@ -189,8 +189,6 @@ extra-source-files:
-- files needed to build man page
man/manfilter.lua
man/pandoc.1.template
-- data files used by TH
emoji.json
-- trypandoc
trypandoc/Makefile
trypandoc/index.html
@ -430,7 +428,7 @@ library
ipynb >= 0.1 && < 0.2,
attoparsec >= 0.12 && < 0.14,
text-conversions >= 0.3 && < 0.4,
template-haskell > 2
emojis >= 0.1 && < 0.2
if os(windows) && arch(i386)
build-depends: basement >= 0.0.10,
foundation >= 0.0.23
@ -465,7 +463,7 @@ library
-fhide-source-paths
default-language: Haskell2010
other-extensions: NoImplicitPrelude, TemplateHaskell
other-extensions: NoImplicitPrelude
hs-source-dirs: src
exposed-modules: Text.Pandoc,
@ -624,7 +622,6 @@ library
Text.Pandoc.UUID,
Text.Pandoc.Translations,
Text.Pandoc.Slides,
Text.Pandoc.Emoji.TH,
Paths_pandoc
autogen-modules: Paths_pandoc
buildable: True

View file

@ -14,14 +14,14 @@ Emoji symbol lookup from canonical string identifier.
-}
module Text.Pandoc.Emoji ( emojis, emojiToInline ) where
import Prelude
import qualified Data.Map as M
import qualified Data.Text as T
import qualified Text.Emoji as E
import Text.Pandoc.Definition (Inline (Span, Str))
import Text.Pandoc.Emoji.TH (genEmojis)
import Data.Text (Text)
import qualified Data.Map as M
emojis :: M.Map T.Text T.Text
emojis = M.fromList $(genEmojis "emoji.json")
emojis :: M.Map Text Text
emojis = M.fromList E.emojis
emojiToInline :: T.Text -> Maybe Inline
emojiToInline emojikey = makeSpan <$> M.lookup emojikey emojis
emojiToInline :: Text -> Maybe Inline
emojiToInline emojikey = makeSpan <$> E.emojiFromAlias emojikey
where makeSpan = Span ("", ["emoji"], [("data-emoji", emojikey)]) . (:[]) . Str

View file

@ -1,40 +0,0 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{- |
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]) -> [| emojis |]
where emojis = [ (alias, 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

@ -19,6 +19,7 @@ extra-deps:
- skylighting-core-0.8.3
- regex-pcre-builtin-0.95.0.8.8.35
- doclayout-0.2.0.1
- emojis-0.1
- HsYAML-0.2.0.0
- HsYAML-aeson-0.2.0.0
- doctemplates-0.8