diff options
Diffstat (limited to 'src/Text/Pandoc/Readers/Odt')
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/Generic/Utils.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/StyleReader.hs | 4 |
5 files changed, 9 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs index d3db3a9e2..9e8221248 100644 --- a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs +++ b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs @@ -100,7 +100,7 @@ liftA fun a = a >>^ fun -- | Duplicate a value to subsequently feed it into different arrows. -- Can almost always be replaced with '(&&&)', 'keepingTheValue', -- or even '(|||)'. --- Aequivalent to +-- Equivalent to -- > returnA &&& returnA duplicate :: (Arrow a) => a b (b,b) duplicate = arr $ join (,) @@ -114,7 +114,7 @@ infixr 2 >>% -- | Duplicate a value and apply an arrow to the second instance. --- Aequivalent to +-- Equivalent to -- > \a -> duplicate >>> second a -- or -- > \a -> returnA &&& a diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs index 6d96897aa..e76bbf5cf 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs @@ -50,7 +50,7 @@ class (Eq nsID, Ord nsID) => NameSpaceID nsID where getNamespaceID :: NameSpaceIRI -> NameSpaceIRIs nsID -> Maybe (NameSpaceIRIs nsID, nsID) - -- | Given a namespace id, lookup its IRI. May be overriden for performance. + -- | Given a namespace id, lookup its IRI. May be overridden for performance. getIRI :: nsID -> NameSpaceIRIs nsID -> Maybe NameSpaceIRI diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs index 616d9290b..45c6cd58c 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs @@ -61,7 +61,7 @@ import qualified Data.Foldable as F (Foldable, foldr) import Data.Maybe --- | Aequivalent to +-- | Equivalent to -- > foldr (.) id -- where '(.)' are 'id' are the ones from "Control.Category" -- and 'foldr' is the one from "Data.Foldable". @@ -72,7 +72,7 @@ import Data.Maybe composition :: (Category cat, F.Foldable f) => f (cat a a) -> cat a a composition = F.foldr (<<<) Cat.id --- | Aequivalent to +-- | Equivalent to -- > foldr (flip (.)) id -- where '(.)' are 'id' are the ones from "Control.Category" -- and 'foldr' is the one from "Data.Foldable". @@ -133,9 +133,7 @@ class Lookupable a where -- can be used directly in almost any case. readLookupables :: (Lookupable a) => String -> [(a,String)] readLookupables s = [ (a,rest) | (word,rest) <- lex s, - let result = lookup word lookupTable, - isJust result, - let Just a = result + a <- maybeToList (lookup word lookupTable) ] -- | Very similar to a simple 'lookup' in the 'lookupTable', but with a lexer. diff --git a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs index 81392e16b..2327ea908 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs @@ -261,7 +261,7 @@ convertingExtraState v a = withSubStateF setVAsExtraState modifyWithA -- The resulting converter even behaves like an identity converter on the -- value level. -- --- Aequivalent to +-- Equivalent to -- -- > \v x a -> convertingExtraState v (returnV x >>> a) -- diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs index e0444559b..6a1682829 100644 --- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs +++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs @@ -138,7 +138,7 @@ fontPitchReader = executeIn NsOffice "font-face-decls" ( lookupDefaultingAttr NsStyle "font-pitch" )) >>?^ ( M.fromList . foldl accumLegalPitches [] ) - ) + ) `ifFailedDo` (returnV (Right M.empty)) where accumLegalPitches ls (Nothing,_) = ls accumLegalPitches ls (Just n,p) = (n,p):ls @@ -342,7 +342,7 @@ instance Read XslUnit where readsPrec _ _ = [] -- | Rough conversion of measures into millimetres. --- Pixels and em's are actually implementation dependant/relative measures, +-- Pixels and em's are actually implementation dependent/relative measures, -- so I could not really easily calculate anything exact here even if I wanted. -- But I do not care about exactness right now, as I only use measures -- to determine if a paragraph is "indented" or not. |