diff options
Diffstat (limited to 'src/Text/Pandoc/Readers/Odt/Generic')
| -rw-r--r-- | src/Text/Pandoc/Readers/Odt/Generic/Utils.hs | 4 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs | 20 |
2 files changed, 11 insertions, 13 deletions
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs index edefe3c70..a065e817d 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs @@ -34,6 +34,7 @@ import qualified Data.Foldable as F (Foldable, foldr) import Data.Maybe import Data.Text (Text) import qualified Data.Text as T +import Text.Read -- | Equivalent to -- > foldr (.) id @@ -104,9 +105,6 @@ uncurry4 fun (a,b,c,d ) = fun a b c d uncurry5 fun (a,b,c,d,e ) = fun a b c d e uncurry6 fun (a,b,c,d,e,f ) = fun a b c d e f -swap :: (a,b) -> (b,a) -swap (a,b) = (b,a) - -- | A version of "Data.List.find" that uses a converter to a Maybe instance. -- The returned value is the first which the converter returns in a 'Just' -- wrapper. diff --git a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs index 0d921e23b..b384d3504 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs @@ -73,7 +73,7 @@ import Text.Pandoc.Readers.Odt.Arrows.Utils import Text.Pandoc.Readers.Odt.Generic.Namespaces import Text.Pandoc.Readers.Odt.Generic.Utils import Text.Pandoc.Readers.Odt.Generic.Fallible - +import Prelude hiding (withState, first, second) -------------------------------------------------------------------------------- -- Basis types for readability -------------------------------------------------------------------------------- @@ -101,7 +101,7 @@ data XMLConverterState nsID extraState where -- Arguably, a real Zipper would be better. But that is an -- optimization that can be made at a later time, e.g. when -- replacing Text.XML.Light. - parentElements :: [XML.Element] + parentElements :: NonEmpty XML.Element -- | A map from internal namespace IDs to the namespace prefixes -- used in XML elements , namespacePrefixes :: NameSpacePrefixes nsID @@ -126,7 +126,7 @@ createStartState :: (NameSpaceID nsID) -> XMLConverterState nsID extraState createStartState element extraState = XMLConverterState - { parentElements = [element] + { parentElements = element :| [] , namespacePrefixes = M.empty , namespaceIRIs = getInitialIRImap , moreState = extraState @@ -152,8 +152,8 @@ currentElement state = head (parentElements state) -- | Replace the current position by another, modifying the extra state -- in the process swapStack' :: XMLConverterState nsID extraState - -> [XML.Element] - -> ( XMLConverterState nsID extraState , [XML.Element] ) + -> NonEmpty XML.Element + -> ( XMLConverterState nsID extraState , NonEmpty XML.Element ) swapStack' state stack = ( state { parentElements = stack } , parentElements state @@ -163,13 +163,13 @@ swapStack' state stack pushElement :: XML.Element -> XMLConverterState nsID extraState -> XMLConverterState nsID extraState -pushElement e state = state { parentElements = e:parentElements state } +pushElement e state = state { parentElements = e :| toList (parentElements state) } -- | Pop the top element from the call stack, unless it is the last one. popElement :: XMLConverterState nsID extraState -> Maybe (XMLConverterState nsID extraState) popElement state - | _:es@(_:_) <- parentElements state = Just $ state { parentElements = es } + | _:|(e:es) <- parentElements state = Just $ state { parentElements = e:|es } | otherwise = Nothing -------------------------------------------------------------------------------- @@ -293,7 +293,7 @@ readNSattributes = fromState $ \state -> maybe (state, failEmpty ) => XMLConverterState nsID extraState -> Maybe (XMLConverterState nsID extraState) extractNSAttrs startState - = foldl (\state d -> state >>= addNS d) + = foldl' (\state d -> state >>= addNS d) (Just startState) nsAttribs where nsAttribs = mapMaybe readNSattr (XML.elAttribs element) @@ -553,7 +553,7 @@ jumpThere = withState (\state element ) -- -swapStack :: XMLConverter nsID extraState [XML.Element] [XML.Element] +swapStack :: XMLConverter nsID extraState (NonEmpty XML.Element) (NonEmpty XML.Element) swapStack = withState swapStack' -- @@ -568,7 +568,7 @@ jumpBack = tryModifyState (popElement >>> maybeToChoice) -- accessible to the converter. switchingTheStack :: XMLConverter nsID moreState a b -> XMLConverter nsID moreState (a, XML.Element) b -switchingTheStack a = second ( (:[]) ^>> swapStack ) +switchingTheStack a = second ( (:|[]) ^>> swapStack ) >>> first a >>> second swapStack >>^ fst |
