Docx reader: remove MultiWayIf
Different formatting rules across 7.X and 8.X. Use empty case expression instead.
This commit is contained in:
parent
09e132726d
commit
a55a1e3a57
1 changed files with 39 additions and 38 deletions
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-# LANGUAGE MultiWayIf #-}
|
||||
{-
|
||||
Copyright (C) 2014-2017 Jesse Rosenthal <jrosenthal@jhu.edu>
|
||||
|
||||
|
@ -575,43 +574,45 @@ bodyPartToBlocks (Paragraph pPr parparts)
|
|||
(if isNull prevParaIls then mempty else space) <>
|
||||
ils'
|
||||
opts <- asks docxOptions
|
||||
if | isNull ils'' && not (isEnabled Ext_empty_paragraphs opts) ->
|
||||
return mempty
|
||||
| Just (TrackedChange Insertion _) <- pChange pPr
|
||||
, AcceptChanges <- readerTrackChanges opts -> do
|
||||
modify $ \s -> s {docxPrevPara = mempty}
|
||||
return $ parStyleToTransform pPr $ para ils''
|
||||
| Just (TrackedChange Insertion _) <- pChange pPr
|
||||
, RejectChanges <- readerTrackChanges opts -> do
|
||||
modify $ \s -> s {docxPrevPara = ils''}
|
||||
return mempty
|
||||
| Just (TrackedChange Insertion cInfo) <- pChange pPr
|
||||
, AllChanges <- readerTrackChanges opts
|
||||
, ChangeInfo _ cAuthor cDate <- cInfo -> do
|
||||
let attr = ("", ["paragraph-insertion"], [("author", cAuthor), ("date", cDate)])
|
||||
insertMark = spanWith attr mempty
|
||||
return $
|
||||
parStyleToTransform pPr $
|
||||
para $ ils'' <> insertMark
|
||||
| Just (TrackedChange Deletion _) <- pChange pPr
|
||||
, AcceptChanges <- readerTrackChanges opts -> do
|
||||
modify $ \s -> s {docxPrevPara = ils''}
|
||||
return mempty
|
||||
| Just (TrackedChange Deletion _) <- pChange pPr
|
||||
, RejectChanges <- readerTrackChanges opts -> do
|
||||
modify $ \s -> s {docxPrevPara = mempty}
|
||||
return $ parStyleToTransform pPr $ para ils''
|
||||
| Just (TrackedChange Deletion cInfo) <- pChange pPr
|
||||
, AllChanges <- readerTrackChanges opts
|
||||
, ChangeInfo _ cAuthor cDate <- cInfo -> do
|
||||
let attr = ("", ["paragraph-deletion"], [("author", cAuthor), ("date", cDate)])
|
||||
insertMark = spanWith attr mempty
|
||||
return $
|
||||
parStyleToTransform pPr $
|
||||
para $ ils'' <> insertMark
|
||||
| otherwise -> do
|
||||
modify $ \s -> s {docxPrevPara = mempty}
|
||||
return $ parStyleToTransform pPr $ para ils''
|
||||
case () of
|
||||
|
||||
_ | isNull ils'' && not (isEnabled Ext_empty_paragraphs opts) ->
|
||||
return mempty
|
||||
_ | Just (TrackedChange Insertion _) <- pChange pPr
|
||||
, AcceptChanges <- readerTrackChanges opts -> do
|
||||
modify $ \s -> s {docxPrevPara = mempty}
|
||||
return $ parStyleToTransform pPr $ para ils''
|
||||
_ | Just (TrackedChange Insertion _) <- pChange pPr
|
||||
, RejectChanges <- readerTrackChanges opts -> do
|
||||
modify $ \s -> s {docxPrevPara = ils''}
|
||||
return mempty
|
||||
_ | Just (TrackedChange Insertion cInfo) <- pChange pPr
|
||||
, AllChanges <- readerTrackChanges opts
|
||||
, ChangeInfo _ cAuthor cDate <- cInfo -> do
|
||||
let attr = ("", ["paragraph-insertion"], [("author", cAuthor), ("date", cDate)])
|
||||
insertMark = spanWith attr mempty
|
||||
return $
|
||||
parStyleToTransform pPr $
|
||||
para $ ils'' <> insertMark
|
||||
_ | Just (TrackedChange Deletion _) <- pChange pPr
|
||||
, AcceptChanges <- readerTrackChanges opts -> do
|
||||
modify $ \s -> s {docxPrevPara = ils''}
|
||||
return mempty
|
||||
_ | Just (TrackedChange Deletion _) <- pChange pPr
|
||||
, RejectChanges <- readerTrackChanges opts -> do
|
||||
modify $ \s -> s {docxPrevPara = mempty}
|
||||
return $ parStyleToTransform pPr $ para ils''
|
||||
_ | Just (TrackedChange Deletion cInfo) <- pChange pPr
|
||||
, AllChanges <- readerTrackChanges opts
|
||||
, ChangeInfo _ cAuthor cDate <- cInfo -> do
|
||||
let attr = ("", ["paragraph-deletion"], [("author", cAuthor), ("date", cDate)])
|
||||
insertMark = spanWith attr mempty
|
||||
return $
|
||||
parStyleToTransform pPr $
|
||||
para $ ils'' <> insertMark
|
||||
_ | otherwise -> do
|
||||
modify $ \s -> s {docxPrevPara = mempty}
|
||||
return $ parStyleToTransform pPr $ para ils''
|
||||
bodyPartToBlocks (ListItem pPr numId lvl (Just levelInfo) parparts) = do
|
||||
-- We check whether this current numId has previously been used,
|
||||
-- since Docx expects us to pick up where we left off.
|
||||
|
|
Loading…
Add table
Reference in a new issue