diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index 0c3840979..33f2049e1 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -192,15 +192,78 @@ endline = try $ do
 cite :: OrgParser (F Inlines)
 cite = try $ do
   guardEnabled Ext_citations
-  (cs, raw) <- withRaw normalCite
+  (cs, raw) <- withRaw (pandocOrgCite <|> orgRefCite)
   return $ (flip B.cite (B.text raw)) <$> cs
 
-normalCite :: OrgParser (F [Citation])
-normalCite = try $  char '['
-                 *> skipSpaces
-                 *> citeList
-                 <* skipSpaces
-                 <* char ']'
+-- | A citation in Pandoc Org-mode style (@[\@citekey]@).
+pandocOrgCite :: OrgParser (F [Citation])
+pandocOrgCite = try $
+  char '[' *> skipSpaces *> citeList <* skipSpaces <* char ']'
+
+orgRefCite :: OrgParser (F [Citation])
+orgRefCite = try $ normalOrgRefCite <|> (fmap (:[]) <$> linkLikeOrgRefCite)
+
+normalOrgRefCite :: OrgParser (F [Citation])
+normalOrgRefCite = try $ do
+  mode <- orgRefCiteMode
+  sequence <$> sepBy1 (orgRefCiteList mode) (char ',')
+ where
+   -- | A list of org-ref style citation keys, parsed as citation of the given
+   -- citation mode.
+   orgRefCiteList :: CitationMode -> OrgParser (F Citation)
+   orgRefCiteList citeMode = try $ do
+     key <- orgRefCiteKey
+     returnF $ Citation
+      { citationId      = key
+      , citationPrefix  = mempty
+      , citationSuffix  = mempty
+      , citationMode    = citeMode
+      , citationNoteNum = 0
+      , citationHash    = 0
+      }
+
+-- | Read a link-like org-ref style citation.  The citation includes pre and
+-- post text.  However, multiple citations are not possible due to limitations
+-- in the syntax.
+linkLikeOrgRefCite :: OrgParser (F Citation)
+linkLikeOrgRefCite = try $ do
+  _    <- string "[["
+  mode <- orgRefCiteMode
+  key  <- orgRefCiteKey
+  _    <- string "]["
+  pre  <- trimInlinesF . mconcat <$> manyTill inline (try $ string "::")
+  spc  <- option False (True <$ spaceChar)
+  suf  <- trimInlinesF . mconcat <$> manyTill inline (try $ string "]]")
+  return $ do
+    pre' <- pre
+    suf' <- suf
+    return Citation
+      { citationId      = key
+      , citationPrefix  = B.toList pre'
+      , citationSuffix  = B.toList (if spc then B.space <> suf' else suf')
+      , citationMode    = mode
+      , citationNoteNum = 0
+      , citationHash    = 0
+      }
+
+-- | Read a citation key.  The characters allowed in citation keys are taken
+-- from the `org-ref-cite-re` variable in `org-ref.el`.
+orgRefCiteKey :: OrgParser String
+orgRefCiteKey = try . many1 . satisfy $ \c ->
+                  isAlphaNum c || c `elem` ("-_:\\./"::String)
+
+-- | Supported citation types.  Only a small subset of org-ref types is
+-- supported for now.  TODO: rewrite this, use LaTeX reader as template.
+orgRefCiteMode :: OrgParser CitationMode
+orgRefCiteMode =
+  choice $ map (\(s, mode) -> mode <$ try (string s <* char ':'))
+    [ ("cite", AuthorInText)
+    , ("citep", NormalCitation)
+    , ("citep*", NormalCitation)
+    , ("citet", AuthorInText)
+    , ("citet*", AuthorInText)
+    , ("citeyear", SuppressAuthor)
+    ]
 
 citeList :: OrgParser (F [Citation])
 citeList = sequence <$> sepBy1 citation (try $ char ';' *> skipSpaces)
diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs
index 9a1420645..0b6b876d8 100644
--- a/src/Text/Pandoc/Readers/Org/Parsing.hs
+++ b/src/Text/Pandoc/Readers/Org/Parsing.hs
@@ -79,6 +79,7 @@ module Text.Pandoc.Readers.Org.Parsing
   , skipMany1
   , spaces
   , anyChar
+  , satisfy
   , string
   , count
   , eof
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index 780053059..7090e8b49 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -300,6 +300,42 @@ tests =
                          , citationHash = 0}
           in (para $ cite [citation] "[see @item1 p. 34-35]")
 
+      , "Org-ref simple citation" =:
+        "cite:pandoc" =?>
+        let citation = Citation
+                       { citationId = "pandoc"
+                       , citationPrefix = mempty
+                       , citationSuffix = mempty
+                       , citationMode = AuthorInText
+                       , citationNoteNum = 0
+                       , citationHash = 0
+                       }
+        in (para $ cite [citation] "cite:pandoc")
+
+      , "Org-ref simple citep citation" =:
+        "citep:pandoc" =?>
+        let citation = Citation
+                       { citationId = "pandoc"
+                       , citationPrefix = mempty
+                       , citationSuffix = mempty
+                       , citationMode = NormalCitation
+                       , citationNoteNum = 0
+                       , citationHash = 0
+                       }
+        in (para $ cite [citation] "citep:pandoc")
+
+      , "Org-ref extended citation" =:
+        "[[citep:Dominik201408][See page 20::, for example]]" =?>
+        let citation = Citation
+                       { citationId = "Dominik201408"
+                       , citationPrefix = toList "See page 20"
+                       , citationSuffix = toList ", for example"
+                       , citationMode = NormalCitation
+                       , citationNoteNum = 0
+                       , citationHash = 0
+                       }
+        in (para $ cite [citation] "[[citep:Dominik201408][See page 20::, for example]]")
+
       , "Inline LaTeX symbol" =:
           "\\dots" =?>
           para "…"