Muse reader: replace pattern matching with "when"

This commit is contained in:
Alexander Krotov 2018-04-07 19:06:40 +03:00
parent 828bfc749d
commit 4cb053ce3d

View file

@ -50,7 +50,7 @@ import Data.List (stripPrefix, intercalate)
import Data.List.Split (splitOn) import Data.List.Split (splitOn)
import qualified Data.Map as M import qualified Data.Map as M
import qualified Data.Set as Set import qualified Data.Set as Set
import Data.Maybe (fromMaybe, isNothing) import Data.Maybe (fromMaybe, isJust, isNothing)
import Data.Text (Text, unpack) import Data.Text (Text, unpack)
import System.FilePath (takeExtension) import System.FilePath (takeExtension)
import Text.HTML.TagSoup import Text.HTML.TagSoup
@ -474,9 +474,8 @@ amuseNoteBlockUntil end = try $ do
updateState (\st -> st { museInPara = False }) updateState (\st -> st { museInPara = False })
(content, e) <- listItemContentsUntil (sourceColumn pos - 1) (fail "x") end (content, e) <- listItemContentsUntil (sourceColumn pos - 1) (fail "x") end
oldnotes <- museNotes <$> getState oldnotes <- museNotes <$> getState
case M.lookup ref oldnotes of when (isJust (M.lookup ref oldnotes))
Just _ -> logMessage $ DuplicateNoteReference ref pos (logMessage $ DuplicateNoteReference ref pos)
Nothing -> return ()
updateState $ \s -> s{ museNotes = M.insert ref (pos, content) oldnotes } updateState $ \s -> s{ museNotes = M.insert ref (pos, content) oldnotes }
return (mempty, e) return (mempty, e)
@ -489,9 +488,8 @@ emacsNoteBlock = try $ do
ref <- noteMarker <* skipSpaces ref <- noteMarker <* skipSpaces
content <- mconcat <$> blocksTillNote content <- mconcat <$> blocksTillNote
oldnotes <- museNotes <$> getState oldnotes <- museNotes <$> getState
case M.lookup ref oldnotes of when (isJust (M.lookup ref oldnotes))
Just _ -> logMessage $ DuplicateNoteReference ref pos (logMessage $ DuplicateNoteReference ref pos)
Nothing -> return ()
updateState $ \s -> s{ museNotes = M.insert ref (pos, content) oldnotes } updateState $ \s -> s{ museNotes = M.insert ref (pos, content) oldnotes }
return mempty return mempty
where where