Apply some HLint suggestions
This commit is contained in:
parent
13740c4543
commit
b5da58e8b4
4 changed files with 12 additions and 17 deletions
|
@ -1,6 +1,5 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Filter
|
||||
|
|
|
@ -1,6 +1,5 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Logging
|
||||
|
|
|
@ -1007,13 +1007,12 @@ parseBlock (Elem e) =
|
|||
b <- getBlocks e
|
||||
modify $ \st -> st{ dbSectionLevel = n - 1 }
|
||||
return $ headerWith (elId, classes, maybeToList titleabbrevElAsAttr++attrs) n' headerText <> b
|
||||
titleabbrevElAsAttr = do
|
||||
txt <- case filterChild (named "titleabbrev") e `mplus`
|
||||
(filterChild (named "info") e >>=
|
||||
filterChild (named "titleabbrev")) of
|
||||
Just t -> Just ("titleabbrev", strContentRecursive t)
|
||||
Nothing -> Nothing
|
||||
return txt
|
||||
titleabbrevElAsAttr =
|
||||
case filterChild (named "titleabbrev") e `mplus`
|
||||
(filterChild (named "info") e >>=
|
||||
filterChild (named "titleabbrev")) of
|
||||
Just t -> Just ("titleabbrev", strContentRecursive t)
|
||||
Nothing -> Nothing
|
||||
lineItems = mapM getInlines $ filterChildren (named "line") e
|
||||
-- | 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
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Writers.Shared
|
||||
Copyright : Copyright (C) 2021 John MacFarlane
|
||||
Module : Text.Pandoc.Writers.Blaze
|
||||
Copyright : Copyright (C) 2021-2022 John MacFarlane
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
||||
|
@ -112,12 +112,10 @@ withWrap wrap
|
|||
toChunks :: Text -> [Doc Text]
|
||||
toChunks = map toDoc . T.groupBy sameStatus
|
||||
where
|
||||
toDoc t =
|
||||
if T.any (== ' ') t
|
||||
then space
|
||||
else if T.any (== '\n') t
|
||||
then cr
|
||||
else literal t
|
||||
toDoc t
|
||||
| T.any (== ' ') t = space
|
||||
| T.any (== '\n') t = cr
|
||||
| otherwise = literal t
|
||||
sameStatus c d =
|
||||
(c == ' ' && d == ' ') ||
|
||||
(c == '\n' && d == '\n') ||
|
||||
|
|
Loading…
Add table
Reference in a new issue