Docx Reader: Change state handling.
We don't need `updateDState` -- the built-in `modify` works just fine. And we redefine `withDState` to use modify.
This commit is contained in:
parent
643435f1de
commit
a4671afd64
1 changed files with 12 additions and 16 deletions
|
@ -112,18 +112,13 @@ data DEnv = DEnv { docxOptions :: ReaderOptions
|
||||||
|
|
||||||
type DocxContext = ReaderT DEnv (State DState)
|
type DocxContext = ReaderT DEnv (State DState)
|
||||||
|
|
||||||
updateDState :: (DState -> DState) -> DocxContext ()
|
withDState :: (DState -> DState) -> DocxContext a -> DocxContext a
|
||||||
updateDState f = do
|
withDState f dctx = do
|
||||||
st <- get
|
ds <- get
|
||||||
put $ f st
|
modify f
|
||||||
|
ctx' <- dctx
|
||||||
withDState :: DState -> DocxContext a -> DocxContext a
|
put ds
|
||||||
withDState ds dctx = do
|
return ctx'
|
||||||
ds' <- get
|
|
||||||
updateDState (\_ -> ds)
|
|
||||||
dctx' <- dctx
|
|
||||||
put ds'
|
|
||||||
return dctx'
|
|
||||||
|
|
||||||
evalDocxContext :: DocxContext a -> DEnv -> DState -> a
|
evalDocxContext :: DocxContext a -> DEnv -> DState -> a
|
||||||
evalDocxContext ctx env st = evalState (runReaderT ctx env) st
|
evalDocxContext ctx env st = evalState (runReaderT ctx env) st
|
||||||
|
@ -307,8 +302,9 @@ parPartToInlines (BookMark _ anchor) =
|
||||||
let newAnchor = case anchor `elem` (M.elems anchorMap) of
|
let newAnchor = case anchor `elem` (M.elems anchorMap) of
|
||||||
True -> uniqueIdent [Str anchor] (M.elems anchorMap)
|
True -> uniqueIdent [Str anchor] (M.elems anchorMap)
|
||||||
False -> anchor
|
False -> anchor
|
||||||
updateDState $ \s -> s { docxAnchorMap = M.insert anchor newAnchor anchorMap}
|
|
||||||
return [Span (anchor, ["anchor"], []) []]
|
return [Span (anchor, ["anchor"], []) []]
|
||||||
|
modify $ \s -> s { docxAnchorMap = M.insert anchor newAnchor anchorMap}
|
||||||
|
return [Span (newAnchor, ["anchor"], []) []]
|
||||||
parPartToInlines (Drawing fp bs) = do
|
parPartToInlines (Drawing fp bs) = do
|
||||||
return $ case True of -- TODO: add self-contained images
|
return $ case True of -- TODO: add self-contained images
|
||||||
True -> [Image [] (fp, "")]
|
True -> [Image [] (fp, "")]
|
||||||
|
@ -427,8 +423,8 @@ oMathElemToTexString (Matrix bases) = do
|
||||||
s <- liftM (intercalate " \\\\\n")(mapM rowString bases)
|
s <- liftM (intercalate " \\\\\n")(mapM rowString bases)
|
||||||
return $ printf "\\begin{matrix}\n%s\n\\end{matrix}" s
|
return $ printf "\\begin{matrix}\n%s\n\\end{matrix}" s
|
||||||
oMathElemToTexString (NAry style sub sup base) | Just c <- nAryChar style = do
|
oMathElemToTexString (NAry style sub sup base) | Just c <- nAryChar style = do
|
||||||
ds <- gets (\s -> s{docxInTexSubscript = True})
|
subString <- withDState (\s -> s{docxInTexSubscript = True}) $
|
||||||
subString <- withDState ds $ concatMapM oMathElemToTexString sub
|
concatMapM oMathElemToTexString sub
|
||||||
supString <- concatMapM oMathElemToTexString sup
|
supString <- concatMapM oMathElemToTexString sup
|
||||||
baseString <- baseToTexString base
|
baseString <- baseToTexString base
|
||||||
return $ case M.lookup c uniconvMap of
|
return $ case M.lookup c uniconvMap of
|
||||||
|
@ -505,7 +501,7 @@ makeHeaderAnchor (Header n (_, classes, kvs) ils) =
|
||||||
do
|
do
|
||||||
hdrIDMap <- gets docxAnchorMap
|
hdrIDMap <- gets docxAnchorMap
|
||||||
let newIdent = uniqueIdent ils (M.elems hdrIDMap)
|
let newIdent = uniqueIdent ils (M.elems hdrIDMap)
|
||||||
updateDState $ \s -> s {docxAnchorMap = M.insert newIdent newIdent hdrIDMap}
|
modify $ \s -> s {docxAnchorMap = M.insert newIdent newIdent hdrIDMap}
|
||||||
return $ Header n (newIdent, classes, kvs) ils
|
return $ Header n (newIdent, classes, kvs) ils
|
||||||
makeHeaderAnchor blk = return blk
|
makeHeaderAnchor blk = return blk
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue