Merge pull request #1374 from jkr/track-changes-options

Track changes with options
This commit is contained in:
John MacFarlane 2014-06-25 23:51:16 -07:00
commit 9f694619cd
11 changed files with 85 additions and 7 deletions

11
README
View file

@ -308,6 +308,17 @@ Reader options
`--tab-stop=`*NUMBER* `--tab-stop=`*NUMBER*
: Specify the number of spaces per tab (default is 4). : Specify the number of spaces per tab (default is 4).
`--track-changes=`*accept|reject|all*
: Specifies what to do with insertions and deletions produced by the MS
Word "track-changes" feature. *accept* (the default), inserts all
insertions, and ignores all deletions. *reject* inserts all
deletions and ignores insertions. *all* puts in both insertions
and deletions, wrapped in spans with `insertion` and `deletion`
classes, respectively. The author and time of change is
included. *all* is useful for scripting: only accepting changes
from a certain reviewer, say, or before a certain date. This
option only affects the Docx reader.
General writer options General writer options
---------------------- ----------------------

View file

@ -174,6 +174,7 @@ data Opt = Opt
, optTeXLigatures :: Bool -- ^ Use TeX ligatures for quotes/dashes , optTeXLigatures :: Bool -- ^ Use TeX ligatures for quotes/dashes
, optDefaultImageExtension :: String -- ^ Default image extension , optDefaultImageExtension :: String -- ^ Default image extension
, optTrace :: Bool -- ^ Print debug information , optTrace :: Bool -- ^ Print debug information
, optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes.
} }
-- | Defaults for command-line options. -- | Defaults for command-line options.
@ -230,6 +231,7 @@ defaultOpts = Opt
, optTeXLigatures = True , optTeXLigatures = True
, optDefaultImageExtension = "" , optDefaultImageExtension = ""
, optTrace = False , optTrace = False
, optTrackChanges = AcceptChanges
} }
-- | A list of functions, each transforming the options data structure -- | A list of functions, each transforming the options data structure
@ -776,6 +778,19 @@ options =
(\opt -> return opt { optTrace = True })) (\opt -> return opt { optTrace = True }))
"" -- "Turn on diagnostic tracing in readers." "" -- "Turn on diagnostic tracing in readers."
, Option "" ["track-changes"]
(ReqArg
(\arg opt -> do
action <- case arg of
"accept" -> return AcceptChanges
"reject" -> return RejectChanges
"all" -> return AllChanges
_ -> err 6
("Unknown option for track-changes: " ++ arg)
return opt { optTrackChanges = action })
"accept|reject|all")
"" -- "Accepting or reject MS Word track-changes.""
, Option "" ["dump-args"] , Option "" ["dump-args"]
(NoArg (NoArg
(\opt -> return opt { optDumpArgs = True })) (\opt -> return opt { optDumpArgs = True }))
@ -973,6 +988,7 @@ main = do
, optTeXLigatures = texLigatures , optTeXLigatures = texLigatures
, optDefaultImageExtension = defaultImageExtension , optDefaultImageExtension = defaultImageExtension
, optTrace = trace , optTrace = trace
, optTrackChanges = trackChanges
} = opts } = opts
when dumpArgs $ when dumpArgs $
@ -1097,6 +1113,7 @@ main = do
, readerApplyMacros = not laTeXOutput , readerApplyMacros = not laTeXOutput
, readerDefaultImageExtension = defaultImageExtension , readerDefaultImageExtension = defaultImageExtension
, readerTrace = trace , readerTrace = trace
, readerTrackChanges = trackChanges
} }
let writerOptions = def { writerStandalone = standalone', let writerOptions = def { writerStandalone = standalone',

View file

@ -41,6 +41,7 @@ module Text.Pandoc.Options ( Extension(..)
, HTMLSlideVariant (..) , HTMLSlideVariant (..)
, EPUBVersion (..) , EPUBVersion (..)
, WriterOptions (..) , WriterOptions (..)
, TrackChanges (..)
, def , def
, isEnabled , isEnabled
) where ) where
@ -211,6 +212,7 @@ data ReaderOptions = ReaderOptions{
-- indented code blocks -- indented code blocks
, readerDefaultImageExtension :: String -- ^ Default extension for images , readerDefaultImageExtension :: String -- ^ Default extension for images
, readerTrace :: Bool -- ^ Print debugging info , readerTrace :: Bool -- ^ Print debugging info
, readerTrackChanges :: TrackChanges
} deriving (Show, Read) } deriving (Show, Read)
instance Default ReaderOptions instance Default ReaderOptions
@ -227,6 +229,7 @@ instance Default ReaderOptions
, readerIndentedCodeClasses = [] , readerIndentedCodeClasses = []
, readerDefaultImageExtension = "" , readerDefaultImageExtension = ""
, readerTrace = False , readerTrace = False
, readerTrackChanges = AcceptChanges
} }
-- --
@ -264,6 +267,12 @@ data HTMLSlideVariant = S5Slides
| NoSlides | NoSlides
deriving (Show, Read, Eq) deriving (Show, Read, Eq)
-- | Options for accepting or rejecting MS Word track-changes.
data TrackChanges = AcceptChanges
| RejectChanges
| AllChanges
deriving (Show, Read, Eq)
-- | Options for writers -- | Options for writers
data WriterOptions = WriterOptions data WriterOptions = WriterOptions
{ writerStandalone :: Bool -- ^ Include header and footer { writerStandalone :: Bool -- ^ Include header and footer

View file

@ -234,9 +234,22 @@ runToInlines opts docx@(Docx _ notes _ _ _) (Endnote fnId) =
parPartToInlines :: ReaderOptions -> Docx -> ParPart -> [Inline] parPartToInlines :: ReaderOptions -> Docx -> ParPart -> [Inline]
parPartToInlines opts docx (PlainRun r) = runToInlines opts docx r parPartToInlines opts docx (PlainRun r) = runToInlines opts docx r
parPartToInlines opts docx (Insertion _ _ _ runs) = parPartToInlines opts docx (Insertion _ author date runs) =
concatMap (runToInlines opts docx) runs case readerTrackChanges opts of
parPartToInlines _ _ (Deletion _ _ _ _) = [] AcceptChanges -> concatMap (runToInlines opts docx) runs
RejectChanges -> []
AllChanges ->
[Span
("", ["insertion"], [("author", author), ("date", date)])
(concatMap (runToInlines opts docx) runs)]
parPartToInlines opts docx (Deletion _ author date runs) =
case readerTrackChanges opts of
AcceptChanges -> []
RejectChanges -> concatMap (runToInlines opts docx) runs
AllChanges ->
[Span
("", ["deletion"], [("author", author), ("date", date)])
(concatMap (runToInlines opts docx) runs)]
parPartToInlines _ _ (BookMark _ anchor) | anchor `elem` dummyAnchors = [] parPartToInlines _ _ (BookMark _ anchor) | anchor `elem` dummyAnchors = []
parPartToInlines _ _ (BookMark _ anchor) = [Span (anchor, ["anchor"], []) []] parPartToInlines _ _ (BookMark _ anchor) = [Span (anchor, ["anchor"], []) []]
parPartToInlines _ (Docx _ _ _ rels _) (Drawing relid) = parPartToInlines _ (Docx _ _ _ rels _) (Drawing relid) =

View file

@ -124,13 +124,37 @@ tests = [ testGroup "inlines"
] ]
, testGroup "track changes" , testGroup "track changes"
[ testCompare [ testCompare
"insert insertion (insertions only)" "insertion (default)"
"docx.track_changes_insertion.docx" "docx.track_changes_insertion.docx"
"docx.track_changes_insertion_only_ins.native" "docx.track_changes_insertion_accept.native"
, testCompareWithOpts def{readerTrackChanges=AcceptChanges}
"insert insertion (accept)"
"docx.track_changes_insertion.docx"
"docx.track_changes_insertion_accept.native"
, testCompareWithOpts def{readerTrackChanges=RejectChanges}
"remove insertion (reject)"
"docx.track_changes_insertion.docx"
"docx.track_changes_insertion_reject.native"
, testCompare , testCompare
"skip deletion (insertions only)" "deletion (default)"
"docx.track_changes_deletion.docx" "docx.track_changes_deletion.docx"
"docx.track_changes_deletion_only_ins.native" "docx.track_changes_deletion_accept.native"
, testCompareWithOpts def{readerTrackChanges=AcceptChanges}
"remove deletion (accept)"
"docx.track_changes_deletion.docx"
"docx.track_changes_deletion_accept.native"
, testCompareWithOpts def{readerTrackChanges=RejectChanges}
"insert deletion (reject)"
"docx.track_changes_deletion.docx"
"docx.track_changes_deletion_reject.native"
, testCompareWithOpts def{readerTrackChanges=AllChanges}
"keep insertion (all)"
"docx.track_changes_deletion.docx"
"docx.track_changes_deletion_all.native"
, testCompareWithOpts def{readerTrackChanges=AllChanges}
"keep deletion (all)"
"docx.track_changes_deletion.docx"
"docx.track_changes_deletion_all.native"
] ]
] ]

View file

@ -0,0 +1 @@
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "text",Space,Str "with",Space,Str "a",Span ("",["deletion"],[("author","eng-dept"),("date","2014-06-25T10:42:00Z")]) [Str "n",Space,Str "excessively",Space,Str "modified"],Space,Str "deletion."]]

View file

@ -0,0 +1 @@
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "text",Space,Str "with",Space,Str "an",Space,Str "excessively",Space,Str "modified",Space,Str "deletion."]]

View file

@ -0,0 +1 @@
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "text",Space,Str "with",Space,Span ("",["insertion"],[("author","eng-dept"),("date","2014-06-25T10:40:00Z")]) [Str "two",Space,Str "exciting"],Space,Str "insertions."]]

View file

@ -0,0 +1 @@
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "text",Space,Str "with",Space,Str "insertions."]]