{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.Docx.Fields ( FieldInfo(..)
, IndexEntry(..)
, parseFieldInfo
) where
import Data.Functor (($>), void)
import qualified Data.Text as T
import Text.Pandoc.Parsing
import Data.Maybe (isJust)
type URL = T.Text
type Anchor = T.Text
data IndexEntry = IndexEntry
{ IndexEntry -> Text
entryTitle :: T.Text
, IndexEntry -> Maybe Text
entrySee :: Maybe T.Text
, IndexEntry -> Maybe Text
entryYomi :: Maybe T.Text
, IndexEntry -> Bool
entryBold :: Bool
, IndexEntry -> Bool
entryItalic :: Bool }
deriving (Int -> IndexEntry -> ShowS
[IndexEntry] -> ShowS
IndexEntry -> String
(Int -> IndexEntry -> ShowS)
-> (IndexEntry -> String)
-> ([IndexEntry] -> ShowS)
-> Show IndexEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndexEntry -> ShowS
showsPrec :: Int -> IndexEntry -> ShowS
$cshow :: IndexEntry -> String
show :: IndexEntry -> String
$cshowList :: [IndexEntry] -> ShowS
showList :: [IndexEntry] -> ShowS
Show)
data FieldInfo = HyperlinkField URL
| Anchor Bool
| IndexrefField IndexEntry
| CslCitation T.Text
| CslBibliography
| EndNoteCite T.Text
| EndNoteRefList
| UnknownField
deriving (Int -> FieldInfo -> ShowS
[FieldInfo] -> ShowS
FieldInfo -> String
(Int -> FieldInfo -> ShowS)
-> (FieldInfo -> String)
-> ([FieldInfo] -> ShowS)
-> Show FieldInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldInfo -> ShowS
showsPrec :: Int -> FieldInfo -> ShowS
$cshow :: FieldInfo -> String
show :: FieldInfo -> String
$cshowList :: [FieldInfo] -> ShowS
showList :: [FieldInfo] -> ShowS
Show)
type Parser = Parsec T.Text ()
parseFieldInfo :: T.Text -> Either ParseError FieldInfo
parseFieldInfo :: Text -> Either ParseError FieldInfo
parseFieldInfo = Parsec Text () FieldInfo
-> String -> Text -> Either ParseError FieldInfo
forall s t a.
Stream s Identity t =>
Parsec s () a -> String -> s -> Either ParseError a
parse Parsec Text () FieldInfo
fieldInfo String
""
fieldInfo :: Parser FieldInfo
fieldInfo :: Parsec Text () FieldInfo
fieldInfo = do
ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
Parsec Text () FieldInfo
hyperlink
Parsec Text () FieldInfo
-> Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Parsec Text () FieldInfo
pageref
Parsec Text () FieldInfo
-> Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Parsec Text () FieldInfo
indexref
Parsec Text () FieldInfo
-> Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Parsec Text () FieldInfo
addIn
Parsec Text () FieldInfo
-> Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
FieldInfo -> Parsec Text () FieldInfo
forall a. a -> ParsecT Text () Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return FieldInfo
UnknownField
addIn :: Parser FieldInfo
addIn :: Parsec Text () FieldInfo
addIn = do
String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"ADDIN"
ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parsec Text () FieldInfo
cslCitation Parsec Text () FieldInfo
-> Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Parsec Text () FieldInfo
cslBibliography Parsec Text () FieldInfo
-> Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Parsec Text () FieldInfo
endnoteCite Parsec Text () FieldInfo
-> Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Parsec Text () FieldInfo
endnoteRefList
cslCitation :: Parser FieldInfo
cslCitation :: Parsec Text () FieldInfo
cslCitation = do
ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"ZOTERO_ITEM" ParsecT Text () Identity String
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a b.
ParsecT Text () Identity a
-> ParsecT Text () Identity b -> ParsecT Text () Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces)
String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"CSL_CITATION"
ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
Text -> FieldInfo
CslCitation (Text -> FieldInfo)
-> ParsecT Text () Identity Text -> Parsec Text () FieldInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Text
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
cslBibliography :: Parser FieldInfo
cslBibliography :: Parsec Text () FieldInfo
cslBibliography = do
String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"ZOTERO_BIBL" ParsecT Text () Identity String
-> ParsecT Text () Identity String
-> ParsecT Text () Identity String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"Mendeley Bibliography CSL_BIBLIOGRAPHY"
FieldInfo -> Parsec Text () FieldInfo
forall a. a -> ParsecT Text () Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return FieldInfo
CslBibliography
endnoteCite :: Parser FieldInfo
endnoteCite :: Parsec Text () FieldInfo
endnoteCite = Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec Text () FieldInfo -> Parsec Text () FieldInfo)
-> Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall a b. (a -> b) -> a -> b
$ do
String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"EN.CITE"
ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
Text -> FieldInfo
EndNoteCite (Text -> FieldInfo)
-> ParsecT Text () Identity Text -> Parsec Text () FieldInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Text
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
endnoteRefList :: Parser FieldInfo
endnoteRefList :: Parsec Text () FieldInfo
endnoteRefList = Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec Text () FieldInfo -> Parsec Text () FieldInfo)
-> Parsec Text () FieldInfo -> Parsec Text () FieldInfo
forall a b. (a -> b) -> a -> b
$ do
String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"EN.REFLIST"
FieldInfo -> Parsec Text () FieldInfo
forall a. a -> ParsecT Text () Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return FieldInfo
EndNoteRefList
escapedQuote :: Parser T.Text
escapedQuote :: ParsecT Text () Identity Text
escapedQuote = String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"\\\"" ParsecT Text () Identity String
-> Text -> ParsecT Text () Identity Text
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Text
"\\\""
inQuotes :: Parser T.Text
inQuotes :: ParsecT Text () Identity Text
inQuotes =
ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Text () Identity Text
escapedQuote ParsecT Text () Identity Text
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Char -> Text
T.singleton (Char -> Text)
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar)
quotedString :: Parser T.Text
quotedString :: ParsecT Text () Identity Text
quotedString = do
Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'
[Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Text () Identity [Text] -> ParsecT Text () Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Text
-> ParsecT Text () Identity Char -> ParsecT Text () Identity [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Text () Identity Text
inQuotes (ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'))
unquotedString :: Parser T.Text
unquotedString :: ParsecT Text () Identity Text
unquotedString = String -> Text
T.pack (String -> Text)
-> ParsecT Text () Identity String -> ParsecT Text () Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity String
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity () -> ParsecT Text () Identity ())
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$ ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
space) ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text () Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof)
fieldArgument :: Parser T.Text
fieldArgument :: ParsecT Text () Identity Text
fieldArgument = do
ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\\')
ParsecT Text () Identity Text
quotedString ParsecT Text () Identity Text
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text () Identity Text
unquotedString
hyperlink :: Parser FieldInfo
hyperlink :: Parsec Text () FieldInfo
hyperlink = do
String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"HYPERLINK"
ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
Text
farg <- Text
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" (ParsecT Text () Identity Text -> ParsecT Text () Identity Text)
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall a b. (a -> b) -> a -> b
$ ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\\') ParsecT Text () Identity ()
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall a b.
ParsecT Text () Identity a
-> ParsecT Text () Identity b -> ParsecT Text () Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity Text
fieldArgument
[(Char, Text)]
switches <- ParsecT Text () Identity (Char, Text)
-> ParsecT Text () Identity [(Char, Text)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Text () Identity (Char, Text)
fieldSwitch
let url :: Text
url = case [Text
s | (Char
'l',Text
s) <- [(Char, Text)]
switches] of
[Text
s] -> Text
farg Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s
[Text]
_ -> Text
farg
FieldInfo -> Parsec Text () FieldInfo
forall a. a -> ParsecT Text () Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (FieldInfo -> Parsec Text () FieldInfo)
-> FieldInfo -> Parsec Text () FieldInfo
forall a b. (a -> b) -> a -> b
$ Text -> FieldInfo
HyperlinkField Text
url
fieldSwitch :: Parser (Char, T.Text)
fieldSwitch :: ParsecT Text () Identity (Char, Text)
fieldSwitch = ParsecT Text () Identity (Char, Text)
-> ParsecT Text () Identity (Char, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity (Char, Text)
-> ParsecT Text () Identity (Char, Text))
-> ParsecT Text () Identity (Char, Text)
-> ParsecT Text () Identity (Char, Text)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\\'
Char
c <- ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
Text
farg <- Text
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
forall a. Monoid a => a
mempty ParsecT Text () Identity Text
fieldArgument
(Char, Text) -> ParsecT Text () Identity (Char, Text)
forall a. a -> ParsecT Text () Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Char
c, Text
farg)
pageref :: Parser FieldInfo
= do
String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"PAGEREF"
ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
Text
farg <- ParsecT Text () Identity Text
fieldArgument
[(Char, Text)]
switches <- ParsecT Text () Identity (Char, Text)
-> ParsecT Text () Identity [(Char, Text)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Text () Identity (Char, Text)
fieldSwitch
let isLink :: Bool
isLink = ((Char, Text) -> Bool) -> [(Char, Text)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'h') (Char -> Bool) -> ((Char, Text) -> Char) -> (Char, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char, Text) -> Char
forall a b. (a, b) -> a
fst) [(Char, Text)]
switches
FieldInfo -> Parsec Text () FieldInfo
forall a. a -> ParsecT Text () Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (FieldInfo -> Parsec Text () FieldInfo)
-> FieldInfo -> Parsec Text () FieldInfo
forall a b. (a -> b) -> a -> b
$ Text -> Bool -> FieldInfo
PagerefField Text
farg Bool
isLink
indexref :: Parser FieldInfo
indexref :: Parsec Text () FieldInfo
indexref = do
String -> ParsecT Text () Identity String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"XE"
ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
Text
farg <- ParsecT Text () Identity Text
fieldArgument
[(Char, Text)]
switches <- ParsecT Text () Identity ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces ParsecT Text () Identity ()
-> ParsecT Text () Identity [(Char, Text)]
-> ParsecT Text () Identity [(Char, Text)]
forall a b.
ParsecT Text () Identity a
-> ParsecT Text () Identity b -> ParsecT Text () Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity (Char, Text)
-> ParsecT Text () Identity [(Char, Text)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Text () Identity (Char, Text)
fieldSwitch
FieldInfo -> Parsec Text () FieldInfo
forall a. a -> ParsecT Text () Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (FieldInfo -> Parsec Text () FieldInfo)
-> FieldInfo -> Parsec Text () FieldInfo
forall a b. (a -> b) -> a -> b
$ IndexEntry -> FieldInfo
IndexrefField (IndexEntry -> FieldInfo) -> IndexEntry -> FieldInfo
forall a b. (a -> b) -> a -> b
$ IndexEntry{ entryTitle :: Text
entryTitle = Text
farg
, entrySee :: Maybe Text
entrySee = Char -> [(Char, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Char
't' [(Char, Text)]
switches
, entryYomi :: Maybe Text
entryYomi = Char -> [(Char, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Char
'y' [(Char, Text)]
switches
, entryBold :: Bool
entryBold = Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Char -> [(Char, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Char
'b' [(Char, Text)]
switches)
, entryItalic :: Bool
entryItalic = Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Char -> [(Char, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Char
'i' [(Char, Text)]
switches) }