diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index c18aa331f..d30c74230 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -161,7 +161,8 @@ module Text.Pandoc.Parsing ( anyLine,
                              setSourceColumn,
                              setSourceLine,
                              newPos,
-                             addWarning
+                             addWarning,
+                             (<+?>)
                              )
 where
 
@@ -1245,3 +1246,7 @@ addWarning mbpos msg =
 
 generalize :: (Monad m) => Parser s st a -> ParserT s st m a
 generalize m = mkPT (\ s -> (return $ (return . runIdentity) <$> runIdentity (runParsecT m s)))
+
+infixr 5 <+?>
+(<+?>) :: (Monoid a, Monad m) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a
+a <+?> b = a >>= flip fmap (try b <|> return mempty) . (<>)
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index ccda83576..5e0cef4f8 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1487,7 +1487,8 @@ code = try $ do
 
 math :: MarkdownParser Inlines
 math =  (B.displayMath <$> (mathDisplay >>= applyMacros'))
-     <|> (B.math <$> (mathInline >>= applyMacros'))
+     <|> ((B.math <$> (mathInline >>= applyMacros')) <+?>
+                            ((getOption readerSmart >>= guard) *> apostrophe <* notFollowedBy space))
 
 -- Parses material enclosed in *s, **s, _s, or __s.
 -- Designed to avoid backtracking.
diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs
index 03884a8e5..6c8e9f306 100644
--- a/tests/Tests/Readers/Markdown.hs
+++ b/tests/Tests/Readers/Markdown.hs
@@ -208,6 +208,9 @@ tests = [ testGroup "inline code"
           , test markdownSmart "apostrophe in French"
             ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
             =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
+          , test markdownSmart "apostrophe after math" $ -- issue #1909
+              "The value of the $x$'s and the systems' condition." =?>
+              para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.")
           ]
         , testGroup "footnotes"
           [ "indent followed by newline and flush-left text" =: