diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index b1f56eed0..f5873d55f 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -80,6 +80,10 @@ newtype PropertyValue = PropertyValue { fromValue :: String }
 toPropertyValue :: String -> PropertyValue
 toPropertyValue = PropertyValue
 
+-- | Check whether the property value is non-nil (i.e. truish).
+isNonNil :: PropertyValue -> Bool
+isNonNil p = map toLower (fromValue p) `notElem` ["()", "{}", "nil"]
+
 -- | Key/value pairs from a PROPERTIES drawer
 type Properties = [(PropertyKey, PropertyValue)]
 
@@ -200,12 +204,16 @@ propertiesToAttr properties =
     toStringPair prop = (fromKey (fst prop), fromValue (snd prop))
     customIdKey = toPropertyKey "custom_id"
     classKey    = toPropertyKey "class"
+    unnumberedKey = toPropertyKey "unnumbered"
+    specialProperties = [customIdKey, classKey, unnumberedKey]
     id'  = fromMaybe mempty . fmap fromValue . lookup customIdKey $ properties
     cls  = fromMaybe mempty . fmap fromValue . lookup classKey    $ properties
-    kvs' = map toStringPair . filter ((`notElem` [customIdKey, classKey]) . fst)
+    kvs' = map toStringPair . filter ((`notElem` specialProperties) . fst)
            $ properties
+    isUnnumbered =
+      fromMaybe False . fmap isNonNil . lookup unnumberedKey $ properties
   in
-    (id', words cls, kvs')
+    (id', words cls ++ (if isUnnumbered then ["unnumbered"] else []), kvs')
 
 tagTitle :: Inlines -> [Tag] -> Inlines
 tagTitle title tags = title <> (mconcat $ map tagToInline tags)
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index d6e7bba22..d4fedc797 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -818,6 +818,15 @@ tests =
                   ] =?>
           headerWith ("fubar", [], [("bar", "baz")]) 1 "foo"
 
+
+      , "Headers marked with a unnumbered property get a class of the same name" =:
+          unlines [ "* Not numbered"
+                  , "  :PROPERTIES:"
+                  , "  :UNNUMBERED: t"
+                  , "  :END:"
+                  ] =?>
+          headerWith ("not-numbered", ["unnumbered"], []) 1 "Not numbered"
+
       , "Paragraph starting with an asterisk" =:
           "*five" =?>
           para "*five"