aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Docx
diff options
context:
space:
mode:
authorJesse Rosenthal <jrosenthal@jhu.edu>2014-08-10 09:10:34 -0400
committerJesse Rosenthal <jrosenthal@jhu.edu>2014-08-10 09:10:34 -0400
commitc15978ce5e0b9784de8aaba1f76f299ca5a996bf (patch)
treec167c001f32aabe1c03c82e380806e54db08c27d /src/Text/Pandoc/Readers/Docx
parenta02ce74acf2189207b178fb7c6b62efd23145b0e (diff)
downloadpandoc-c15978ce5e0b9784de8aaba1f76f299ca5a996bf.tar.gz
Change head/tail to pattern guards.
Diffstat (limited to 'src/Text/Pandoc/Readers/Docx')
-rw-r--r--src/Text/Pandoc/Readers/Docx/Reducible.hs15
1 files changed, 8 insertions, 7 deletions
diff --git a/src/Text/Pandoc/Readers/Docx/Reducible.hs b/src/Text/Pandoc/Readers/Docx/Reducible.hs
index 2f1945c7d..2dbef4131 100644
--- a/src/Text/Pandoc/Readers/Docx/Reducible.hs
+++ b/src/Text/Pandoc/Readers/Docx/Reducible.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE OverloadedStrings, PatternGuards #-}
{-
Copyright (C) 2014 Jesse Rosenthal <jrosenthal@jhu.edu>
@@ -87,12 +87,13 @@ combineReducibles r s =
remaining' = conts' \\ shared
in
case null shared of
- True -> case () of
- _ | (not . null) rs && isSpace (last rs) ->
- rebuild conts (init rs) ++ [last rs, s]
- _ | (not . null) ss && isSpace (head ss) ->
- [r, head ss] ++ rebuild conts' (tail ss)
- _ -> [r,s]
+ True | (x : xs) <- reverse rs
+ , isSpace x ->
+ rebuild conts (reverse xs) ++ [x, s]
+ | (x : xs) <- ss
+ , isSpace x ->
+ [r, x] ++ rebuild conts' (xs)
+ True -> [r,s]
False -> rebuild
shared $
reduceList $