diff options
| author | John MacFarlane <[email protected]> | 2021-03-11 15:49:27 -0800 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2021-03-13 15:05:37 -0800 |
| commit | 8be95ad8e5150d5cab66c4abdf59baaf4670c6c8 (patch) | |
| tree | 9655036efbaabda6a2a7802dc971c7fba5a987ca /src/Text/Pandoc/Writers/OpenDocument.hs | |
| parent | 35b66a76718205c303f416bf0afc01c098e8a171 (diff) | |
Use custom Prelude based on relude.relude
The Prelude now longer exports partial functions, so
a large number of uses of these functions in the
code base have been rewritten.
A .ghci file has been added; this is necessary for
ghci to work properly with the custom Prelude.
Currently there are lots of compiler warnings.
We should either fix these or go to using a custom
Prelude that changes less than relude.
Diffstat (limited to 'src/Text/Pandoc/Writers/OpenDocument.hs')
| -rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 20 |
1 files changed, 11 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index cf42f2228..b9d8de756 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -15,7 +15,7 @@ Conversion of 'Pandoc' documents to OpenDocument XML. -} module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where import Control.Arrow ((***), (>>>)) -import Control.Monad.State.Strict hiding (when) +import Control.Monad.State.Strict import Data.Char (chr) import Data.Foldable (find) import Data.List (sortOn, sortBy, foldl') @@ -97,9 +97,6 @@ defaultWriterState = , stIdentTypes = [] } -when :: Bool -> Doc Text -> Doc Text -when p a = if p then a else empty - addTableStyle :: PandocMonad m => Doc Text -> OD m () addTableStyle i = modify $ \s -> s { stTableStyles = i : stTableStyles s } @@ -226,7 +223,9 @@ handleSpaces s = case T.uncons s of _ -> rm s where genTag = T.span (==' ') >>> tag . T.length *** rm >>> uncurry (<>) - tag n = when (n /= 0) $ selfClosingTag "text:s" [("text:c", tshow n)] + tag n = if n /= 0 + then selfClosingTag "text:s" [("text:c", tshow n)] + else mempty rm t = case T.uncons t of Just ( ' ',xs) -> char ' ' <> genTag xs Just ('\t',xs) -> selfClosingTag "text:tab" [] <> genTag xs @@ -309,9 +308,11 @@ orderedItemToOpenDocument o n bs = vcat <$> mapM go bs go b = blockToOpenDocument o b newLevel a l = do nn <- length <$> gets stParaStyles - ls <- head <$> gets stListStyles - modify $ \s -> s { stListStyles = orderedListLevelStyle a ls : - drop 1 (stListStyles s) } + listStyles <- gets stListStyles + case listStyles of + [] -> return () + (lst:rest) -> modify $ \s -> s { stListStyles = + orderedListLevelStyle a lst : rest } inTagsIndented "text:list" <$> orderedListToOpenDocument o nn l isTightList :: [[Block]] -> Bool @@ -720,7 +721,8 @@ bulletListStyle l = do [ ("text:level" , tshow (i + 1)) , ("text:style-name" , "Bullet_20_Symbols" ) , ("style:num-suffix", "." ) - , ("text:bullet-char", T.singleton (bulletList !! i)) + , ("text:bullet-char", maybe mempty T.singleton + (bulletList !!? i)) ] (listLevelStyle (1 + i)) bulletList = map chr $ cycle [8226,9702,9642] listElStyle = map doStyles [0..9] |
