diff options
author | John MacFarlane <jgm@berkeley.edu> | 2019-12-08 17:25:58 -0800 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2019-12-08 17:27:18 -0800 |
commit | 0bfe478a693451500528fc05c1e5f48f3ca1a55b (patch) | |
tree | 1b2c6f9cc737243b093ca1ec4ebfdcb04b888524 /src/Text/Pandoc/Emoji | |
parent | 7f4154a8bbeff772b778b60c75fe1081b3b9b5f1 (diff) | |
download | pandoc-0bfe478a693451500528fc05c1e5f48f3ca1a55b.tar.gz |
Use external emojis package.
Moved the emoji-specified code into an external package
we can depend on.
Diffstat (limited to 'src/Text/Pandoc/Emoji')
-rw-r--r-- | src/Text/Pandoc/Emoji/TH.hs | 40 |
1 files changed, 0 insertions, 40 deletions
diff --git a/src/Text/Pandoc/Emoji/TH.hs b/src/Text/Pandoc/Emoji/TH.hs deleted file mode 100644 index bf3ed0c16..000000000 --- a/src/Text/Pandoc/Emoji/TH.hs +++ /dev/null @@ -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" |