[Docx Reader] Get rid of unused NullModifier in Readers.Docx.Combine
This commit is contained in:
parent
48cef91d18
commit
27465638a1
1 changed files with 15 additions and 18 deletions
|
@ -68,7 +68,6 @@ import Text.Pandoc.Builder
|
||||||
|
|
||||||
data Modifier a = Modifier (a -> a)
|
data Modifier a = Modifier (a -> a)
|
||||||
| AttrModifier (Attr -> a -> a) Attr
|
| AttrModifier (Attr -> a -> a) Attr
|
||||||
| NullModifier
|
|
||||||
|
|
||||||
spaceOutInlinesL :: Inlines -> (Inlines, Inlines)
|
spaceOutInlinesL :: Inlines -> (Inlines, Inlines)
|
||||||
spaceOutInlinesL ms = (l, stackInlines fs (m' <> r))
|
spaceOutInlinesL ms = (l, stackInlines fs (m' <> r))
|
||||||
|
@ -94,7 +93,6 @@ isSpace _ = False
|
||||||
|
|
||||||
stackInlines :: [Modifier Inlines] -> Inlines -> Inlines
|
stackInlines :: [Modifier Inlines] -> Inlines -> Inlines
|
||||||
stackInlines [] ms = ms
|
stackInlines [] ms = ms
|
||||||
stackInlines (NullModifier : fs) ms = stackInlines fs ms
|
|
||||||
stackInlines (Modifier f : fs) ms =
|
stackInlines (Modifier f : fs) ms =
|
||||||
if isEmpty ms
|
if isEmpty ms
|
||||||
then stackInlines fs ms
|
then stackInlines fs ms
|
||||||
|
@ -103,23 +101,23 @@ stackInlines (AttrModifier f attr : fs) ms = f attr $ stackInlines fs ms
|
||||||
|
|
||||||
unstackInlines :: Inlines -> ([Modifier Inlines], Inlines)
|
unstackInlines :: Inlines -> ([Modifier Inlines], Inlines)
|
||||||
unstackInlines ms = case ilModifierAndInnards ms of
|
unstackInlines ms = case ilModifierAndInnards ms of
|
||||||
(NullModifier, _) -> ([], ms)
|
Nothing -> ([], ms)
|
||||||
(f, innards ) -> first (f :) $ unstackInlines innards
|
Just (f, inner) -> first (f :) $ unstackInlines inner
|
||||||
|
|
||||||
ilModifierAndInnards :: Inlines -> (Modifier Inlines, Inlines)
|
ilModifierAndInnards :: Inlines -> Maybe (Modifier Inlines, Inlines)
|
||||||
ilModifierAndInnards ils = case viewl $ unMany ils of
|
ilModifierAndInnards ils = case viewl $ unMany ils of
|
||||||
x :< xs | Seq.null xs -> case x of
|
x :< xs | Seq.null xs -> second fromList <$> case x of
|
||||||
Emph lst -> (Modifier emph, fromList lst)
|
Emph lst -> Just (Modifier emph, lst)
|
||||||
Strong lst -> (Modifier strong, fromList lst)
|
Strong lst -> Just (Modifier strong, lst)
|
||||||
SmallCaps lst -> (Modifier smallcaps, fromList lst)
|
SmallCaps lst -> Just (Modifier smallcaps, lst)
|
||||||
Strikeout lst -> (Modifier strikeout, fromList lst)
|
Strikeout lst -> Just (Modifier strikeout, lst)
|
||||||
Underline lst -> (Modifier underline, fromList lst)
|
Underline lst -> Just (Modifier underline, lst)
|
||||||
Superscript lst -> (Modifier superscript, fromList lst)
|
Superscript lst -> Just (Modifier superscript, lst)
|
||||||
Subscript lst -> (Modifier subscript, fromList lst)
|
Subscript lst -> Just (Modifier subscript, lst)
|
||||||
Link attr lst tgt -> (Modifier $ linkWith attr (fst tgt) (snd tgt), fromList lst)
|
Link attr lst tgt -> Just (Modifier $ linkWith attr (fst tgt) (snd tgt), lst)
|
||||||
Span attr lst -> (AttrModifier spanWith attr, fromList lst)
|
Span attr lst -> Just (AttrModifier spanWith attr, lst)
|
||||||
_ -> (NullModifier, ils)
|
_ -> Nothing
|
||||||
_ -> (NullModifier, ils)
|
_ -> Nothing
|
||||||
|
|
||||||
inlinesL :: Inlines -> (Inlines, Inlines)
|
inlinesL :: Inlines -> (Inlines, Inlines)
|
||||||
inlinesL ils = case viewl $ unMany ils of
|
inlinesL ils = case viewl $ unMany ils of
|
||||||
|
@ -181,7 +179,6 @@ combineBlocks bs cs = bs <> cs
|
||||||
instance (Monoid a, Eq a) => Eq (Modifier a) where
|
instance (Monoid a, Eq a) => Eq (Modifier a) where
|
||||||
(Modifier f) == (Modifier g) = f mempty == g mempty
|
(Modifier f) == (Modifier g) = f mempty == g mempty
|
||||||
(AttrModifier f attr) == (AttrModifier g attr') = f attr mempty == g attr' mempty
|
(AttrModifier f attr) == (AttrModifier g attr') = f attr mempty == g attr' mempty
|
||||||
NullModifier == NullModifier = True
|
|
||||||
_ == _ = False
|
_ == _ = False
|
||||||
|
|
||||||
isEmpty :: (Monoid a, Eq a) => a -> Bool
|
isEmpty :: (Monoid a, Eq a) => a -> Bool
|
||||||
|
|
Loading…
Add table
Reference in a new issue