@@ -42,8 +42,10 @@ module Text.Pandoc.Writers.Shared (
4242 , fixDisplayMath
4343 , unsmartify
4444 , gridTable
45- , metaValueToInlines
46- , metaValueToString
45+ , lookupMetaBool
46+ , lookupMetaBlocks
47+ , lookupMetaInlines
48+ , lookupMetaString
4749 , stripLeadingTrailingSpace
4850 , groffEscape
4951 )
@@ -63,7 +65,6 @@ import Text.Pandoc.Definition
6365import Text.Pandoc.Options
6466import Text.Pandoc.Pretty
6567import Text.Pandoc.Shared (stringify )
66- import Text.Pandoc.Walk (query )
6768import Text.Pandoc.UTF8 (toStringLazy )
6869import Text.Pandoc.XML (escapeStringForXML )
6970import Text.Printf (printf )
@@ -339,19 +340,50 @@ gridTable opts blocksToDoc headless aligns widths headers rows = do
339340 body $$
340341 border ' -' (repeat AlignDefault ) widthsInChars
341342
342- metaValueToInlines :: MetaValue -> [Inline ]
343- metaValueToInlines (MetaString s) = [Str s]
344- metaValueToInlines (MetaInlines ils) = ils
345- metaValueToInlines (MetaBlocks bs) = query return bs
346- metaValueToInlines (MetaBool b) = [Str $ show b]
347- metaValueToInlines _ = []
348343
349- metaValueToString :: MetaValue -> String
350- metaValueToString (MetaString s) = s
351- metaValueToString (MetaInlines ils) = stringify ils
352- metaValueToString (MetaBlocks bs) = stringify bs
353- metaValueToString (MetaBool b) = show b
354- metaValueToString _ = " "
344+
345+ -- | Retrieve the metadata value for a given @key@
346+ -- and convert to Bool.
347+ lookupMetaBool :: String -> Meta -> Bool
348+ lookupMetaBool key meta =
349+ case lookupMeta key meta of
350+ Just (MetaBlocks _) -> True
351+ Just (MetaInlines _) -> True
352+ Just (MetaString (_: _)) -> True
353+ Just (MetaBool True ) -> True
354+ _ -> False
355+
356+ -- | Retrieve the metadata value for a given @key@
357+ -- and extract blocks.
358+ lookupMetaBlocks :: String -> Meta -> [Block ]
359+ lookupMetaBlocks key meta =
360+ case lookupMeta key meta of
361+ Just (MetaBlocks bs) -> bs
362+ Just (MetaInlines ils) -> [Plain ils]
363+ Just (MetaString s) -> [Plain [Str s]]
364+ _ -> []
365+
366+ -- | Retrieve the metadata value for a given @key@
367+ -- and extract inlines.
368+ lookupMetaInlines :: String -> Meta -> [Inline ]
369+ lookupMetaInlines key meta =
370+ case lookupMeta key meta of
371+ Just (MetaString s) -> [Str s]
372+ Just (MetaInlines ils) -> ils
373+ Just (MetaBlocks [Plain ils]) -> ils
374+ Just (MetaBlocks [Para ils]) -> ils
375+ _ -> []
376+
377+ -- | Retrieve the metadata value for a given @key@
378+ -- and convert to String.
379+ lookupMetaString :: String -> Meta -> String
380+ lookupMetaString key meta =
381+ case lookupMeta key meta of
382+ Just (MetaString s) -> s
383+ Just (MetaInlines ils) -> stringify ils
384+ Just (MetaBlocks bs) -> stringify bs
385+ Just (MetaBool b) -> show b
386+ _ -> " "
355387
356388-- | Escape non-ASCII characters using groff \u[..] sequences.
357389groffEscape :: T. Text -> T. Text
0 commit comments