diff --git a/pandoc.cabal b/pandoc.cabal
index e22908918..ac28ad068 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -246,7 +246,7 @@ Library
                  old-locale >= 1 && < 1.1,
                  time >= 1.2 && < 1.5,
                  HTTP >= 4000.0.5 && < 4000.3,
-                 texmath >= 0.6.3 && < 0.7,
+                 texmath >= 0.6.4 && < 0.7,
                  xml >= 1.3.12 && < 1.4,
                  random >= 1 && < 1.1,
                  extensible-exceptions >= 0.1 && < 0.2,
diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs
index fe49a992e..1f7088f72 100644
--- a/src/Text/Pandoc/Readers/TeXMath.hs
+++ b/src/Text/Pandoc/Readers/TeXMath.hs
@@ -30,93 +30,13 @@ Conversion of TeX math to a list of 'Pandoc' inline elements.
 module Text.Pandoc.Readers.TeXMath ( readTeXMath ) where
 
 import Text.Pandoc.Definition
-import Text.TeXMath.Types
-import Text.TeXMath.Parser
+import Text.TeXMath
 
 -- | Converts a raw TeX math formula to a list of 'Pandoc' inlines.
 -- Defaults to raw formula between @$@ characters if entire formula
 -- can't be converted.
 readTeXMath :: String    -- ^ String to parse (assumes @'\n'@ line endings)
             -> [Inline]
-readTeXMath inp = case texMathToPandoc inp of
+readTeXMath inp = case texMathToPandoc DisplayInline inp of
                         Left _    -> [Str ("$" ++ inp ++ "$")]
                         Right res -> res
-
-texMathToPandoc :: String -> Either String [Inline]
-texMathToPandoc inp = inp `seq`
-  case parseFormula inp of
-         Left err    -> Left err
-         Right exps  -> case expsToInlines exps of
-                             Nothing  -> Left "Formula too complex for [Inline]"
-                             Just r   -> Right r
-
-expsToInlines :: [Exp] -> Maybe [Inline]
-expsToInlines xs = do
-  res <- mapM expToInlines xs
-  return (concat res)
-
-expToInlines :: Exp -> Maybe [Inline]
-expToInlines (ENumber s) = Just [Str s]
-expToInlines (EIdentifier s) = Just [Emph [Str s]]
-expToInlines (EMathOperator s) = Just [Str s]
-expToInlines (ESymbol t s) = Just $ addSpace t (Str s)
-  where addSpace Op x = [x, thinspace]
-        addSpace Bin x = [medspace, x, medspace]
-        addSpace Rel x = [widespace, x, widespace]
-        addSpace Pun x = [x, thinspace]
-        addSpace _ x = [x]
-        thinspace = Str "\x2006"
-        medspace  = Str "\x2005"
-        widespace = Str "\x2004"
-expToInlines (EStretchy x) = expToInlines x
-expToInlines (EDelimited start end xs) = do
-  xs' <- mapM expToInlines xs
-  return $ [Str start] ++ concat xs' ++ [Str end]
-expToInlines (EGrouped xs) = expsToInlines xs
-expToInlines (ESpace "0.167em") = Just [Str "\x2009"]
-expToInlines (ESpace "0.222em") = Just [Str "\x2005"]
-expToInlines (ESpace "0.278em") = Just [Str "\x2004"]
-expToInlines (ESpace "0.333em") = Just [Str "\x2004"]
-expToInlines (ESpace "1em")     = Just [Str "\x2001"]
-expToInlines (ESpace "2em")     = Just [Str "\x2001\x2001"]
-expToInlines (ESpace _)         = Just [Str " "]
-expToInlines (EBinary _ _ _) = Nothing
-expToInlines (ESub x y) = do
-  x' <- expToInlines x
-  y' <- expToInlines y
-  return $ x' ++ [Subscript y']
-expToInlines (ESuper x y) = do
-  x' <- expToInlines x
-  y' <- expToInlines y
-  return $ x' ++ [Superscript y']
-expToInlines (ESubsup x y z) = do
-  x' <- expToInlines x
-  y' <- expToInlines y
-  z' <- expToInlines z
-  return $ x' ++ [Subscript y'] ++ [Superscript z']
-expToInlines (EDown x y) = expToInlines (ESub x y)
-expToInlines (EUp x y) = expToInlines (ESuper x y)
-expToInlines (EDownup x y z) = expToInlines (ESubsup x y z)
-expToInlines (EText TextNormal x) = Just [Str x]
-expToInlines (EText TextBold x) = Just [Strong [Str x]]
-expToInlines (EText TextMonospace x) = Just [Code nullAttr x]
-expToInlines (EText TextItalic x) = Just [Emph [Str x]]
-expToInlines (EText _ x) = Just [Str x]
-expToInlines (EOver (EGrouped [EIdentifier [c]]) (ESymbol Accent [accent])) =
-    case accent of
-         '\x203E' -> Just [Emph [Str [c,'\x0304']]]  -- bar
-         '\x00B4' -> Just [Emph [Str [c,'\x0301']]]  -- acute
-         '\x0060' -> Just [Emph [Str [c,'\x0300']]]  -- grave
-         '\x02D8' -> Just [Emph [Str [c,'\x0306']]]  -- breve
-         '\x02C7' -> Just [Emph [Str [c,'\x030C']]]  -- check
-         '.'      -> Just [Emph [Str [c,'\x0307']]]  -- dot
-         '\x00B0' -> Just [Emph [Str [c,'\x030A']]]  -- ring
-         '\x20D7' -> Just [Emph [Str [c,'\x20D7']]]  -- arrow right
-         '\x20D6' -> Just [Emph [Str [c,'\x20D6']]]  -- arrow left
-         '\x005E' -> Just [Emph [Str [c,'\x0302']]]  -- hat
-         '\x0302' -> Just [Emph [Str [c,'\x0302']]]  -- hat
-         '~'      -> Just [Emph [Str [c,'\x0303']]]  -- tilde
-         _        -> Nothing
-expToInlines _ = Nothing
-
-