diff --git a/README b/README
index 7b75565c1..236637d10 100644
--- a/README
+++ b/README
@@ -284,6 +284,12 @@ Reader options
     if no directory is provided.  If you want to run a script in the
     working directory, preface the filename with `./`.
 
+`-M` *KEY[=VAL]*, `--metadata=`*KEY[:VAL]*
+:   Set the metadata field *KEY* to the value *VAL* after
+    parsing.  A value specified on the command line overrides a value
+    specified in the document.  Values will be interpreted as raw strings.
+    If no value is specified, the value will be treated as Boolean true.
+
 `--normalize`
 :   Normalize the document after reading:  merge adjacent
     `Str` or `Emph` elements, for example, and remove repeated `Space`s.
diff --git a/pandoc.hs b/pandoc.hs
index 3713467ad..0bc2d7359 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -113,7 +113,7 @@ data Opt = Opt
     , optTransforms        :: [Pandoc -> Pandoc]  -- ^ Doc transforms to apply
     , optTemplate          :: Maybe FilePath  -- ^ Custom template
     , optVariables         :: [(String,String)] -- ^ Template variables to set
-    , optMetadata          :: [(String,String)] -- ^ Metadata fields to set
+    , optMetadata          :: [(String,MetaValue)] -- ^ Metadata fields to set
     , optOutputFile        :: String  -- ^ Name of output file
     , optNumberSections    :: Bool    -- ^ Number sections in LaTeX
     , optNumberOffset      :: [Int]   -- ^ Starting number for sections
@@ -328,8 +328,8 @@ options =
                  (ReqArg
                   (\arg opt -> do
                      let (key,val) = case break (`elem` ":=") arg of
-                                       (k,_:v) -> (k,v)
-                                       (k,_)   -> (k,"true")
+                                       (k,_:v) -> (k, MetaString v)
+                                       (k,_)   -> (k, MetaBool True)
                      return opt{ optMetadata = (key,val) : optMetadata opt })
                   "KEY[:VALUE]")
                  ""
@@ -658,7 +658,7 @@ options =
     , Option "" ["bibliography"]
                  (ReqArg
                   (\arg opt ->
-                     return opt{ optMetadata = ("bibliography",arg) :
+                     return opt{ optMetadata = ("bibliography",MetaString arg) :
                                  optMetadata opt
                                , optPlugins = externalFilter "pandoc-citeproc"
                                    : optPlugins opt
@@ -669,7 +669,7 @@ options =
      , Option "" ["csl"]
                  (ReqArg
                   (\arg opt ->
-                     return opt{ optMetadata = ("csl",arg) :
+                     return opt{ optMetadata = ("csl", MetaString arg) :
                                  optMetadata opt })
                    "FILE")
                  ""
@@ -677,7 +677,8 @@ options =
      , Option "" ["citation-abbreviations"]
                  (ReqArg
                   (\arg opt ->
-                     return opt{ optMetadata = ("citation-abbreviations",arg) :
+                     return opt{ optMetadata = ("citation-abbreviations",
+                                                MetaString arg) :
                                  optMetadata opt })
                    "FILE")
                  ""
@@ -1104,7 +1105,7 @@ main = do
            reader readerOpts
 
 
-  let doc0 = foldr (\(k,v) -> setMeta k (MetaString v)) doc metadata
+  let doc0 = foldr (\(k,v) -> setMeta k v) doc metadata
   let doc1 = foldr ($) doc0 transforms
   doc2 <- foldrM ($) doc1 $ map ($ [writerName']) plugins