Skip to content

Commit

Permalink
DocBook reader: support href on link...
Browse files Browse the repository at this point in the history
even in a fragment.  (We now just look for an `href` attribute without
worrying about the namespace.)

See #8437.
  • Loading branch information
jgm committed Nov 29, 2022
1 parent 07ebafc commit 8f9e162
Showing 1 changed file with 5 additions and 1 deletion.
6 changes: 5 additions & 1 deletion src/Text/Pandoc/Readers/DocBook.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
{- |
Expand Down Expand Up @@ -1277,7 +1278,10 @@ parseInline (Elem e) =
"ulink" -> innerInlines (link (attrValue "url" e) "")
"link" -> do
ils <- innerInlines id
let href = case findAttr (QName "href" (Just "http://www.w3.org/1999/xlink") Nothing) e of
let href = case findAttrBy
(\case
QName "href" _ _ -> True
_ -> False) e of
Just h -> h
_ -> "#" <> attrValue "linkend" e
let ils' = if ils == mempty then str href else ils
Expand Down

0 comments on commit 8f9e162

Please sign in to comment.