Fix some haddock errors.
This commit is contained in:
parent
545c0911aa
commit
c1717378b0
8 changed files with 13 additions and 18 deletions
|
@ -1022,7 +1022,7 @@ parseBlock (Elem e) =
|
||||||
Just t -> Just ("titleabbrev", strContentRecursive t)
|
Just t -> Just ("titleabbrev", strContentRecursive t)
|
||||||
Nothing -> Nothing
|
Nothing -> Nothing
|
||||||
lineItems = mapM getInlines $ filterChildren (named "line") e
|
lineItems = mapM getInlines $ filterChildren (named "line") e
|
||||||
-- | Admonitions are parsed into a div. Following other Docbook tools that output HTML,
|
-- Admonitions are parsed into a div. Following other Docbook tools that output HTML,
|
||||||
-- we parse the optional title as a div with the @title@ class, and give the
|
-- we parse the optional title as a div with the @title@ class, and give the
|
||||||
-- block itself a class corresponding to the admonition name.
|
-- block itself a class corresponding to the admonition name.
|
||||||
parseAdmonition label = do
|
parseAdmonition label = do
|
||||||
|
|
|
@ -274,15 +274,10 @@ rowsToRowspans rows = let
|
||||||
spans = g cells Nothing (listToMaybe acc)
|
spans = g cells Nothing (listToMaybe acc)
|
||||||
in spans : acc
|
in spans : acc
|
||||||
|
|
||||||
g ::
|
g :: [Cell] -- the current row
|
||||||
-- | The current row
|
-> Maybe Integer -- Number of columns left below
|
||||||
[Cell] ->
|
-> Maybe [(Int, Cell)] -- (rowspan so far, cell) for the row below this one
|
||||||
-- | Number of columns left below
|
-> [(Int, Cell)] -- (rowspan so far, cell) for this row
|
||||||
Maybe Integer ->
|
|
||||||
-- | (rowspan so far, cell) for the row below this one
|
|
||||||
Maybe [(Int, Cell)] ->
|
|
||||||
-- | (rowspan so far, cell) for this row
|
|
||||||
[(Int, Cell)]
|
|
||||||
g cells _ Nothing = zip (repeat 1) cells
|
g cells _ Nothing = zip (repeat 1) cells
|
||||||
g cells columnsLeftBelow (Just rowBelow) =
|
g cells columnsLeftBelow (Just rowBelow) =
|
||||||
case cells of
|
case cells of
|
||||||
|
|
|
@ -332,7 +332,7 @@ normalOrgRefCite = try $ do
|
||||||
moreCitations <- many (try $ char ',' *> orgRefCiteList mode)
|
moreCitations <- many (try $ char ',' *> orgRefCiteList mode)
|
||||||
return . sequence $ firstCitation : moreCitations
|
return . sequence $ firstCitation : moreCitations
|
||||||
where
|
where
|
||||||
-- | A list of org-ref style citation keys, parsed as citation of the given
|
-- A list of org-ref style citation keys, parsed as citation of the given
|
||||||
-- citation mode.
|
-- citation mode.
|
||||||
orgRefCiteList :: PandocMonad m => CitationMode -> OrgParser m (F Citation)
|
orgRefCiteList :: PandocMonad m => CitationMode -> OrgParser m (F Citation)
|
||||||
orgRefCiteList citeMode = try $ do
|
orgRefCiteList citeMode = try $ do
|
||||||
|
|
|
@ -360,7 +360,7 @@ blockToMarkdown' opts (Div attrs ils) = do
|
||||||
case () of
|
case () of
|
||||||
() | "blurb" `elem` classes' -> prefixed "B> " contents <> blankline
|
() | "blurb" `elem` classes' -> prefixed "B> " contents <> blankline
|
||||||
| "aside" `elem` classes' -> prefixed "A> " contents <> blankline
|
| "aside" `elem` classes' -> prefixed "A> " contents <> blankline
|
||||||
-- | necessary to enable option to create a bibliography
|
-- necessary to enable option to create a bibliography
|
||||||
| (take 3 (T.unpack id')) == "ref" -> contents <> blankline
|
| (take 3 (T.unpack id')) == "ref" -> contents <> blankline
|
||||||
| otherwise -> contents <> blankline
|
| otherwise -> contents <> blankline
|
||||||
| isEnabled Ext_fenced_divs opts &&
|
| isEnabled Ext_fenced_divs opts &&
|
||||||
|
|
|
@ -213,8 +213,8 @@ blockToMuse (OrderedList (start, style, _) items) = do
|
||||||
topLevel <- asks envTopLevel
|
topLevel <- asks envTopLevel
|
||||||
return $ (if topLevel then nest 1 else id) (vcat contents) $$ blankline
|
return $ (if topLevel then nest 1 else id) (vcat contents) $$ blankline
|
||||||
where orderedListItemToMuse :: PandocMonad m
|
where orderedListItemToMuse :: PandocMonad m
|
||||||
=> Text -- ^ marker for list item
|
=> Text -- marker for list item
|
||||||
-> [Block] -- ^ list item (list of blocks)
|
-> [Block] -- list item (list of blocks)
|
||||||
-> Muse m (Doc Text)
|
-> Muse m (Doc Text)
|
||||||
orderedListItemToMuse marker item = hang (T.length marker + 1) (literal marker <> space)
|
orderedListItemToMuse marker item = hang (T.length marker + 1) (literal marker <> space)
|
||||||
<$> blockListToMuse item
|
<$> blockListToMuse item
|
||||||
|
@ -597,7 +597,7 @@ inlineToMuse (Strong [Emph lst]) = do
|
||||||
else if null lst' || startsWithSpace lst' || endsWithSpace lst'
|
else if null lst' || startsWithSpace lst' || endsWithSpace lst'
|
||||||
then emphasis "**<em>" "</em>**" lst'
|
then emphasis "**<em>" "</em>**" lst'
|
||||||
else emphasis "***" "***" lst'
|
else emphasis "***" "***" lst'
|
||||||
-- | Underline is only supported in Emacs Muse mode.
|
-- Underline is only supported in Emacs Muse mode.
|
||||||
inlineToMuse (Underline lst) = do
|
inlineToMuse (Underline lst) = do
|
||||||
opts <- asks envOptions
|
opts <- asks envOptions
|
||||||
contents <- inlineListToMuse lst
|
contents <- inlineListToMuse lst
|
||||||
|
|
|
@ -448,7 +448,7 @@ updateMasterElems layouts master masterRels = (updatedMaster, updatedMasterRels)
|
||||||
in (thisId, Elem newRelationship : relationships)
|
in (thisId, Elem newRelationship : relationships)
|
||||||
in (newRelationshipIds, e {elContent = elContent e <> newRelationships})
|
in (newRelationshipIds, e {elContent = elContent e <> newRelationships})
|
||||||
|
|
||||||
-- | Whether the layout needs to be added to the Relationships element.
|
-- Whether the layout needs to be added to the Relationships element.
|
||||||
isNew :: Element -> SlideLayout -> Bool
|
isNew :: Element -> SlideLayout -> Bool
|
||||||
isNew relationships SlideLayout{..} = let
|
isNew relationships SlideLayout{..} = let
|
||||||
toDetails = fmap (takeFileName . T.unpack)
|
toDetails = fmap (takeFileName . T.unpack)
|
||||||
|
|
|
@ -192,7 +192,7 @@ blockToTEI _ HorizontalRule = return $
|
||||||
,("type","separator")
|
,("type","separator")
|
||||||
,("rendition","line")]
|
,("rendition","line")]
|
||||||
|
|
||||||
-- | TEI Tables
|
-- TEI Tables
|
||||||
-- TEI Simple's tables are composed of cells and rows; other
|
-- TEI Simple's tables are composed of cells and rows; other
|
||||||
-- table info in the AST is here lossily discard.
|
-- table info in the AST is here lossily discard.
|
||||||
blockToTEI opts (Table _ blkCapt specs thead tbody tfoot) = do
|
blockToTEI opts (Table _ blkCapt specs thead tbody tfoot) = do
|
||||||
|
|
|
@ -324,7 +324,7 @@ inlineToZimWiki _ (Math mathType str) = return $ delim <> str <> delim -- note
|
||||||
DisplayMath -> "$$"
|
DisplayMath -> "$$"
|
||||||
InlineMath -> "$"
|
InlineMath -> "$"
|
||||||
|
|
||||||
-- | f == Format "html" = return $ "<html>" <> str <> "</html>"
|
-- f == Format "html" = return $ "<html>" <> str <> "</html>"
|
||||||
inlineToZimWiki opts il@(RawInline f str)
|
inlineToZimWiki opts il@(RawInline f str)
|
||||||
| f == Format "zimwiki" = return str
|
| f == Format "zimwiki" = return str
|
||||||
| f == Format "html" = indentFromHTML opts str
|
| f == Format "html" = indentFromHTML opts str
|
||||||
|
|
Loading…
Add table
Reference in a new issue