diff --git a/pandoc.cabal b/pandoc.cabal
index aad149c8a..058378199 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -168,7 +168,7 @@ Library
     Build-depends: highlighting-kate >= 0.2.7.1
     cpp-options:   -D_HIGHLIGHTING
   if flag(citeproc)
-    Build-depends: citeproc-hs >= 0.2
+    Build-depends: citeproc-hs >= 0.3 && < 0.4
     cpp-options:   -D_CITEPROC
   if impl(ghc >= 6.12)
     Ghc-Options:   -O2 -Wall -fno-warn-unused-do-bind
diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs
index 16215505e..d8a4659e7 100644
--- a/src/Text/Pandoc/Biblio.hs
+++ b/src/Text/Pandoc/Biblio.hs
@@ -30,7 +30,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
 module Text.Pandoc.Biblio ( processBiblio ) where
 
 import Control.Monad ( when )
-import Data.Char ( toUpper )
 import Data.List
 import Data.Unique
 import Text.CSL hiding ( Cite(..), Citation(..) )
@@ -52,9 +51,9 @@ processBiblio cf r p
                                   ncits  = map (queryWith getCite) $ queryWith getNote p'
                                   needNt = cits \\ concat ncits
                               in (,) needNt $ getNoteCitations needNt p'
-            result     = citeproc' csl r (setNearNote csl $ map (map toCslCite) grps)
+            result     = citeproc csl r (setNearNote csl $ map (map toCslCite) grps)
             cits_map   = zip grps (citations result)
-            biblioList = map (read . renderPandoc' csl) (bibliography result)
+            biblioList = map (renderPandoc' csl) (bibliography result)
             Pandoc m b = processWith (processCite csl cits_map) p'
         return . generateNotes nts . Pandoc m $ b ++ biblioList
 
@@ -65,7 +64,7 @@ processCite s cs il
     | otherwise      = il
     where
       process t = case lookup t cs of
-                    Just  i -> read $ renderPandoc s i
+                    Just  i -> renderPandoc s i
                     Nothing -> [Str ("Error processing " ++ show t)]
 
 -- | Retrieve all citations from a 'Pandoc' docuument. To be used with
@@ -91,8 +90,8 @@ getNoteCitations needNote
       in  queryWith getCitation . getCits
 
 setHash :: Citation -> IO Citation
-setHash (Citation i p l nn ao na _)
-    = hashUnique `fmap` newUnique >>= return . Citation i p l nn ao na
+setHash (Citation i p l cm nn _)
+    = hashUnique `fmap` newUnique >>= return . Citation i p l cm nn
 
 generateNotes :: [Inline] -> Pandoc -> Pandoc
 generateNotes needNote = processWith (mvCiteInNote needNote)
@@ -109,12 +108,12 @@ mvCiteInNote is = procInlines mvCite
     where
       mvCite :: [Inline] -> [Inline]
       mvCite inls
-          | x:i:xs <- inls, startWPt xs
-          , x == Space,   i `elem_` is = split i xs ++ mvCite (tailInline xs)
+          | x:i:xs <- inls, startWithPunct xs
+          , x == Space,   i `elem_` is = split i xs ++ mvCite (tailFirstInlineStr xs)
           | x:i:xs <- inls
           , x == Space,   i `elem_` is = mvInNote i :  mvCite xs
           | i:xs <- inls, i `elem_` is
-          , startWPt xs                = split i xs ++ mvCite (tailInline xs)
+          , startWithPunct xs          = split i xs ++ mvCite (tailFirstInlineStr xs)
           | i:xs <- inls, Note _ <- i  = checkNt  i :  mvCite xs
           | i:xs <- inls               = i          :  mvCite xs
           | otherwise                  = []
@@ -124,91 +123,17 @@ mvCiteInNote is = procInlines mvCite
           | Cite t o <- i = Note [Para [Cite t $ sanitize o]]
           | otherwise     = Note [Para [i                  ]]
       sanitize i
-          | endWPt  i = toCapital i
-          | otherwise = toCapital (i ++ [Str "."])
+          | endWithPunct i = toCapital i
+          | otherwise      = toCapital (i ++ [Str "."])
 
       checkPt i
           | Cite c o : xs <- i
-          , endWPt o, startWPt xs
-          , endWPt  o = Cite c (initInline o) : checkPt xs
-          | x:xs <- i = x : checkPt xs
-          | otherwise = []
-      endWPt   = and . map (`elem` ".,;:!?") . lastInline
-      startWPt = and . map (`elem` ".,;:!?") . headInline
+          , endWithPunct o, startWithPunct xs
+          , endWithPunct o = Cite c (initInline o) : checkPt xs
+          | x:xs <- i      = x : checkPt xs
+          | otherwise      = []
       checkNt  = processWith $ procInlines checkPt
 
-headInline :: [Inline] -> String
-headInline [] = []
-headInline (i:_)
-    | Str s <- i = head' s
-    | Space <- i = " "
-    | otherwise  = headInline $ getInline i
-    where
-      head' s = if s /= [] then [head s] else []
-
-lastInline :: [Inline] -> String
-lastInline [] = []
-lastInline (i:[])
-    | Str s <- i = last' s
-    | Space <- i = " "
-    | otherwise  = lastInline $ getInline i
-    where
-      last' s = if s /= [] then [last s] else []
-lastInline (_:xs) = lastInline xs
-
-initInline :: [Inline] -> [Inline]
-initInline [] = []
-initInline (i:[])
-    | Str          s <- i = return $ Str         (init'       s)
-    | Emph        is <- i = return $ Emph        (initInline is)
-    | Strong      is <- i = return $ Strong      (initInline is)
-    | Strikeout   is <- i = return $ Strikeout   (initInline is)
-    | Superscript is <- i = return $ Superscript (initInline is)
-    | Subscript   is <- i = return $ Subscript   (initInline is)
-    | Quoted q    is <- i = return $ Quoted q    (initInline is)
-    | SmallCaps   is <- i = return $ SmallCaps   (initInline is)
-    | Link      is t <- i = return $ Link        (initInline is) t
-    | otherwise           = []
-    where
-      init' s = if s /= [] then init s else []
-initInline (i:xs) = i : initInline xs
-
-tailInline :: [Inline] -> [Inline]
-tailInline = mapHeadInline tail'
-    where
-      tail' s = if s /= [] then tail s else []
-
-toCapital :: [Inline] -> [Inline]
-toCapital = mapHeadInline toCap
-    where
-      toCap s = if s /= [] then toUpper (head s) : tail s else []
-
-mapHeadInline :: (String -> String) -> [Inline] -> [Inline]
-mapHeadInline _ [] = []
-mapHeadInline f (i:xs)
-    | Str          s <- i = Str         (f                s)   : xs
-    | Emph        is <- i = Emph        (mapHeadInline f is)   : xs
-    | Strong      is <- i = Strong      (mapHeadInline f is)   : xs
-    | Strikeout   is <- i = Strikeout   (mapHeadInline f is)   : xs
-    | Superscript is <- i = Superscript (mapHeadInline f is)   : xs
-    | Subscript   is <- i = Subscript   (mapHeadInline f is)   : xs
-    | Quoted q    is <- i = Quoted q    (mapHeadInline f is)   : xs
-    | SmallCaps   is <- i = SmallCaps   (mapHeadInline f is)   : xs
-    | Link      is t <- i = Link        (mapHeadInline f is) t : xs
-    | otherwise           = []
-
-getInline :: Inline -> [Inline]
-getInline i
-    | Emph        is <- i = is
-    | Strong      is <- i = is
-    | Strikeout   is <- i = is
-    | Superscript is <- i = is
-    | Subscript   is <- i = is
-    | Quoted _    is <- i = is
-    | SmallCaps   is <- i = is
-    | Link      is _ <- i = is
-    | otherwise           = []
-
 setCiteNoteNum :: [Inline] -> Int -> [Inline]
 setCiteNoteNum ((Cite cs o):xs) n = Cite (setCitationNoteNum n cs) o : setCiteNoteNum xs n
 setCiteNoteNum               _  _ = []
@@ -217,13 +142,17 @@ setCitationNoteNum :: Int -> [Citation] -> [Citation]
 setCitationNoteNum i = map $ \c -> c { citationNoteNum = i}
 
 toCslCite :: Citation -> CSL.Cite
-toCslCite (Citation i p l nn ao na _)
+toCslCite (Citation i p l cm nn _)
     = let (la,lo) = parseLocator l
+          citMode = case cm of
+                      AuthorOnly     -> (True, False)
+                      SuppressAuthor -> (False,True )
+                      NormalCitation -> (False,False)
       in   emptyCite { CSL.citeId         = i
                      , CSL.citePrefix     = p
                      , CSL.citeLabel      = la
                      , CSL.citeLocator    = lo
                      , CSL.citeNoteNumber = show nn
-                     , CSL.authorOnly     = ao
-                     , CSL.suppressAuthor = na
+                     , CSL.authorOnly     = fst citMode
+                     , CSL.suppressAuthor = snd citMode
                      }
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 030da9167..0256184f6 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1346,5 +1346,9 @@ parseLabel = try $ do
       (p',o) = if p /= [] && last p == '+'
                then (init p   , True )
                else (p        , False)
-  return $ Citation cit (trim p') (trim loc) 0 o na 0
+      mode = case (na,o) of
+               (True, False) -> SuppressAuthor
+               (False,True ) -> AuthorOnly
+               _             -> NormalCitation
+  return $ Citation cit (trim p') (trim loc) mode 0 0
 #endif