HLint: use fromMaybe
Replace uses of `maybe x id` with `fromMaybe x`.
This commit is contained in:
parent
c8fc0a0374
commit
3d70059a48
10 changed files with 30 additions and 23 deletions
|
@ -41,6 +41,7 @@ import System.Directory
|
|||
import System.Environment
|
||||
import Control.Monad (unless)
|
||||
import Data.List (isInfixOf)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import qualified Data.ByteString.Base64 as B64
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
import Text.Pandoc.Definition
|
||||
|
@ -87,7 +88,7 @@ handleImage' baseURL tmpdir (Image ils (src,tit)) = do
|
|||
res <- fetchItem baseURL src
|
||||
case res of
|
||||
Right (contents, Just mime) -> do
|
||||
let ext = maybe (takeExtension src) id $
|
||||
let ext = fromMaybe (takeExtension src) $
|
||||
extensionFromMimeType mime
|
||||
let basename = UTF8.toString $ B64.encode $ UTF8.fromString src
|
||||
let fname = tmpdir </> basename <.> ext
|
||||
|
|
|
@ -12,6 +12,7 @@ import Data.Char (isSpace)
|
|||
import Control.Monad.State
|
||||
import Control.Applicative ((<$>))
|
||||
import Data.List (intersperse)
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
||||
{-
|
||||
|
||||
|
@ -683,7 +684,7 @@ parseBlock (Elem e) =
|
|||
"lowerroman" -> LowerRoman
|
||||
"upperroman" -> UpperRoman
|
||||
_ -> Decimal
|
||||
let start = maybe 1 id $
|
||||
let start = fromMaybe 1 $
|
||||
(attrValue "override" <$> filterElement (named "listitem") e)
|
||||
>>= safeRead
|
||||
orderedListWith (start,listStyle,DefaultDelim)
|
||||
|
@ -779,7 +780,7 @@ parseBlock (Elem e) =
|
|||
caption <- case filterChild isCaption e of
|
||||
Just t -> getInlines t
|
||||
Nothing -> return mempty
|
||||
let e' = maybe e id $ filterChild (named "tgroup") e
|
||||
let e' = fromMaybe e $ filterChild (named "tgroup") e
|
||||
let isColspec x = named "colspec" x || named "col" x
|
||||
let colspecs = case filterChild (named "colgroup") e' of
|
||||
Just c -> filterChildren isColspec c
|
||||
|
@ -801,7 +802,7 @@ parseBlock (Elem e) =
|
|||
Just "center" -> AlignCenter
|
||||
_ -> AlignDefault
|
||||
let toWidth c = case findAttr (unqual "colwidth") c of
|
||||
Just w -> maybe 0 id
|
||||
Just w -> fromMaybe 0
|
||||
$ safeRead $ '0': filter (\x ->
|
||||
(x >= '0' && x <= '9')
|
||||
|| x == '.') w
|
||||
|
|
|
@ -207,7 +207,7 @@ pHeader = try $ do
|
|||
let bodyTitle = TagOpen tagtype attr ~== TagOpen "h1" [("class","title")]
|
||||
let level = read (drop 1 tagtype)
|
||||
contents <- liftM concat $ manyTill inline (pCloses tagtype <|> eof)
|
||||
let ident = maybe "" id $ lookup "id" attr
|
||||
let ident = fromMaybe "" $ lookup "id" attr
|
||||
let classes = maybe [] words $ lookup "class" attr
|
||||
let keyvals = [(k,v) | (k,v) <- attr, k /= "class", k /= "id"]
|
||||
return $ if bodyTitle
|
||||
|
@ -257,7 +257,7 @@ pCol = try $ do
|
|||
skipMany pBlank
|
||||
return $ case lookup "width" attribs of
|
||||
Just x | not (null x) && last x == '%' ->
|
||||
maybe 0.0 id $ safeRead ('0':'.':init x)
|
||||
fromMaybe 0.0 $ safeRead ('0':'.':init x)
|
||||
_ -> 0.0
|
||||
|
||||
pColgroup :: TagParser [Double]
|
||||
|
|
|
@ -1722,7 +1722,7 @@ spanHtml = try $ do
|
|||
guardEnabled Ext_markdown_in_html_blocks
|
||||
(TagOpen _ attrs, _) <- htmlTag (~== TagOpen "span" [])
|
||||
contents <- mconcat <$> manyTill inline (htmlTag (~== TagClose "span"))
|
||||
let ident = maybe "" id $ lookup "id" attrs
|
||||
let ident = fromMaybe "" $ lookup "id" attrs
|
||||
let classes = maybe [] words $ lookup "class" attrs
|
||||
let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"]
|
||||
return $ B.spanWith (ident, classes, keyvals) <$> contents
|
||||
|
@ -1732,7 +1732,7 @@ divHtml = try $ do
|
|||
guardEnabled Ext_markdown_in_html_blocks
|
||||
(TagOpen _ attrs, _) <- htmlTag (~== TagOpen "div" [])
|
||||
contents <- mconcat <$> manyTill block (htmlTag (~== TagClose "div"))
|
||||
let ident = maybe "" id $ lookup "id" attrs
|
||||
let ident = fromMaybe "" $ lookup "id" attrs
|
||||
let classes = maybe [] words $ lookup "class" attrs
|
||||
let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"]
|
||||
return $ B.divWith (ident, classes, keyvals) <$> contents
|
||||
|
|
|
@ -54,6 +54,7 @@ import Data.Sequence (viewl, ViewL(..), (<|))
|
|||
import qualified Data.Foldable as F
|
||||
import qualified Data.Map as M
|
||||
import Data.Char (isDigit, isSpace)
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
||||
-- | Read mediawiki from an input string and return a Pandoc document.
|
||||
readMediaWiki :: ReaderOptions -- ^ Reader options
|
||||
|
@ -204,7 +205,7 @@ table = do
|
|||
tableStart
|
||||
styles <- option [] parseAttrs <* blankline
|
||||
let tableWidth = case lookup "width" styles of
|
||||
Just w -> maybe 1.0 id $ parseWidth w
|
||||
Just w -> fromMaybe 1.0 $ parseWidth w
|
||||
Nothing -> 1.0
|
||||
caption <- option mempty tableCaption
|
||||
optional rowsep
|
||||
|
@ -285,7 +286,7 @@ tableCell = try $ do
|
|||
Just "center" -> AlignCenter
|
||||
_ -> AlignDefault
|
||||
let width = case lookup "width" attrs of
|
||||
Just xs -> maybe 0.0 id $ parseWidth xs
|
||||
Just xs -> fromMaybe 0.0 $ parseWidth xs
|
||||
Nothing -> 0.0
|
||||
return ((align, width), bs)
|
||||
|
||||
|
@ -387,7 +388,7 @@ orderedList =
|
|||
spaces
|
||||
items <- many (listItem '#' <|> li)
|
||||
optional (htmlTag (~== TagClose "ol"))
|
||||
let start = maybe 1 id $ safeRead $ fromAttrib "start" tag
|
||||
let start = fromMaybe 1 $ safeRead $ fromAttrib "start" tag
|
||||
return $ B.orderedListWith (start, DefaultStyle, DefaultDelim) items
|
||||
|
||||
definitionList :: MWParser Blocks
|
||||
|
|
|
@ -29,6 +29,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
Conversion of 'Pandoc' documents to docx.
|
||||
-}
|
||||
module Text.Pandoc.Writers.Docx ( writeDocx ) where
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.List ( intercalate, groupBy )
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
@ -130,7 +131,8 @@ writeDocx opts doc@(Pandoc meta _) = do
|
|||
let mkOverrideNode (part', contentType') = mknode "Override"
|
||||
[("PartName",part'),("ContentType",contentType')] ()
|
||||
let mkImageOverride (_, imgpath, mbMimeType, _, _) =
|
||||
mkOverrideNode ("/word/" ++ imgpath, maybe "application/octet-stream" id mbMimeType)
|
||||
mkOverrideNode ("/word/" ++ imgpath,
|
||||
fromMaybe "application/octet-stream" mbMimeType)
|
||||
let overrides = map mkOverrideNode
|
||||
[("/word/webSettings.xml",
|
||||
"application/vnd.openxmlformats-officedocument.wordprocessingml.webSettings+xml")
|
||||
|
@ -322,7 +324,7 @@ mkNum markers marker numid =
|
|||
NumberMarker _ _ start ->
|
||||
map (\lvl -> mknode "w:lvlOverride" [("w:ilvl",show (lvl :: Int))]
|
||||
$ mknode "w:startOverride" [("w:val",show start)] ()) [0..6]
|
||||
where absnumid = maybe 0 id $ M.lookup marker markers
|
||||
where absnumid = fromMaybe 0 $ M.lookup marker markers
|
||||
|
||||
mkAbstractNum :: (ListMarker,Int) -> IO Element
|
||||
mkAbstractNum (marker,numid) = do
|
||||
|
|
|
@ -176,8 +176,8 @@ addMetadataFromXML e@(Element (QName name _ (Just "dc")) attrs _ _) md
|
|||
, titleFileAs = getAttr "file-as"
|
||||
, titleType = getAttr "type"
|
||||
} : epubTitle md }
|
||||
| name == "date" = md{ epubDate = maybe "" id $ normalizeDate'
|
||||
$ strContent e }
|
||||
| name == "date" = md{ epubDate = fromMaybe "" $ normalizeDate'
|
||||
$ strContent e }
|
||||
| name == "language" = md{ epubLanguage = strContent e }
|
||||
| name == "creator" = md{ epubCreator =
|
||||
Creator{ creatorText = strContent e
|
||||
|
@ -271,7 +271,7 @@ metadataFromMeta opts meta = EPUBMetadata{
|
|||
}
|
||||
where identifiers = getIdentifier meta
|
||||
titles = getTitle meta
|
||||
date = maybe "" id $
|
||||
date = fromMaybe "" $
|
||||
(metaValueToString <$> lookupMeta "date" meta) >>= normalizeDate'
|
||||
language = maybe "" metaValueToString $
|
||||
lookupMeta "language" meta `mplus` lookupMeta "lang" meta
|
||||
|
@ -297,7 +297,7 @@ writeEPUB :: WriterOptions -- ^ Writer options
|
|||
-> Pandoc -- ^ Document to convert
|
||||
-> IO B.ByteString
|
||||
writeEPUB opts doc@(Pandoc meta _) = do
|
||||
let version = maybe EPUB2 id (writerEpubVersion opts)
|
||||
let version = fromMaybe EPUB2 (writerEpubVersion opts)
|
||||
let epub3 = version == EPUB3
|
||||
epochtime <- floor `fmap` getPOSIXTime
|
||||
let mkEntry path content = toEntry path epochtime content
|
||||
|
@ -401,7 +401,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
|
|||
chapToEntry num (Chapter mbnum bs) = mkEntry (showChapter num)
|
||||
$ renderHtml
|
||||
$ writeHtml opts'{ writerNumberOffset =
|
||||
maybe [] id mbnum }
|
||||
fromMaybe [] mbnum }
|
||||
$ case bs of
|
||||
(Header _ _ xs : _) ->
|
||||
Pandoc (setMeta "title" (fromList xs) nullMeta) bs
|
||||
|
@ -436,7 +436,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
|
|||
let fontNode ent = unode "item" !
|
||||
[("id", takeBaseName $ eRelativePath ent),
|
||||
("href", eRelativePath ent),
|
||||
("media-type", maybe "" id $ getMimeType $ eRelativePath ent)] $ ()
|
||||
("media-type", fromMaybe "" $ getMimeType $ eRelativePath ent)] $ ()
|
||||
let plainTitle = case docTitle meta of
|
||||
[] -> case epubTitle metadata of
|
||||
[] -> "UNTITLED"
|
||||
|
|
|
@ -45,7 +45,7 @@ import Numeric ( showHex )
|
|||
import Data.Char ( ord, toLower )
|
||||
import Data.List ( isPrefixOf, intersperse )
|
||||
import Data.String ( fromString )
|
||||
import Data.Maybe ( catMaybes )
|
||||
import Data.Maybe ( catMaybes, fromMaybe )
|
||||
import Control.Monad.State
|
||||
import Text.Blaze.Html hiding(contents)
|
||||
import Text.Blaze.Internal(preEscapedString)
|
||||
|
@ -118,7 +118,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
let stringifyHTML = escapeStringForXML . stringify
|
||||
let authsMeta = map stringifyHTML $ docAuthors meta
|
||||
let dateMeta = stringifyHTML $ docDate meta
|
||||
let slideLevel = maybe (getSlideLevel blocks) id $ writerSlideLevel opts
|
||||
let slideLevel = fromMaybe (getSlideLevel blocks) $ writerSlideLevel opts
|
||||
let sects = hierarchicalize $
|
||||
if writerSlideVariant opts == NoSlides
|
||||
then blocks
|
||||
|
|
|
@ -40,6 +40,7 @@ import Network.URI ( isURI, unEscapeString )
|
|||
import Data.List ( (\\), isSuffixOf, isInfixOf,
|
||||
isPrefixOf, intercalate, intersperse )
|
||||
import Data.Char ( toLower, isPunctuation, isAscii, isLetter, isDigit, ord )
|
||||
import Data.Maybe ( fromMaybe )
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Monad.State
|
||||
import Text.Pandoc.Pretty
|
||||
|
@ -240,7 +241,7 @@ inCmd cmd contents = char '\\' <> text cmd <> braces contents
|
|||
toSlides :: [Block] -> State WriterState [Block]
|
||||
toSlides bs = do
|
||||
opts <- gets stOptions
|
||||
let slideLevel = maybe (getSlideLevel bs) id $ writerSlideLevel opts
|
||||
let slideLevel = fromMaybe (getSlideLevel bs) $ writerSlideLevel opts
|
||||
let bs' = prepSlides slideLevel bs
|
||||
concat `fmap` (mapM (elementToBeamer slideLevel) $ hierarchicalize bs')
|
||||
|
||||
|
|
|
@ -31,6 +31,7 @@ Conversion of 'Pandoc' documents to ODT.
|
|||
module Text.Pandoc.Writers.ODT ( writeODT ) where
|
||||
import Data.IORef
|
||||
import Data.List ( isPrefixOf )
|
||||
import Data.Maybe ( fromMaybe )
|
||||
import qualified Data.ByteString.Lazy as B
|
||||
import Text.Pandoc.UTF8 ( fromStringLazy )
|
||||
import Codec.Archive.Zip
|
||||
|
@ -127,7 +128,7 @@ transformPic opts entriesRef (Image lab (src,_)) = do
|
|||
return $ Emph lab
|
||||
Right (img, _) -> do
|
||||
let size = imageSize img
|
||||
let (w,h) = maybe (0,0) id $ sizeInPoints `fmap` size
|
||||
let (w,h) = fromMaybe (0,0) $ sizeInPoints `fmap` size
|
||||
let tit' = show w ++ "x" ++ show h
|
||||
entries <- readIORef entriesRef
|
||||
let newsrc = "Pictures/" ++ show (length entries) ++ takeExtension src
|
||||
|
|
Loading…
Reference in a new issue