aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2015-10-22 17:54:58 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2015-10-22 17:54:58 -0700
commit317d9eea17e9181e2e0b54651c7f04e6d0e8c230 (patch)
treebf042b8f7caed6e27cd4fae67409eb67d5b9ed53 /src
parent48b68aac43bbd7aed397c01ecc94c703f7b81fa7 (diff)
downloadpandoc-317d9eea17e9181e2e0b54651c7f04e6d0e8c230.tar.gz
Changed § to % in operators from Odt.Arrows.Utils.
This prevents problems building haddocks with "C" locale. Closes #2457.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs39
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs12
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs28
-rw-r--r--src/Text/Pandoc/Readers/Odt/Namespaces.hs2
-rw-r--r--src/Text/Pandoc/Readers/Odt/StyleReader.hs4
5 files changed, 42 insertions, 43 deletions
diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
index d4dcf5be2..fdc02d8d2 100644
--- a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
+++ b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
@@ -129,24 +129,23 @@ joinOn :: (Arrow a) => (x -> y -> z) -> a (x,y) z
joinOn = arr.uncurry
-- | Applies a function to the uncurried result-pair of an arrow-application.
--- (The §-symbol was chosen to evoke an association with pairs through the
--- shared first character)
-(>>§) :: (Arrow a) => a x (b,c) -> (b -> c -> d) -> a x d
-a >>§ f = a >>^ uncurry f
+-- (The %-symbol was chosen to evoke an association with pairs.)
+(>>%) :: (Arrow a) => a x (b,c) -> (b -> c -> d) -> a x d
+a >>% f = a >>^ uncurry f
--- | '(>>§)' with its arguments flipped
-(§<<) :: (Arrow a) => (b -> c -> d) -> a x (b,c) -> a x d
-(§<<) = flip (>>§)
+-- | '(>>%)' with its arguments flipped
+(%<<) :: (Arrow a) => (b -> c -> d) -> a x (b,c) -> a x d
+(%<<) = flip (>>%)
-- | Precomposition with an uncurried function
-(§>>) :: (Arrow a) => (b -> c -> d) -> a d r -> a (b,c) r
-f §>> a = uncurry f ^>> a
+(%>>) :: (Arrow a) => (b -> c -> d) -> a d r -> a (b,c) r
+f %>> a = uncurry f ^>> a
-- | Precomposition with an uncurried function (right to left variant)
-(<<§) :: (Arrow a) => a d r -> (b -> c -> d) -> a (b,c) r
-(<<§) = flip (§>>)
+(<<%) :: (Arrow a) => a d r -> (b -> c -> d) -> a (b,c) r
+(<<%) = flip (%>>)
-infixr 2 >>§, §<<, §>>, <<§
+infixr 2 >>%, %<<, %>>, <<%
-- | Duplicate a value and apply an arrow to the second instance.
@@ -271,7 +270,7 @@ newtype ParallelArrow a b c = CoEval { evalParallelArrow :: a b c }
instance (Arrow a, Monoid m) => Monoid (ParallelArrow a b m) where
mempty = CoEval $ returnV mempty
- (CoEval a) `mappend` (CoEval ~b) = CoEval $ a &&& b >>§ mappend
+ (CoEval a) `mappend` (CoEval ~b) = CoEval $ a &&& b >>% mappend
-- | Evaluates a collection of arrows in a parallel fashion.
--
@@ -433,29 +432,29 @@ a ^>>?^? f = a ^>> Left ^|||^ f
a >>?! f = a >>> right f
---
-(>>?§) :: (ArrowChoice a, Monoid f)
+(>>?%) :: (ArrowChoice a, Monoid f)
=> FallibleArrow a x f (b,b')
-> (b -> b' -> c)
-> FallibleArrow a x f c
-a >>?§ f = a >>?^ (uncurry f)
+a >>?% f = a >>?^ (uncurry f)
---
-(^>>?§) :: (ArrowChoice a, Monoid f)
+(^>>?%) :: (ArrowChoice a, Monoid f)
=> (x -> Either f (b,b'))
-> (b -> b' -> c)
-> FallibleArrow a x f c
-a ^>>?§ f = arr a >>?^ (uncurry f)
+a ^>>?% f = arr a >>?^ (uncurry f)
---
-(>>?§?) :: (ArrowChoice a, Monoid f)
+(>>?%?) :: (ArrowChoice a, Monoid f)
=> FallibleArrow a x f (b,b')
-> (b -> b' -> (Either f c))
-> FallibleArrow a x f c
-a >>?§? f = a >>?^? (uncurry f)
+a >>?%? f = a >>?^? (uncurry f)
infixr 1 >>?, >>?^, >>?^?
infixr 1 ^>>?, ^>>?^, ^>>?^?, >>?!
-infixr 1 >>?§, ^>>?§, >>?§?
+infixr 1 >>?%, ^>>?%, >>?%?
-- | Keep values that are Right, replace Left values by a constant.
ifFailedUse :: (ArrowChoice a) => v -> a (Either f v) v
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 9ff3532e1..1f1c57646 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -145,7 +145,7 @@ type OdtReaderSafe a b = XMLReaderSafe ReaderState a b
fromStyles :: (a -> Styles -> b) -> OdtReaderSafe a b
fromStyles f = keepingTheValue
(getExtraState >>^ styleSet)
- >>§ f
+ >>% f
--
getStyleByName :: OdtReader StyleName Style
@@ -162,7 +162,7 @@ lookupListStyle = fromStyles lookupListStyleByName >>^ maybeToChoice
--
switchCurrentListStyle :: OdtReaderSafe (Maybe ListStyle) (Maybe ListStyle)
switchCurrentListStyle = keepingTheValue getExtraState
- >>§ swapCurrentListStyle
+ >>% swapCurrentListStyle
>>> first setExtraState
>>^ snd
@@ -170,7 +170,7 @@ switchCurrentListStyle = keepingTheValue getExtraState
pushStyle :: OdtReaderSafe Style Style
pushStyle = keepingTheValue (
( keepingTheValue getExtraState
- >>§ pushStyle'
+ >>% pushStyle'
)
>>> setExtraState
)
@@ -470,7 +470,7 @@ matchingElement :: (Monoid e)
matchingElement ns name reader = (ns, name, asResultAccumulator reader)
where
asResultAccumulator :: (ArrowChoice a, Monoid m) => a m m -> a m (Fallible m)
- asResultAccumulator a = liftAsSuccess $ keepingTheValue a >>§ (<>)
+ asResultAccumulator a = liftAsSuccess $ keepingTheValue a >>% (<>)
--
matchChildContent' :: (Monoid result)
@@ -497,14 +497,14 @@ matchChildContent ls fallback = returnV mempty >>> matchContent ls fallback
--
-- | Open Document allows several consecutive spaces if they are marked up
read_plain_text :: OdtReaderSafe (Inlines, XML.Content) Inlines
-read_plain_text = fst ^&&& read_plain_text' >>§ recover
+read_plain_text = fst ^&&& read_plain_text' >>% recover
where
-- fallible version
read_plain_text' :: OdtReader (Inlines, XML.Content) Inlines
read_plain_text' = ( second ( arr extractText )
>>^ spreadChoice >>?! second text
)
- >>?§ (<>)
+ >>?% (<>)
--
extractText :: XML.Content -> Fallible String
extractText (XML.Text cData) = succeedWith (XML.cdData cData)
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
index 7c1764889..8c03d1a09 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
@@ -331,7 +331,7 @@ convertingExtraState v a = withSubStateF setVAsExtraState modifyWithA
where
setVAsExtraState = liftAsSuccess $ extractFromState id >>^ replaceExtraState v
modifyWithA = keepingTheValue (moreState ^>> a)
- >>^ spreadChoice >>?§ flip replaceExtraState
+ >>^ spreadChoice >>?% flip replaceExtraState
-- | First sets the extra state to the new value. Then produces a new
-- extra state with a converter that uses the new state. Finally, the
@@ -413,14 +413,14 @@ elemName :: (NameSpaceID nsID)
-> XMLConverter nsID extraState x XML.QName
elemName nsID name = lookupNSiri nsID
&&& lookupNSprefix nsID
- >>§ XML.QName name
+ >>% XML.QName name
-- | Checks if a given element matches both a specified namespace id
-- and a specified element name
elemNameIs :: (NameSpaceID nsID)
=> nsID -> ElementName
-> XMLConverter nsID extraState XML.Element Bool
-elemNameIs nsID name = keepingTheValue (lookupNSiri nsID) >>§ hasThatName
+elemNameIs nsID name = keepingTheValue (lookupNSiri nsID) >>% hasThatName
where hasThatName e iri = let elName = XML.elName e
in XML.qName elName == name
&& XML.qURI elName == iri
@@ -461,8 +461,8 @@ currentElemIs'' nsID name = ( (getCurrentElement >>^ XML.elName >>>
(XML.qName >>^ (&&).(== name) )
^&&&^
(XML.qIRI >>^ (==) )
- ) >>§ (.)
- ) &&& lookupNSiri nsID >>§ ($)
+ ) >>% (.)
+ ) &&& lookupNSiri nsID >>% ($)
-}
--
@@ -487,7 +487,7 @@ findChildren :: (NameSpaceID nsID)
-> XMLConverter nsID extraState x [XML.Element]
findChildren nsID name = elemName nsID name
&&& getCurrentElement
- >>§ XML.findChildren
+ >>% XML.findChildren
--
filterChildren :: (XML.Element -> Bool)
@@ -508,7 +508,7 @@ findChild' :: (NameSpaceID nsID)
-> XMLConverter nsID extraState x (Maybe XML.Element)
findChild' nsID name = elemName nsID name
&&& getCurrentElement
- >>§ XML.findChild
+ >>% XML.findChild
--
findChild :: (NameSpaceID nsID)
@@ -596,7 +596,7 @@ isThatTheAttrValue :: (NameSpaceID nsID)
isThatTheAttrValue nsID attrName
= keepingTheValue
(findAttr nsID attrName)
- >>§ right.(==)
+ >>% right.(==)
-- | Lookup value in a dictionary, fail if no attribute found or value
-- not in dictionary
@@ -669,7 +669,7 @@ findAttr' :: (NameSpaceID nsID)
-> XMLConverter nsID extraState x (Maybe AttributeValue)
findAttr' nsID attrName = elemName nsID attrName
&&& getCurrentElement
- >>§ XML.findAttr
+ >>% XML.findAttr
-- | Return value as string or fail
findAttr :: (NameSpaceID nsID)
@@ -787,7 +787,7 @@ prepareIteration :: (NameSpaceID nsID)
-> XMLConverter nsID extraState b [(b, XML.Element)]
prepareIteration nsID name = keepingTheValue
(findChildren nsID name)
- >>§ distributeValue
+ >>% distributeValue
-- | Applies a converter to every child element of a specific type.
-- Collects results in a 'Monoid'.
@@ -877,9 +877,9 @@ makeMatcherE nsID name c = ( second (
elemNameIs nsID name
>>^ bool Nothing (Just tryC)
)
- >>§ (<|>)
+ >>% (<|>)
) &&&^ snd
- where tryC = (fst ^&&& executeThere c >>§ recover) &&&^ snd
+ where tryC = (fst ^&&& executeThere c >>% recover) &&&^ snd
-- Helper function: The @c@ is actually a converter that is to be selected by
-- matching XML content to the first two parameters.
@@ -899,14 +899,14 @@ makeMatcherC nsID name c = ( second ( contentToElem
>>^ bool Nothing (Just cWithJump)
)
)
- >>§ (<|>)
+ >>% (<|>)
) &&&^ snd
where cWithJump = ( fst
^&&& ( second contentToElem
>>> spreadChoice
^>>? executeThere c
)
- >>§ recover)
+ >>% recover)
&&&^ snd
contentToElem :: FallibleXMLConverter nsID extraState XML.Content XML.Element
contentToElem = arr $ \e -> case e of
diff --git a/src/Text/Pandoc/Readers/Odt/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Namespaces.hs
index e28056814..deb009998 100644
--- a/src/Text/Pandoc/Readers/Odt/Namespaces.hs
+++ b/src/Text/Pandoc/Readers/Odt/Namespaces.hs
@@ -107,4 +107,4 @@ nsIDs = [
("http://www.w3.org/1999/xhtml" , NsXHtml ),
("http://www.w3.org/2002/xforms" , NsXForms ),
("http://www.w3.org/1999/xlink" , NsXLink )
- ] \ No newline at end of file
+ ]
diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
index e403424f6..96cfed0b3 100644
--- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
@@ -174,7 +174,7 @@ findPitch :: XMLReaderSafe FontPitches _x (Maybe FontPitch)
findPitch = ( lookupAttr NsStyle "font-pitch"
`ifFailedDo` findAttr NsStyle "font-name"
>>? ( keepingTheValue getExtraState
- >>§ M.lookup
+ >>% M.lookup
>>^ maybeToChoice
)
)
@@ -447,7 +447,7 @@ readAllStyles :: StyleReader _x Styles
readAllStyles = ( readFontPitches
>>?! ( readAutomaticStyles
&&& readStyles ))
- >>?§? chooseMax
+ >>?%? chooseMax
-- all top elements are always on the same hierarchy level
--