aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Emoji/TH.hs
blob: bf3ed0c1602c65f09ad7d39cc912416f2fbe6ef9 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
{-# 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"