{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
#ifdef EMBED_DICTIONARY
{-# LANGUAGE TemplateHaskell #-}
#endif
-- | Provides higher-level APIs.  Read 'transformHtmlText' function first,
-- and then see also 'Configuration' type.
module Text.Seonbi.Facade
    ( -- * HTML transformation
      transformHtmlText
    , transformHtmlLazyText
      -- * Configuration and presets
    , Configuration (..)
    , ko_KP
    , ko_KR
    , presets
      -- * Content types
    , ContentType
    , contentTypeFromText
    , contentTypes
    , contentTypeText
      -- * Dictionaries
    , HanjaDictionary
    , readDictionaryFile
    , southKoreanDictionary
      -- * Options
    , ArrowOption (..)
    , CiteOption (..)
    , HanjaOption (..)
    , HanjaReadingOption (..)
    , HanjaRenderingOption (..)
    , QuoteOption (..)
    , StopOption (..)
    ) where

#if MIN_VERSION_base(4,13,0)
import Prelude hiding (MonadFail)
#endif

import Control.Monad.Fail (MonadFail)
import Data.Char
import Data.Kind (Type)
import Data.Maybe
import Data.String (IsString)
import GHC.Exts (IsList (toList))
import GHC.Generics (Generic)
import System.IO.Error
import System.IO.Unsafe

import Data.ByteString.Lazy
import Data.Csv
#ifdef EMBED_DICTIONARY
import Data.FileEmbed
#endif
import Data.Map.Strict
import Data.Set
import Data.Text
import qualified Data.Text.Lazy as LT
import System.FilePath
    ( (</>)
#ifdef EMBED_DICTIONARY
    , takeDirectory
#endif
    )

#ifndef EMBED_DICTIONARY
import Paths_seonbi (getDataDir)
#endif
import Text.Seonbi.ContentTypes
import Text.Seonbi.Hanja
import Text.Seonbi.Html
import Text.Seonbi.Punctuation
import Text.Seonbi.Trie as Trie

-- | Transformation settings.  For the most cases, you could use one of
-- presets:
--
-- - 'ko_KR'
-- - 'ko_KP'
data Monad m => Configuration m a = Configuration
    { -- | An optional debugging logger to print its internal AST.
      forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe (HtmlEntity -> m a)
debugLogger :: Maybe (HtmlEntity -> m a)
      -- | A content type of the input and output.  It has to be a member of
      -- 'contentTypes'.
    , forall (m :: * -> *) a. Monad m => Configuration m a -> ContentType
contentType :: ContentType
      -- | An option to decide how quotation marks are rendered.
      -- If 'Nothing' no quotes are transformed.
    , forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe QuoteOption
quote :: Maybe QuoteOption
      -- | An option to transform folk-citing quotes (e.g., @\<\<한겨레\>\>@)
      -- into proper citing quotes (e.g., @《한겨레》@).
    , forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe CiteOption
cite :: Maybe CiteOption
      -- | Settings to transform arrow-looking punctuations into proper arrows.
      -- If 'Nothing' no arrows are transformed.
    , forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe ArrowOption
arrow :: Maybe ArrowOption
      -- | Whether to transform triple periods into a proper ellipsis.
    , forall (m :: * -> *) a. Monad m => Configuration m a -> Bool
ellipsis :: Bool
      -- | Whether to transform folk em dashes into proper em dashes.
    , forall (m :: * -> *) a. Monad m => Configuration m a -> Bool
emDash :: Bool
      -- | Settings to normalize stops (periods, commas, and interpuncts).
      -- If 'Nothing' stops are never touched.
    , forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe StopOption
stop :: Maybe StopOption
      -- | Settings to deal with Sino-Korean words.
    , forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe HanjaOption
hanja :: Maybe HanjaOption
    }

instance Monad m => Show (Configuration m a) where
    show :: Configuration m a -> String
show Configuration m a
c = String
"Configuration {\n" forall a. Semigroup a => a -> a -> a
<>
        String
"  debugLogger = " forall a. Semigroup a => a -> a -> a
<>
            forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"Nothing" (forall a b. a -> b -> a
const String
"Just ...") (forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe (HtmlEntity -> m a)
debugLogger Configuration m a
c) forall a. Semigroup a => a -> a -> a
<> String
"," forall a. Semigroup a => a -> a -> a
<>
        String
"  contentType = " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (forall (m :: * -> *) a. Monad m => Configuration m a -> ContentType
contentType Configuration m a
c) forall a. Semigroup a => a -> a -> a
<> String
"," forall a. Semigroup a => a -> a -> a
<>
        String
"  quote = " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe QuoteOption
quote Configuration m a
c) forall a. Semigroup a => a -> a -> a
<> String
"," forall a. Semigroup a => a -> a -> a
<>
        String
"  arrow = " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe CiteOption
cite Configuration m a
c) forall a. Semigroup a => a -> a -> a
<> String
"," forall a. Semigroup a => a -> a -> a
<>
        String
"  cite = " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe ArrowOption
arrow Configuration m a
c) forall a. Semigroup a => a -> a -> a
<> String
"," forall a. Semigroup a => a -> a -> a
<>
        String
"  ellipsis = " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (forall (m :: * -> *) a. Monad m => Configuration m a -> Bool
ellipsis Configuration m a
c) forall a. Semigroup a => a -> a -> a
<> String
"," forall a. Semigroup a => a -> a -> a
<>
        String
"  emDash = " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (forall (m :: * -> *) a. Monad m => Configuration m a -> Bool
emDash Configuration m a
c) forall a. Semigroup a => a -> a -> a
<> String
"," forall a. Semigroup a => a -> a -> a
<>
        String
"  stop = " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe StopOption
stop Configuration m a
c) forall a. Semigroup a => a -> a -> a
<> String
"," forall a. Semigroup a => a -> a -> a
<>
        String
"  hanja = " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe HanjaOption
hanja Configuration m a
c) forall a. Semigroup a => a -> a -> a
<>
        String
"}"

-- | An option to decide how quotation marks are rendered.
data QuoteOption
    -- | English-style curved quotes (@‘@: U+2018, @’@: U+2019, @“@: U+201C,
    -- @”@: U+201D), which are used by South Korean orthography.
    = CurvedQuotes
    -- | Vertical corner brackets (@﹁@: U+FE41, @﹂@: U+FE42, @﹃@: U+FE43,
    -- @﹄@: U+FE44), which are used by East Asian orthography.
    | VerticalCornerBrackets
    -- | Traditional horizontal corner brackets (@「@: U+300C, @」@: U+300D,
    -- @『@: U+300E, @』@: U+300F), which are used by East Asian orthography.
    | HorizontalCornerBrackets
    -- | East Asian guillemets (@〈@: U+3008, @〉@: U+3009, @《@: U+300A, @》@:
    -- U+300B), which are used by North Korean orthography.
    | Guillemets
    -- | Use English-style curved quotes (@‘@: U+2018, @’@: U+2019) for single
    -- quotes, and HTML @\<q\>@ tags for double quotes.
    | CurvedSingleQuotesWithQ
    -- | Use vertical corner brackets (@﹁@: U+FE41, @﹂@: U+FE42)
    -- for single quotes, and HTML @\<q\>@ tags for double quotes.
    | VerticalCornerBracketsWithQ
    -- | Use horizontal corner brackets (@「@: U+300C, @」@: U+300D)
    -- for single quotes, and HTML @\<q\>@ tags for double quotes.
    | HorizontalCornerBracketsWithQ
    deriving (Int -> QuoteOption
QuoteOption -> Int
QuoteOption -> [QuoteOption]
QuoteOption -> QuoteOption
QuoteOption -> QuoteOption -> [QuoteOption]
QuoteOption -> QuoteOption -> QuoteOption -> [QuoteOption]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: QuoteOption -> QuoteOption -> QuoteOption -> [QuoteOption]
$cenumFromThenTo :: QuoteOption -> QuoteOption -> QuoteOption -> [QuoteOption]
enumFromTo :: QuoteOption -> QuoteOption -> [QuoteOption]
$cenumFromTo :: QuoteOption -> QuoteOption -> [QuoteOption]
enumFromThen :: QuoteOption -> QuoteOption -> [QuoteOption]
$cenumFromThen :: QuoteOption -> QuoteOption -> [QuoteOption]
enumFrom :: QuoteOption -> [QuoteOption]
$cenumFrom :: QuoteOption -> [QuoteOption]
fromEnum :: QuoteOption -> Int
$cfromEnum :: QuoteOption -> Int
toEnum :: Int -> QuoteOption
$ctoEnum :: Int -> QuoteOption
pred :: QuoteOption -> QuoteOption
$cpred :: QuoteOption -> QuoteOption
succ :: QuoteOption -> QuoteOption
$csucc :: QuoteOption -> QuoteOption
Enum, QuoteOption -> QuoteOption -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QuoteOption -> QuoteOption -> Bool
$c/= :: QuoteOption -> QuoteOption -> Bool
== :: QuoteOption -> QuoteOption -> Bool
$c== :: QuoteOption -> QuoteOption -> Bool
Eq, forall x. Rep QuoteOption x -> QuoteOption
forall x. QuoteOption -> Rep QuoteOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QuoteOption x -> QuoteOption
$cfrom :: forall x. QuoteOption -> Rep QuoteOption x
Generic, ReadPrec [QuoteOption]
ReadPrec QuoteOption
Int -> ReadS QuoteOption
ReadS [QuoteOption]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [QuoteOption]
$creadListPrec :: ReadPrec [QuoteOption]
readPrec :: ReadPrec QuoteOption
$creadPrec :: ReadPrec QuoteOption
readList :: ReadS [QuoteOption]
$creadList :: ReadS [QuoteOption]
readsPrec :: Int -> ReadS QuoteOption
$creadsPrec :: Int -> ReadS QuoteOption
Read, Int -> QuoteOption -> ShowS
[QuoteOption] -> ShowS
QuoteOption -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QuoteOption] -> ShowS
$cshowList :: [QuoteOption] -> ShowS
show :: QuoteOption -> String
$cshow :: QuoteOption -> String
showsPrec :: Int -> QuoteOption -> ShowS
$cshowsPrec :: Int -> QuoteOption -> ShowS
Show)

-- | An option to transform folk-citing quotes (e.g., @\<\<한겨레\>\>@) into
-- proper citing quotes (e.g., @《한겨레》@).
data CiteOption
    -- | Cite a title using angle quotes, used by South Korean orthography in
    -- horizontal writing (橫書), e.g., 《나비와 엉겅퀴》 or 〈枾崎의 바다〉.
    = AngleQuotes
    -- | Cite a title using corner brackets, used by South Korean orthography in
    -- vertical writing (縱書) and Japanese orthography,
    -- e.g., 『나비와 엉겅퀴』 or 「枾崎의 바다」.
    | CornerBrackets
    -- | Same as 'AngleQuotes' except it wraps the title with a @\<cite\>@ tag.
    | AngleQuotesWithCite
    -- | Same as 'CornerBrackets' except it wraps the title with
    -- a @\<cite\>@ tag.
    | CornerBracketsWithCite
    deriving (Int -> CiteOption
CiteOption -> Int
CiteOption -> [CiteOption]
CiteOption -> CiteOption
CiteOption -> CiteOption -> [CiteOption]
CiteOption -> CiteOption -> CiteOption -> [CiteOption]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CiteOption -> CiteOption -> CiteOption -> [CiteOption]
$cenumFromThenTo :: CiteOption -> CiteOption -> CiteOption -> [CiteOption]
enumFromTo :: CiteOption -> CiteOption -> [CiteOption]
$cenumFromTo :: CiteOption -> CiteOption -> [CiteOption]
enumFromThen :: CiteOption -> CiteOption -> [CiteOption]
$cenumFromThen :: CiteOption -> CiteOption -> [CiteOption]
enumFrom :: CiteOption -> [CiteOption]
$cenumFrom :: CiteOption -> [CiteOption]
fromEnum :: CiteOption -> Int
$cfromEnum :: CiteOption -> Int
toEnum :: Int -> CiteOption
$ctoEnum :: Int -> CiteOption
pred :: CiteOption -> CiteOption
$cpred :: CiteOption -> CiteOption
succ :: CiteOption -> CiteOption
$csucc :: CiteOption -> CiteOption
Enum, CiteOption -> CiteOption -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CiteOption -> CiteOption -> Bool
$c/= :: CiteOption -> CiteOption -> Bool
== :: CiteOption -> CiteOption -> Bool
$c== :: CiteOption -> CiteOption -> Bool
Eq, forall x. Rep CiteOption x -> CiteOption
forall x. CiteOption -> Rep CiteOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CiteOption x -> CiteOption
$cfrom :: forall x. CiteOption -> Rep CiteOption x
Generic, ReadPrec [CiteOption]
ReadPrec CiteOption
Int -> ReadS CiteOption
ReadS [CiteOption]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CiteOption]
$creadListPrec :: ReadPrec [CiteOption]
readPrec :: ReadPrec CiteOption
$creadPrec :: ReadPrec CiteOption
readList :: ReadS [CiteOption]
$creadList :: ReadS [CiteOption]
readsPrec :: Int -> ReadS CiteOption
$creadsPrec :: Int -> ReadS CiteOption
Read, Int -> CiteOption -> ShowS
[CiteOption] -> ShowS
CiteOption -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CiteOption] -> ShowS
$cshowList :: [CiteOption] -> ShowS
show :: CiteOption -> String
$cshow :: CiteOption -> String
showsPrec :: Int -> CiteOption -> ShowS
$cshowsPrec :: Int -> CiteOption -> ShowS
Show)

-- | Settings to transform arrow-looking punctuations into proper arrows.
data ArrowOption = ArrowOption
    { -- | Whether to transform bi-directional arrows as well as
      -- left/rightwards arrows.
      ArrowOption -> Bool
bidirArrow :: Bool
      -- | Whether to transform double arrows as well as single arrows.
    , ArrowOption -> Bool
doubleArrow :: Bool
    } deriving (ArrowOption -> ArrowOption -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrowOption -> ArrowOption -> Bool
$c/= :: ArrowOption -> ArrowOption -> Bool
== :: ArrowOption -> ArrowOption -> Bool
$c== :: ArrowOption -> ArrowOption -> Bool
Eq, forall x. Rep ArrowOption x -> ArrowOption
forall x. ArrowOption -> Rep ArrowOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ArrowOption x -> ArrowOption
$cfrom :: forall x. ArrowOption -> Rep ArrowOption x
Generic, Int -> ArrowOption -> ShowS
[ArrowOption] -> ShowS
ArrowOption -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ArrowOption] -> ShowS
$cshowList :: [ArrowOption] -> ShowS
show :: ArrowOption -> String
$cshow :: ArrowOption -> String
showsPrec :: Int -> ArrowOption -> ShowS
$cshowsPrec :: Int -> ArrowOption -> ShowS
Show)

-- | Settings to normalize stops (periods, commas, and interpuncts) in docs.
data StopOption
    -- | Stop sentences in the modern Korean style which follows Western stops.
    -- E.g.:
    --
    -- > 봄·여름·가을·겨울. 어제, 오늘.
    = Horizontal
    -- | Similar to 'horizontalStops' except slashes are used instead of
    -- interpuncts. E.g.:
    --
    -- > 봄/여름/가을/겨울. 어제, 오늘.
    | HorizontalWithSlashes
    -- | Stop sentences in the pre-modern Korean style which follows Chinese
    -- stops.  E.g.:
    --
    -- > 봄·여름·가을·겨울。어제、오늘。
    | Vertical
    deriving (Int -> StopOption
StopOption -> Int
StopOption -> [StopOption]
StopOption -> StopOption
StopOption -> StopOption -> [StopOption]
StopOption -> StopOption -> StopOption -> [StopOption]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: StopOption -> StopOption -> StopOption -> [StopOption]
$cenumFromThenTo :: StopOption -> StopOption -> StopOption -> [StopOption]
enumFromTo :: StopOption -> StopOption -> [StopOption]
$cenumFromTo :: StopOption -> StopOption -> [StopOption]
enumFromThen :: StopOption -> StopOption -> [StopOption]
$cenumFromThen :: StopOption -> StopOption -> [StopOption]
enumFrom :: StopOption -> [StopOption]
$cenumFrom :: StopOption -> [StopOption]
fromEnum :: StopOption -> Int
$cfromEnum :: StopOption -> Int
toEnum :: Int -> StopOption
$ctoEnum :: Int -> StopOption
pred :: StopOption -> StopOption
$cpred :: StopOption -> StopOption
succ :: StopOption -> StopOption
$csucc :: StopOption -> StopOption
Enum, StopOption -> StopOption -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopOption -> StopOption -> Bool
$c/= :: StopOption -> StopOption -> Bool
== :: StopOption -> StopOption -> Bool
$c== :: StopOption -> StopOption -> Bool
Eq, forall x. Rep StopOption x -> StopOption
forall x. StopOption -> Rep StopOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopOption x -> StopOption
$cfrom :: forall x. StopOption -> Rep StopOption x
Generic, ReadPrec [StopOption]
ReadPrec StopOption
Int -> ReadS StopOption
ReadS [StopOption]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopOption]
$creadListPrec :: ReadPrec [StopOption]
readPrec :: ReadPrec StopOption
$creadPrec :: ReadPrec StopOption
readList :: ReadS [StopOption]
$creadList :: ReadS [StopOption]
readsPrec :: Int -> ReadS StopOption
$creadsPrec :: Int -> ReadS StopOption
Read, Int -> StopOption -> ShowS
[StopOption] -> ShowS
StopOption -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopOption] -> ShowS
$cshowList :: [StopOption] -> ShowS
show :: StopOption -> String
$cshow :: StopOption -> String
showsPrec :: Int -> StopOption -> ShowS
$cshowsPrec :: Int -> StopOption -> ShowS
Show)

-- | Settings to deal with Sino-Korean words.
data HanjaOption = HanjaOption
    { -- | How to render Sino-Korean words.
      HanjaOption -> HanjaRenderingOption
rendering :: HanjaRenderingOption
      -- | How to rewrite Sino-Korean words in hangul.
    , HanjaOption -> HanjaReadingOption
reading :: HanjaReadingOption
    } deriving (Int -> HanjaOption -> ShowS
[HanjaOption] -> ShowS
HanjaOption -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HanjaOption] -> ShowS
$cshowList :: [HanjaOption] -> ShowS
show :: HanjaOption -> String
$cshow :: HanjaOption -> String
showsPrec :: Int -> HanjaOption -> ShowS
$cshowsPrec :: Int -> HanjaOption -> ShowS
Show)

-- | Available options to render Sino-Korean words.
data HanjaRenderingOption
    -- | Renders a word in hangul-only, no hanja at all (e.g., @안녕히@).
    = HangulOnly
    -- | Renders a word in hangul followed by hanja in parentheses
    -- (e.g., @안녕(安寧)히@).
    | HanjaInParentheses
    -- | Renders words in hangul-only for the most part, and if there are
    -- homophones in a document put their hanja notation in parentheses
    -- (e.g., @안녕히@ or @소수(小數)와 소수(素數)@).
    | DisambiguatingHanjaInParentheses
    -- | Renders a word in @<ruby>@ tag (e.g.,
    -- @\<ruby\>安寧\<rp\>(\<\/rp\>\<rt\>안녕\<\/rt\>\<rp\>)\<\/rp\>\<\/ruby\>히@).
    --
    -- Please read [Use Cases & Exploratory Approaches for Ruby
    -- Markup](https://www.w3.org/TR/ruby-use-cases/) as well for more
    -- information.
    | HanjaInRuby
    deriving (Int -> HanjaRenderingOption
HanjaRenderingOption -> Int
HanjaRenderingOption -> [HanjaRenderingOption]
HanjaRenderingOption -> HanjaRenderingOption
HanjaRenderingOption
-> HanjaRenderingOption -> [HanjaRenderingOption]
HanjaRenderingOption
-> HanjaRenderingOption
-> HanjaRenderingOption
-> [HanjaRenderingOption]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: HanjaRenderingOption
-> HanjaRenderingOption
-> HanjaRenderingOption
-> [HanjaRenderingOption]
$cenumFromThenTo :: HanjaRenderingOption
-> HanjaRenderingOption
-> HanjaRenderingOption
-> [HanjaRenderingOption]
enumFromTo :: HanjaRenderingOption
-> HanjaRenderingOption -> [HanjaRenderingOption]
$cenumFromTo :: HanjaRenderingOption
-> HanjaRenderingOption -> [HanjaRenderingOption]
enumFromThen :: HanjaRenderingOption
-> HanjaRenderingOption -> [HanjaRenderingOption]
$cenumFromThen :: HanjaRenderingOption
-> HanjaRenderingOption -> [HanjaRenderingOption]
enumFrom :: HanjaRenderingOption -> [HanjaRenderingOption]
$cenumFrom :: HanjaRenderingOption -> [HanjaRenderingOption]
fromEnum :: HanjaRenderingOption -> Int
$cfromEnum :: HanjaRenderingOption -> Int
toEnum :: Int -> HanjaRenderingOption
$ctoEnum :: Int -> HanjaRenderingOption
pred :: HanjaRenderingOption -> HanjaRenderingOption
$cpred :: HanjaRenderingOption -> HanjaRenderingOption
succ :: HanjaRenderingOption -> HanjaRenderingOption
$csucc :: HanjaRenderingOption -> HanjaRenderingOption
Enum, HanjaRenderingOption -> HanjaRenderingOption -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HanjaRenderingOption -> HanjaRenderingOption -> Bool
$c/= :: HanjaRenderingOption -> HanjaRenderingOption -> Bool
== :: HanjaRenderingOption -> HanjaRenderingOption -> Bool
$c== :: HanjaRenderingOption -> HanjaRenderingOption -> Bool
Eq, forall x. Rep HanjaRenderingOption x -> HanjaRenderingOption
forall x. HanjaRenderingOption -> Rep HanjaRenderingOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HanjaRenderingOption x -> HanjaRenderingOption
$cfrom :: forall x. HanjaRenderingOption -> Rep HanjaRenderingOption x
Generic, ReadPrec [HanjaRenderingOption]
ReadPrec HanjaRenderingOption
Int -> ReadS HanjaRenderingOption
ReadS [HanjaRenderingOption]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HanjaRenderingOption]
$creadListPrec :: ReadPrec [HanjaRenderingOption]
readPrec :: ReadPrec HanjaRenderingOption
$creadPrec :: ReadPrec HanjaRenderingOption
readList :: ReadS [HanjaRenderingOption]
$creadList :: ReadS [HanjaRenderingOption]
readsPrec :: Int -> ReadS HanjaRenderingOption
$creadsPrec :: Int -> ReadS HanjaRenderingOption
Read, Int -> HanjaRenderingOption -> ShowS
[HanjaRenderingOption] -> ShowS
HanjaRenderingOption -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HanjaRenderingOption] -> ShowS
$cshowList :: [HanjaRenderingOption] -> ShowS
show :: HanjaRenderingOption -> String
$cshow :: HanjaRenderingOption -> String
showsPrec :: Int -> HanjaRenderingOption -> ShowS
$cshowsPrec :: Int -> HanjaRenderingOption -> ShowS
Show)

-- | Settings to read Sino-Korean words.
data HanjaReadingOption = HanjaReadingOption
    { -- | Whether to apply Initial Sound Law (頭音法則) or not.
      HanjaReadingOption -> Bool
initialSoundLaw :: Bool
      -- | A dictionary which has hanja readings.  Keys are
      -- hanja words and values are their corresponding hangul readings,
      -- e.g.:
      --
      -- > [("敗北", "패배"), ("北極", "북극")] :: HanjaDictionary
    , HanjaReadingOption -> HanjaDictionary
dictionary :: HanjaDictionary
    }

instance Show HanjaReadingOption where
    show :: HanjaReadingOption -> String
show HanjaReadingOption { HanjaDictionary
dictionary :: HanjaDictionary
dictionary :: HanjaReadingOption -> HanjaDictionary
dictionary, Bool
initialSoundLaw :: Bool
initialSoundLaw :: HanjaReadingOption -> Bool
initialSoundLaw } =
        String
"HanjaReadingOption {" forall a. Semigroup a => a -> a -> a
<>
        String
" dictionary = [" forall a. Semigroup a => a -> a -> a
<>
        forall a. Show a => a -> String
show (forall a. Trie a -> Int
Trie.size HanjaDictionary
dictionary) forall a. Semigroup a => a -> a -> a
<>
        String
" words]," forall a. Semigroup a => a -> a -> a
<>
        String
" initialSoundLaw = " forall a. Semigroup a => a -> a -> a
<>
        forall a. Show a => a -> String
show Bool
initialSoundLaw forall a. Semigroup a => a -> a -> a
<>
        String
" }"

-- | Transforms a given text.  'Nothing' if it fails to parse the given
-- text.
transformHtmlText :: forall (m :: Type -> Type) a. (Monad m, MonadFail m)
                  => Configuration m a -> Text -> m Text
transformHtmlText :: forall (m :: * -> *) a.
(Monad m, MonadFail m) =>
Configuration m a -> Text -> m Text
transformHtmlText Configuration m a
config =
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
LT.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
(Monad m, MonadFail m) =>
Configuration m a -> Text -> m Text
transformHtmlLazyText Configuration m a
config forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
LT.fromStrict

-- | A lazy version of 'transformHtmlText' function.
transformHtmlLazyText :: forall (m :: Type -> Type) a. (Monad m, MonadFail m)
                      => Configuration m a -> LT.Text -> m LT.Text
transformHtmlLazyText :: forall (m :: * -> *) a.
(Monad m, MonadFail m) =>
Configuration m a -> Text -> m Text
transformHtmlLazyText config :: Configuration m a
config@Configuration { ContentType
contentType :: ContentType
contentType :: forall (m :: * -> *) a. Monad m => Configuration m a -> ContentType
contentType, Maybe (HtmlEntity -> m a)
debugLogger :: Maybe (HtmlEntity -> m a)
debugLogger :: forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe (HtmlEntity -> m a)
debugLogger } =
    forall (m :: * -> *).
(Monad m, MonadFail m) =>
ContentType -> HtmlTransformer m -> Text -> m Text
transformWithContentType ContentType
contentType [HtmlEntity] -> m [HtmlEntity]
transformerM
  where
    transformer :: [HtmlEntity] -> [HtmlEntity]
    transformer :: [HtmlEntity] -> [HtmlEntity]
transformer = forall (m :: * -> *) a.
Monad m =>
Configuration m a -> [HtmlEntity] -> [HtmlEntity]
toTransformer Configuration m a
config
    transformerM :: [HtmlEntity] -> m [HtmlEntity]
transformerM = case Maybe (HtmlEntity -> m a)
debugLogger of
        Maybe (HtmlEntity -> m a)
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [HtmlEntity] -> [HtmlEntity]
transformer
        Just HtmlEntity -> m a
logger -> \ [HtmlEntity]
input -> do
            forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ HtmlEntity -> m a
logger [HtmlEntity]
input
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [HtmlEntity] -> [HtmlEntity]
transformer [HtmlEntity]
input

toTransformers :: Monad m => Configuration m a -> [[HtmlEntity] -> [HtmlEntity]]
toTransformers :: forall (m :: * -> *) a.
Monad m =>
Configuration m a -> [[HtmlEntity] -> [HtmlEntity]]
toTransformers Configuration { Maybe QuoteOption
quote :: Maybe QuoteOption
quote :: forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe QuoteOption
quote
                             , Maybe CiteOption
cite :: Maybe CiteOption
cite :: forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe CiteOption
cite
                             , Maybe ArrowOption
arrow :: Maybe ArrowOption
arrow :: forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe ArrowOption
arrow
                             , Bool
ellipsis :: Bool
ellipsis :: forall (m :: * -> *) a. Monad m => Configuration m a -> Bool
ellipsis
                             , Bool
emDash :: Bool
emDash :: forall (m :: * -> *) a. Monad m => Configuration m a -> Bool
emDash
                             , Maybe StopOption
stop :: Maybe StopOption
stop :: forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe StopOption
stop
                             , Maybe HanjaOption
hanja :: Maybe HanjaOption
hanja :: forall (m :: * -> *) a.
Monad m =>
Configuration m a -> Maybe HanjaOption
hanja
                             } =
    [ case Maybe QuoteOption
quote of
        Maybe QuoteOption
Nothing -> forall a. a -> a
id
        Just QuoteOption
quoteOption -> Quotes -> [HtmlEntity] -> [HtmlEntity]
transformQuote forall a b. (a -> b) -> a -> b
$
            case QuoteOption
quoteOption of
                QuoteOption
CurvedQuotes -> Quotes
curvedQuotes
                QuoteOption
Guillemets -> Quotes
guillemets
                QuoteOption
VerticalCornerBrackets -> Quotes
verticalCornerBrackets
                QuoteOption
HorizontalCornerBrackets -> Quotes
horizontalCornerBrackets
                QuoteOption
CurvedSingleQuotesWithQ -> Quotes
curvedSingleQuotesWithQ
                QuoteOption
VerticalCornerBracketsWithQ -> Quotes
verticalCornerBracketsWithQ
                QuoteOption
HorizontalCornerBracketsWithQ -> Quotes
horizontalCornerBracketsWithQ
    , case Maybe CiteOption
cite of
        Maybe CiteOption
Nothing -> forall a. a -> a
id
        Just CiteOption
citeOption -> CitationQuotes -> [HtmlEntity] -> [HtmlEntity]
quoteCitation forall a b. (a -> b) -> a -> b
$
            case CiteOption
citeOption of
                CiteOption
AngleQuotes -> CitationQuotes
angleQuotes { htmlElement :: Maybe (HtmlTag, Text)
htmlElement = forall a. Maybe a
Nothing }
                CiteOption
CornerBrackets -> CitationQuotes
cornerBrackets { htmlElement :: Maybe (HtmlTag, Text)
htmlElement = forall a. Maybe a
Nothing }
                CiteOption
AngleQuotesWithCite -> CitationQuotes
angleQuotes
                CiteOption
CornerBracketsWithCite -> CitationQuotes
cornerBrackets
    , case Maybe ArrowOption
arrow of
        Maybe ArrowOption
Nothing -> forall a. a -> a
id
        Just ArrowOption { Bool
bidirArrow :: Bool
bidirArrow :: ArrowOption -> Bool
bidirArrow, Bool
doubleArrow :: Bool
doubleArrow :: ArrowOption -> Bool
doubleArrow } -> Set ArrowTransformationOption -> [HtmlEntity] -> [HtmlEntity]
transformArrow forall a b. (a -> b) -> a -> b
$
            forall a. Ord a => [a] -> Set a
Data.Set.fromList forall a b. (a -> b) -> a -> b
$ forall a. [Maybe a] -> [a]
catMaybes
                [ if Bool
bidirArrow then forall a. a -> Maybe a
Just ArrowTransformationOption
LeftRight else forall a. Maybe a
Nothing
                , if Bool
doubleArrow then forall a. a -> Maybe a
Just ArrowTransformationOption
DoubleArrow else forall a. Maybe a
Nothing
                ]
    , case Maybe StopOption
stop of
        Maybe StopOption
Nothing -> forall a. a -> a
id
        Just StopOption
stopOption -> Stops -> [HtmlEntity] -> [HtmlEntity]
normalizeStops forall a b. (a -> b) -> a -> b
$
            case StopOption
stopOption of
                StopOption
Horizontal -> Stops
horizontalStops
                StopOption
HorizontalWithSlashes -> Stops
horizontalStopsWithSlashes
                StopOption
Vertical -> Stops
verticalStops
    , if Bool
ellipsis then [HtmlEntity] -> [HtmlEntity]
transformEllipsis else forall a. a -> a
id
    , if Bool
emDash then [HtmlEntity] -> [HtmlEntity]
transformEmDash else forall a. a -> a
id
    , case Maybe HanjaOption
hanja of
        Maybe HanjaOption
Nothing ->
            forall a. a -> a
id
        Just HanjaOption
                { HanjaRenderingOption
rendering :: HanjaRenderingOption
rendering :: HanjaOption -> HanjaRenderingOption
rendering
                , reading :: HanjaOption -> HanjaReadingOption
reading = HanjaReadingOption { Bool
initialSoundLaw :: Bool
initialSoundLaw :: HanjaReadingOption -> Bool
initialSoundLaw, HanjaDictionary
dictionary :: HanjaDictionary
dictionary :: HanjaReadingOption -> HanjaDictionary
dictionary }
                } ->
            HanjaPhoneticization -> [HtmlEntity] -> [HtmlEntity]
phoneticizeHanja forall a b. (a -> b) -> a -> b
$ forall a. Default a => a
def
                { phoneticizer :: HanjaWordPhoneticizer
phoneticizer =
                    let withDict :: HanjaWordPhoneticizer -> HanjaWordPhoneticizer
withDict = if forall a. Trie a -> Bool
Trie.null HanjaDictionary
dictionary
                            then forall a. a -> a
id
                            else HanjaDictionary -> HanjaWordPhoneticizer -> HanjaWordPhoneticizer
withDictionary HanjaDictionary
dictionary
                        phoneticize :: HanjaWordPhoneticizer
phoneticize = if Bool
initialSoundLaw
                            then HanjaWordPhoneticizer
phoneticizeHanjaWordWithInitialSoundLaw
                            else HanjaWordPhoneticizer
phoneticizeHanjaWord
                    in
                        HanjaWordPhoneticizer -> HanjaWordPhoneticizer
withDict HanjaWordPhoneticizer
phoneticize
                , wordRenderer :: HanjaWordRenderer
wordRenderer = case HanjaRenderingOption
rendering of
                    HanjaRenderingOption
HangulOnly -> HanjaWordRenderer
hangulOnly
                    HanjaRenderingOption
HanjaInParentheses -> HanjaWordRenderer
hanjaInParentheses
                    HanjaRenderingOption
DisambiguatingHanjaInParentheses -> HanjaWordRenderer
hangulOnly
                    HanjaRenderingOption
HanjaInRuby -> HanjaWordRenderer
hanjaInRuby
                , homophoneRenderer :: HanjaWordRenderer
homophoneRenderer = case HanjaRenderingOption
rendering of
                    HanjaRenderingOption
HangulOnly -> HanjaWordRenderer
hangulOnly
                    HanjaRenderingOption
HanjaInParentheses -> HanjaWordRenderer
hanjaInParentheses
                    HanjaRenderingOption
DisambiguatingHanjaInParentheses -> HanjaWordRenderer
hanjaInParentheses
                    HanjaRenderingOption
HanjaInRuby -> HanjaWordRenderer
hanjaInRuby
                }
    ]

toTransformer :: Monad m => Configuration m a -> [HtmlEntity] -> [HtmlEntity]
toTransformer :: forall (m :: * -> *) a.
Monad m =>
Configuration m a -> [HtmlEntity] -> [HtmlEntity]
toTransformer =
    forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Prelude.foldl forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall a. a -> a
id forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
Monad m =>
Configuration m a -> [[HtmlEntity] -> [HtmlEntity]]
toTransformers

-- | Preset 'Configuration' for South Korean orthography.
ko_KR :: Monad m => Configuration m a
ko_KR :: forall (m :: * -> *) a. Monad m => Configuration m a
ko_KR = Configuration
    { debugLogger :: Maybe (HtmlEntity -> m a)
debugLogger = forall a. Maybe a
Nothing
    , quote :: Maybe QuoteOption
quote = forall a. a -> Maybe a
Just QuoteOption
CurvedQuotes
    , cite :: Maybe CiteOption
cite = forall a. a -> Maybe a
Just CiteOption
AngleQuotes
    , arrow :: Maybe ArrowOption
arrow = forall a. a -> Maybe a
Just ArrowOption { bidirArrow :: Bool
bidirArrow = Bool
True, doubleArrow :: Bool
doubleArrow = Bool
True }
    , ellipsis :: Bool
ellipsis = Bool
True
    , emDash :: Bool
emDash = Bool
True
    , stop :: Maybe StopOption
stop = forall a. a -> Maybe a
Just StopOption
Horizontal
    , hanja :: Maybe HanjaOption
hanja = forall a. a -> Maybe a
Just HanjaOption
        { rendering :: HanjaRenderingOption
rendering = HanjaRenderingOption
DisambiguatingHanjaInParentheses
        , reading :: HanjaReadingOption
reading = HanjaReadingOption
            { dictionary :: HanjaDictionary
dictionary = HanjaDictionary
southKoreanDictionaryUnsafe
            , initialSoundLaw :: Bool
initialSoundLaw = Bool
True
            }
        }
    , contentType :: ContentType
contentType = ContentType
"text/html"
    }

-- | Preset 'Configuration' for North Korean orthography.
ko_KP :: Monad m => Configuration m a
ko_KP :: forall (m :: * -> *) a. Monad m => Configuration m a
ko_KP = forall (m :: * -> *) a. Monad m => Configuration m a
ko_KR
    { quote :: Maybe QuoteOption
quote = forall a. a -> Maybe a
Just QuoteOption
Guillemets
    , hanja :: Maybe HanjaOption
hanja = forall a. a -> Maybe a
Just HanjaOption
        { rendering :: HanjaRenderingOption
rendering = HanjaRenderingOption
HangulOnly
        , reading :: HanjaReadingOption
reading = HanjaReadingOption
            { dictionary :: HanjaDictionary
dictionary = []
            , initialSoundLaw :: Bool
initialSoundLaw = Bool
False
            }
        }
    }

-- | A mapping of locale code strings (e.g., @"ko-kr"@) to the corresponding
-- 'Configuration' presets (e.g., 'ko_KR').
presets :: (Ord k, IsString k, Monad m) => Map k (Configuration m a)
presets :: forall k (m :: * -> *) a.
(Ord k, IsString k, Monad m) =>
Map k (Configuration m a)
presets =
    [ (k
"ko-kp", forall (m :: * -> *) a. Monad m => Configuration m a
ko_KP)
    , (k
"ko-kr", forall (m :: * -> *) a. Monad m => Configuration m a
ko_KR)
    ]

-- | Loads a dictionary file.  The file consists of two-column TSV
-- (tab-separated values); the first column is hanja and the second column is
-- hangul.
readDictionaryFile :: FilePath -> IO HanjaDictionary
readDictionaryFile :: String -> IO HanjaDictionary
readDictionaryFile String
path = do
    ByteString
byteString <- String -> IO ByteString
Data.ByteString.Lazy.readFile String
path
    case ByteString -> Either String HanjaDictionary
readDictionaryByteString ByteString
byteString of
        Right HanjaDictionary
dic -> forall (m :: * -> *) a. Monad m => a -> m a
return HanjaDictionary
dic
        Left String
err -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
err

-- | Reads a dictionary from TSV bytes.
readDictionaryByteString :: Data.ByteString.Lazy.ByteString
                         -> Either String HanjaDictionary
readDictionaryByteString :: ByteString -> Either String HanjaDictionary
readDictionaryByteString ByteString
byteString =
    case forall a.
FromRecord a =>
DecodeOptions
-> HasHeader -> ByteString -> Either String (Vector a)
decodeWith DecodeOptions
tsvDecodeOptions HasHeader
NoHeader ByteString
byteString of
        Right Vector DictionaryPair
vector -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Prelude.foldl
            (\ HanjaDictionary
d (DictionaryPair Text
k Text
v) -> forall a. Text -> a -> Trie a -> Trie a
Trie.insert Text
k Text
v HanjaDictionary
d)
            forall a. Trie a
Trie.empty
            (forall l. IsList l => l -> [Item l]
GHC.Exts.toList Vector DictionaryPair
vector)
        Left String
err -> forall a b. a -> Either a b
Left String
err
  where
    tsvDecodeOptions :: DecodeOptions
    tsvDecodeOptions :: DecodeOptions
tsvDecodeOptions = DecodeOptions
defaultDecodeOptions
        { decDelimiter :: Word8
decDelimiter = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
'\t')
        }

{-# NOINLINE southKoreanDictionaryUnsafe #-}
southKoreanDictionaryUnsafe :: HanjaDictionary
southKoreanDictionaryUnsafe :: HanjaDictionary
southKoreanDictionaryUnsafe =
    forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ IO HanjaDictionary -> IO HanjaDictionary
ignoreError IO HanjaDictionary
southKoreanDictionary
  where
    ignoreError :: IO HanjaDictionary -> IO HanjaDictionary
    ignoreError :: IO HanjaDictionary -> IO HanjaDictionary
ignoreError IO HanjaDictionary
action =
        forall a. IO a -> (IOError -> IO a) -> IO a
catchIOError IO HanjaDictionary
action forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Trie a
Trie.empty

-- | Loads [Standard Korean Language Dictionary](https://stdict.korean.go.kr/)
-- (標準國語大辭典) data.
southKoreanDictionary :: IO HanjaDictionary
#ifdef EMBED_DICTIONARY
southKoreanDictionary =
    case readDictionaryByteString bytes of
        Right dic -> return dic
        Left err -> fail err
  where
    bytes :: Data.ByteString.Lazy.ByteString
    bytes = Data.ByteString.Lazy.fromStrict $ $(embedFile $
        takeDirectory __FILE__ </> ".." </> ".." </> ".." </> "data" </>
        "ko-kr-stdict.tsv")

#else
southKoreanDictionary :: IO HanjaDictionary
southKoreanDictionary = do
    String
dataDir <- IO String
getDataDir
    String -> IO HanjaDictionary
readDictionaryFile (String
dataDir String -> ShowS
</> String
"ko-kr-stdict.tsv")
#endif

data DictionaryPair = DictionaryPair !Text !Text deriving (forall x. Rep DictionaryPair x -> DictionaryPair
forall x. DictionaryPair -> Rep DictionaryPair x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DictionaryPair x -> DictionaryPair
$cfrom :: forall x. DictionaryPair -> Rep DictionaryPair x
Generic, Int -> DictionaryPair -> ShowS
[DictionaryPair] -> ShowS
DictionaryPair -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DictionaryPair] -> ShowS
$cshowList :: [DictionaryPair] -> ShowS
show :: DictionaryPair -> String
$cshow :: DictionaryPair -> String
showsPrec :: Int -> DictionaryPair -> ShowS
$cshowsPrec :: Int -> DictionaryPair -> ShowS
Show)

instance FromRecord DictionaryPair

{- HLINT ignore "Use camelCase" -}