Skip to content

Commit

Permalink
Allow YAML bibliographies to be arrays of references.
Browse files Browse the repository at this point in the history
Previously, they had to be YAML objects with a `references` key.

Closes #10452.
  • Loading branch information
jgm committed Dec 12, 2024
1 parent 4272e8a commit d04e490
Showing 1 changed file with 12 additions and 7 deletions.
19 changes: 12 additions & 7 deletions src/Text/Pandoc/Readers/Metadata.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ module Text.Pandoc.Readers.Metadata (
import Control.Monad.Except (throwError)
import qualified Data.ByteString as B
import qualified Data.Map as M
import qualified Data.Vector as V
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Yaml as Yaml
Expand Down Expand Up @@ -83,20 +84,24 @@ yamlBsToRefs :: (PandocMonad m, HasLastStrPosition st)
yamlBsToRefs pMetaValue idpred bstr =
case Yaml.decodeAllEither' bstr of
Right (Object m : _) -> do
let isSelected (String t) = idpred t
isSelected _ = False
let hasSelectedId (Object o) =
case parse (withObject "ref" (.:? "id")) (Object o) of
Success (Just id') -> isSelected id'
_ -> False
hasSelectedId _ = False
case parse (withObject "metadata" (.:? "references")) (Object m) of
Success (Just refs) -> sequence <$>
mapM (yamlToMetaValue pMetaValue) (filter hasSelectedId refs)
_ -> return $ return []
Right (Array v : _) -> do
let refs = filter hasSelectedId $ V.toList v
sequence <$> mapM (yamlToMetaValue pMetaValue) (filter hasSelectedId refs)
Right _ -> return . return $ []
Left err' -> throwError $ PandocParseError
$ T.pack $ Yaml.prettyPrintParseException err'
where
isSelected (String t) = idpred t
isSelected _ = False
hasSelectedId (Object o) =
case parse (withObject "ref" (.:? "id")) (Object o) of
Success (Just id') -> isSelected id'
_ -> False
hasSelectedId _ = False

normalizeMetaValue :: (PandocMonad m, HasLastStrPosition st)
=> ParsecT Sources st m (Future st MetaValue)
Expand Down

0 comments on commit d04e490

Please sign in to comment.