diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 392b17bbc..1d0400d96 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -512,6 +512,7 @@ inline =
          , underline
          , code
          , math
+         , displayMath
          , verbatim
          , subscript
          , superscript
@@ -607,7 +608,15 @@ verbatim  :: OrgParser Inlines
 verbatim  = B.rawInline "" <$> verbatimBetween '~'
 
 math      :: OrgParser Inlines
-math      = B.math         <$> mathStringBetween '$'
+math      = B.math         <$> choice [ math1CharBetween '$'
+                                      , mathStringBetween '$'
+                                      , rawMathBetween "\\(" "\\)"
+                                      ]
+
+displayMath :: OrgParser Inlines
+displayMath = B.displayMath <$> choice [ rawMathBetween "\\[" "\\]"
+                                       , rawMathBetween "$$"  "$$"
+                                       ]
 
 subscript :: OrgParser Inlines
 subscript = B.subscript    <$> (try $ char '_' *> maybeGroupedByBraces)
@@ -655,6 +664,21 @@ mathStringBetween c = try $ do
   final <- mathEnd c
   return $ body ++ [final]
 
+-- | Parse a single character between @c@ using math rules
+math1CharBetween :: Char
+                -> OrgParser String
+math1CharBetween c = try $ do
+  char c
+  res <- noneOf $ c:mathForbiddenBorderChars
+  char c
+  eof <|> lookAhead (oneOf mathPostChars) *> return ()
+  return [res]
+
+rawMathBetween :: String
+               -> String
+               -> OrgParser String
+rawMathBetween s e = try $ string s *> manyTill anyChar (try $ string e)
+
 -- | Parses the start (opening character) of emphasis
 emphasisStart :: Char -> OrgParser Char
 emphasisStart c = try $ do
@@ -747,7 +771,7 @@ emphasisAllowedNewlines = 1
 
 -- | Chars allowed after an inline ($...$) math statement
 mathPostChars :: [Char]
-mathPostChars = "\t\n \"',-.:;?"
+mathPostChars = "\t\n \"'),-.:;?"
 
 -- | Chars not allowed at the (inner) border of math
 mathForbiddenBorderChars :: [Char]
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index efd8fe977..9e9482e45 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -54,14 +54,26 @@ tests =
           "=Robot.rock()=" =?>
           para (code "Robot.rock()")
 
-      , "Math" =:
-          "$E=mc^2$" =?>
-           para (math "E=mc^2")
-
       , "Verbatim" =:
           "~word for word~" =?>
           para (rawInline "" "word for word")
 
+      , "Math $..$" =:
+          "$E=mc^2$" =?>
+           para (math "E=mc^2")
+
+      , "Math $$..$$" =:
+          "$$E=mc^2$$" =?>
+          para (displayMath "E=mc^2")
+
+      , "Math \\[..\\]" =:
+          "\\[E=ℎν\\]" =?>
+          para (displayMath "E=ℎν")
+
+      , "Math \\(..\\)" =:
+          "\\(σ_x σ_p ≥ \\frac{ℏ}{2}\\)" =?>
+          para (math "σ_x σ_p ≥ \\frac{ℏ}{2}")
+
       , "Symbol" =:
           "A * symbol" =?>
           para (str "A" <> space <> str "*" <> space <> "symbol")
@@ -86,14 +98,19 @@ tests =
           unlines [ "this+that+ +so+on"
                   , "seven*eight* nine*"
                   , "+not+funny+"
-                  , "this == self"
                   ] =?>
           para (spcSep [ "this+that+", "+so+on"
                        , "seven*eight*", "nine*"
                        , strikeout "not+funny"
-                       , "this" <> space <> "==" <> space <> "self"
                        ])
 
+      , "No empty markup" =:
+          -- FIXME: __ is erroneously parsed as subscript "_"
+          -- "// ** __ ++ == ~~ $$" =?>
+          -- para (spcSep [ "//", "**", "__", "++", "==", "~~", "$$" ])
+          "// ** ++ == ~~ $$" =?>
+          para (spcSep [ "//", "**", "++", "==", "~~", "$$" ])
+
       , "Adherence to Org's rules for markup borders" =:
           "/t/& a/ / ./r/ (*l*) /e/! /b/." =?>
           para (spcSep [ emph $ "t/&" <> space <> "a"
@@ -109,6 +126,13 @@ tests =
           para ((math "a\nb\nc") <> space <>
                 spcSep [ "$d", "e", "f", "g$" ])
 
+      , "Single-character math" =:
+          "$a$ $b$! $c$?" =?>
+          para (spcSep [ math "a"
+                       , "$b$!"
+                       , (math "c") <> "?"
+                       ])
+
       , "Markup may not span more than two lines" =:
           unlines [ "/this *is +totally", "nice+ not*", "emph/" ] =?>
           para (spcSep [ "/this"