diff --git a/data/templates/default.context b/data/templates/default.context
index 49b2c1f6f..78055daed 100644
--- a/data/templates/default.context
+++ b/data/templates/default.context
@@ -80,6 +80,10 @@ $endif$
 \setuphead[subsubsubsection]   [style=\sc]
 \setuphead[subsubsubsubsection][style=\it]
 
+\definesectionlevels
+   [default]
+   [section, subsection, subsubsection, subsubsubsection, subsubsubsubsection]
+
 $if(headertext)$
 \setupheadertexts$for(headertext)$[$headertext$]$endfor$
 $endif$
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 51674da87..de836e4b1 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -42,7 +42,13 @@ data WriterState =
               , stCslHangingIndent :: Bool -- CSL hanging indent
               }
 
-data Tabl = Xtb | Ntb deriving (Show, Eq)
+-- | Table type
+data Tabl = Xtb  -- ^ Extreme tables
+          | Ntb  -- ^ Natural tables
+  deriving (Show, Eq)
+
+-- | Whether a heading belongs to a section environment or is standalone.
+data HeadingType = SectionHeading | NonSectionHeading
 
 orderedListStyles :: [Char]
 orderedListStyles = cycle "narg"
@@ -158,7 +164,7 @@ blockToConTeXt :: PandocMonad m => Block -> WM m (Doc Text)
 blockToConTeXt Null = return empty
 blockToConTeXt (Div attr@(_,"section":_,_)
                  (Header level _ title' : xs)) = do
-  header' <- sectionHeader attr level title'
+  header' <- sectionHeader attr level title' SectionHeading
   footer' <- sectionFooter attr level
   innerContents <- blockListToConTeXt xs
   return $ header' $$ innerContents $$ footer'
@@ -250,7 +256,8 @@ blockToConTeXt (DefinitionList lst) =
   liftM vcat $ mapM defListItemToConTeXt lst
 blockToConTeXt HorizontalRule = return $ "\\thinrule" <> blankline
 -- If this is ever executed, provide a default for the reference identifier.
-blockToConTeXt (Header level attr lst) = sectionHeader attr level lst
+blockToConTeXt (Header level attr lst) =
+  sectionHeader attr level lst NonSectionHeading
 blockToConTeXt (Table _ blkCapt specs thead tbody tfoot) = do
     let (caption, aligns, widths, heads, rows) = toLegacyTable blkCapt specs thead tbody tfoot
     opts <- gets stOptions
@@ -500,11 +507,12 @@ sectionHeader :: PandocMonad m
               => Attr
               -> Int
               -> [Inline]
+              -> HeadingType
               -> WM m (Doc Text)
-sectionHeader (ident,classes,kvs) hdrLevel lst = do
+sectionHeader (ident,classes,kvs) hdrLevel lst secenv = do
   opts <- gets stOptions
   contents <- inlineListToConTeXt lst
-  levelText <- sectionLevelToText opts (ident,classes,kvs) hdrLevel
+  levelText <- sectionLevelToText opts (ident,classes,kvs) hdrLevel secenv
   let ident' = if T.null ident
                then empty
                else "reference=" <> braces (literal (toLabel ident))
@@ -514,38 +522,44 @@ sectionHeader (ident,classes,kvs) hdrLevel lst = do
   let options = if isEmpty keys || isEmpty levelText
                 then empty
                 else brackets keys
-        where keys = hcat $ intersperse "," $ filter (not . isEmpty) [contents', ident']
-  let starter = if writerSectionDivs opts
-                then "\\start"
-                else "\\"
+        where keys = hcat $ intersperse "," $
+                     filter (not . isEmpty) [contents', ident']
+  let starter = case secenv of
+                  SectionHeading -> "\\start"
+                  NonSectionHeading -> "\\"
   return $ starter <> levelText <> options <> blankline
 
 -- | Craft the section footer
 sectionFooter :: PandocMonad m => Attr -> Int -> WM m (Doc Text)
 sectionFooter attr hdrLevel = do
   opts <- gets stOptions
-  levelText <- sectionLevelToText opts attr hdrLevel
-  return $ if writerSectionDivs opts
-           then "\\stop" <> levelText <> blankline
-           else empty
+  levelText <- sectionLevelToText opts attr hdrLevel SectionHeading
+  return $ "\\stop" <> levelText <> blankline
 
 -- | Generate a textual representation of the section level
-sectionLevelToText :: PandocMonad m => WriterOptions -> Attr -> Int -> WM m (Doc Text)
-sectionLevelToText opts (_,classes,_) hdrLevel = do
-  let level' = case writerTopLevelDivision opts of
-                 TopLevelPart    -> hdrLevel - 2
-                 TopLevelChapter -> hdrLevel - 1
-                 TopLevelSection -> hdrLevel
-                 TopLevelDefault -> hdrLevel
-  let (section, chapter) = if "unnumbered" `elem` classes
-                              then (literal "subject", literal "title")
-                              else (literal "section", literal "chapter")
-  return $ case level' of
-             -1         -> literal "part"
-             0          -> chapter
-             n | n >= 1 -> text (concat (replicate (n - 1) "sub"))
-                           <> section
-             _          -> empty -- cannot happen
+sectionLevelToText :: PandocMonad m
+                   => WriterOptions -> Attr -> Int -> HeadingType
+                   -> WM m (Doc Text)
+sectionLevelToText opts (_,classes,_) hdrLevel headingType = do
+  let semanticSection shift = do
+        let (section, chapter) = if "unnumbered" `elem` classes
+                                 then (literal "subject", literal "title")
+                                 else (literal "section", literal "chapter")
+        return $ case hdrLevel + shift of
+                   -1         -> literal "part"
+                   0          -> chapter
+                   n | n >= 1 -> text (concat (replicate (n - 1) "sub"))
+                                 <> section
+                   _          -> empty -- cannot happen
+
+  case writerTopLevelDivision opts of
+    TopLevelPart    -> semanticSection (-2)
+    TopLevelChapter -> semanticSection (-1)
+    TopLevelSection -> semanticSection 0
+    TopLevelDefault -> return . literal $
+                       case headingType of
+                         SectionHeading    -> "sectionlevel"
+                         NonSectionHeading -> ""
 
 fromBCP47 :: PandocMonad m => Maybe Text -> WM m (Maybe Text)
 fromBCP47 mbs = fromBCP47' <$> toLang mbs
diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs
index 254a5fad6..aced9ab7d 100644
--- a/test/Tests/Writers/ConTeXt.hs
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -19,8 +19,10 @@ context' = unpack . purely (writeConTeXt def{ writerWrapText = WrapNone }) . toP
 contextNtb :: (ToPandoc a) => a -> String
 contextNtb = unpack . purely (writeConTeXt def{ writerExtensions = enableExtension Ext_ntb pandocExtensions }) . toPandoc
 
-contextDiv :: (ToPandoc a) => a -> String
-contextDiv = unpack . purely (writeConTeXt def{ writerSectionDivs = True }) . toPandoc
+contextSection :: (ToPandoc a) => a -> String
+contextSection = unpack
+  . purely (writeConTeXt def{ writerTopLevelDivision = TopLevelSection })
+  . toPandoc
 
 {-
   "my test" =: X =?> Y
@@ -56,8 +58,10 @@ tests =
   , testGroup "headers"
     [ "level 1" =:
       headerWith ("my-header",[],[]) 1 "My header" =?>
-      "\\section[title={My header},reference={my-header}]"
-    , test contextDiv "section-divs" $
+      "\\startsectionlevel[title={My header},reference={my-header}]\n" <>
+      "\n" <>
+      "\\stopsectionlevel"
+    , test contextSection "Section as top-level" $
       (   headerWith ("header1", [], []) 1 (text "Header1")
        <> headerWith ("header2", [], []) 2 (text "Header2")
        <> headerWith ("header3", [], []) 3 (text "Header3")
diff --git a/test/command/3968.md b/test/command/3968.md
index c76cfcba4..dfa0e8986 100644
--- a/test/command/3968.md
+++ b/test/command/3968.md
@@ -4,7 +4,11 @@
 
 ## Section
 ^D
-\chapter[title={Chapter},reference={chapter}]
+\startchapter[title={Chapter},reference={chapter}]
 
-\section[title={Section},reference={section}]
+\startsection[title={Section},reference={section}]
+
+\stopsection
+
+\stopchapter
 ```
diff --git a/test/writer.context b/test/writer.context
index 32a8f8004..0844520fb 100644
--- a/test/writer.context
+++ b/test/writer.context
@@ -40,6 +40,10 @@
 \setuphead[subsubsubsection]   [style=\sc]
 \setuphead[subsubsubsubsection][style=\it]
 
+\definesectionlevels
+   [default]
+   [section, subsection, subsubsection, subsubsubsection, subsubsubsubsection]
+
 \setuphead[chapter, section, subsection, subsubsection, subsubsubsection, subsubsubsubsection][number=no]
 
 \definedescription
@@ -76,34 +80,52 @@ markdown test suite.
 
 \thinrule
 
-\section[title={Headers},reference={headers}]
+\startsectionlevel[title={Headers},reference={headers}]
 
-\subsection[title={Level 2 with an \goto{embedded
+\startsectionlevel[title={Level 2 with an \goto{embedded
 link}[url(/url)]},reference={level-2-with-an-embedded-link}]
 
-\subsubsection[title={Level 3 with
+\startsectionlevel[title={Level 3 with
 {\em emphasis}},reference={level-3-with-emphasis}]
 
-\subsubsubsection[title={Level 4},reference={level-4}]
+\startsectionlevel[title={Level 4},reference={level-4}]
 
-\subsubsubsubsection[title={Level 5},reference={level-5}]
+\startsectionlevel[title={Level 5},reference={level-5}]
 
-\section[title={Level 1},reference={level-1}]
+\stopsectionlevel
 
-\subsection[title={Level 2 with
+\stopsectionlevel
+
+\stopsectionlevel
+
+\stopsectionlevel
+
+\stopsectionlevel
+
+\startsectionlevel[title={Level 1},reference={level-1}]
+
+\startsectionlevel[title={Level 2 with
 {\em emphasis}},reference={level-2-with-emphasis}]
 
-\subsubsection[title={Level 3},reference={level-3}]
+\startsectionlevel[title={Level 3},reference={level-3}]
 
 with no blank line
 
-\subsection[title={Level 2},reference={level-2}]
+\stopsectionlevel
+
+\stopsectionlevel
+
+\startsectionlevel[title={Level 2},reference={level-2}]
 
 with no blank line
 
 \thinrule
 
-\section[title={Paragraphs},reference={paragraphs}]
+\stopsectionlevel
+
+\stopsectionlevel
+
+\startsectionlevel[title={Paragraphs},reference={paragraphs}]
 
 Here's a regular paragraph.
 
@@ -118,7 +140,9 @@ here.
 
 \thinrule
 
-\section[title={Block Quotes},reference={block-quotes}]
+\stopsectionlevel
+
+\startsectionlevel[title={Block Quotes},reference={block-quotes}]
 
 E-mail style:
 
@@ -161,7 +185,9 @@ And a following paragraph.
 
 \thinrule
 
-\section[title={Code Blocks},reference={code-blocks}]
+\stopsectionlevel
+
+\startsectionlevel[title={Code Blocks},reference={code-blocks}]
 
 Code:
 
@@ -185,9 +211,11 @@ These should not be escaped:  \$ \\ \> \[ \{
 
 \thinrule
 
-\section[title={Lists},reference={lists}]
+\stopsectionlevel
 
-\subsection[title={Unordered},reference={unordered}]
+\startsectionlevel[title={Lists},reference={lists}]
+
+\startsectionlevel[title={Unordered},reference={unordered}]
 
 Asterisks tight:
 
@@ -255,7 +283,9 @@ Minuses loose:
   Minus 3
 \stopitemize
 
-\subsection[title={Ordered},reference={ordered}]
+\stopsectionlevel
+
+\startsectionlevel[title={Ordered},reference={ordered}]
 
 Tight:
 
@@ -314,7 +344,9 @@ Multiple paragraphs:
   Item 3.
 \stopenumerate
 
-\subsection[title={Nested},reference={nested}]
+\stopsectionlevel
+
+\startsectionlevel[title={Nested},reference={nested}]
 
 \startitemize[packed]
 \item
@@ -368,7 +400,9 @@ Same thing but with paragraphs:
   Third
 \stopenumerate
 
-\subsection[title={Tabs and spaces},reference={tabs-and-spaces}]
+\stopsectionlevel
+
+\startsectionlevel[title={Tabs and spaces},reference={tabs-and-spaces}]
 
 \startitemize
 \item
@@ -384,7 +418,9 @@ Same thing but with paragraphs:
   \stopitemize
 \stopitemize
 
-\subsection[title={Fancy list markers},reference={fancy-list-markers}]
+\stopsectionlevel
+
+\startsectionlevel[title={Fancy list markers},reference={fancy-list-markers}]
 
 \startenumerate[n][start=2,left=(,stopper=)]
 \item
@@ -448,7 +484,11 @@ B. Williams
 
 \thinrule
 
-\section[title={Definition Lists},reference={definition-lists}]
+\stopsectionlevel
+
+\stopsectionlevel
+
+\startsectionlevel[title={Definition Lists},reference={definition-lists}]
 
 Tight using spaces:
 
@@ -559,7 +599,9 @@ Blank line after term, indented marker, alternate markers:
   \stopenumerate
 \stopdescription
 
-\section[title={HTML Blocks},reference={html-blocks}]
+\stopsectionlevel
+
+\startsectionlevel[title={HTML Blocks},reference={html-blocks}]
 
 Simple block on one line:
 
@@ -619,7 +661,9 @@ Hr's:
 
 \thinrule
 
-\section[title={Inline Markup},reference={inline-markup}]
+\stopsectionlevel
+
+\startsectionlevel[title={Inline Markup},reference={inline-markup}]
 
 This is {\em emphasized}, and so {\em is this}.
 
@@ -648,7 +692,9 @@ a^b c^d, a\lettertilde{}b c\lettertilde{}d.
 
 \thinrule
 
-\section[title={Smart quotes, ellipses,
+\stopsectionlevel
+
+\startsectionlevel[title={Smart quotes, ellipses,
 dashes},reference={smart-quotes-ellipses-dashes}]
 
 \quotation{Hello,} said the spider. \quotation{\quote{Shelob} is my name.}
@@ -671,7 +717,9 @@ Ellipses\ldots{}and\ldots{}and\ldots{}.
 
 \thinrule
 
-\section[title={LaTeX},reference={latex}]
+\stopsectionlevel
+
+\startsectionlevel[title={LaTeX},reference={latex}]
 
 \startitemize[packed]
 \item
@@ -717,7 +765,9 @@ Cat    & 1      \\ \hline
 
 \thinrule
 
-\section[title={Special Characters},reference={special-characters}]
+\stopsectionlevel
+
+\startsectionlevel[title={Special Characters},reference={special-characters}]
 
 Here is some unicode:
 
@@ -778,9 +828,11 @@ Minus: -
 
 \thinrule
 
-\section[title={Links},reference={links}]
+\stopsectionlevel
 
-\subsection[title={Explicit},reference={explicit}]
+\startsectionlevel[title={Links},reference={links}]
+
+\startsectionlevel[title={Explicit},reference={explicit}]
 
 Just a \goto{URL}[url(/url/)].
 
@@ -800,7 +852,9 @@ Just a \goto{URL}[url(/url/)].
 
 \goto{Empty}[url()].
 
-\subsection[title={Reference},reference={reference}]
+\stopsectionlevel
+
+\startsectionlevel[title={Reference},reference={reference}]
 
 Foo \goto{bar}[url(/url/)].
 
@@ -824,7 +878,9 @@ Foo \goto{bar}[url(/url/)].
 
 Foo \goto{biz}[url(/url/)].
 
-\subsection[title={With ampersands},reference={with-ampersands}]
+\stopsectionlevel
+
+\startsectionlevel[title={With ampersands},reference={with-ampersands}]
 
 Here's a \goto{link with an ampersand in the
 URL}[url(http://example.com/?foo=1&bar=2)].
@@ -836,7 +892,9 @@ Here's an \goto{inline link}[url(/script?foo=1&bar=2)].
 
 Here's an \goto{inline link in pointy braces}[url(/script?foo=1&bar=2)].
 
-\subsection[title={Autolinks},reference={autolinks}]
+\stopsectionlevel
+
+\startsectionlevel[title={Autolinks},reference={autolinks}]
 
 With an ampersand: \useURL[url1][http://example.com/?foo=1&bar=2]\from[url1]
 
@@ -863,7 +921,11 @@ or here: <http://example.com/>
 
 \thinrule
 
-\section[title={Images},reference={images}]
+\stopsectionlevel
+
+\stopsectionlevel
+
+\startsectionlevel[title={Images},reference={images}]
 
 From \quotation{Voyage dans la Lune} by Georges Melies (1902):
 
@@ -873,7 +935,9 @@ Here is a movie {\externalfigure[movie.jpg]} icon.
 
 \thinrule
 
-\section[title={Footnotes},reference={footnotes}]
+\stopsectionlevel
+
+\startsectionlevel[title={Footnotes},reference={footnotes}]
 
 Here is a footnote reference,\footnote{Here is the footnote. It can go anywhere
   after the footnote reference. It need not be placed at the end of the
@@ -905,4 +969,6 @@ Notes can go in quotes.\footnote{In quote.}
 
 This paragraph should not be part of the note, as it is not indented.
 
+\stopsectionlevel
+
 \stoptext
diff --git a/test/writers-lang-and-dir.context b/test/writers-lang-and-dir.context
index ecb04d208..c8ce6e815 100644
--- a/test/writers-lang-and-dir.context
+++ b/test/writers-lang-and-dir.context
@@ -38,6 +38,10 @@
 \setuphead[subsubsubsection]   [style=\sc]
 \setuphead[subsubsubsubsection][style=\it]
 
+\definesectionlevels
+   [default]
+   [section, subsection, subsubsection, subsubsubsection, subsubsubsubsection]
+
 \setuphead[chapter, section, subsection, subsubsection, subsubsubsection, subsubsubsubsection][number=no]
 
 \definedescription
@@ -61,7 +65,8 @@
 
 \starttext
 
-\section[title={Empty Divs and Spans},reference={empty-divs-and-spans}]
+\startsectionlevel[title={Empty Divs and
+Spans},reference={empty-divs-and-spans}]
 
 Some text and
 
@@ -71,7 +76,9 @@ and more text.
 
 Next paragraph with a span and a word-thatincludesaspanright?
 
-\section[title={Directionality},reference={directionality}]
+\stopsectionlevel
+
+\startsectionlevel[title={Directionality},reference={directionality}]
 
 Some text and
 
@@ -90,7 +97,9 @@ and a ltr div. with a {\righttoleft rtl span}.
 Next paragraph with a {\righttoleft rtl span} and a
 word-that-includesa{\lefttoright ltrspan}right?
 
-\section[title={Languages},reference={languages}]
+\stopsectionlevel
+
+\startsectionlevel[title={Languages},reference={languages}]
 
 Some text and
 
@@ -106,7 +115,9 @@ word-that-includesa{\language[de-ch]Swiss German span}right?
 
 Some {\language[es]Spanish text}.
 
-\section[title={Combined},reference={combined}]
+\stopsectionlevel
+
+\startsectionlevel[title={Combined},reference={combined}]
 
 Some text and
 
@@ -123,4 +134,6 @@ Next paragraph with a {\language[en-gb]{\lefttoright British ltr span}}
 and a word-that-includesa{\language[de-ch]{\lefttoright Swiss German ltr
 span}}right?
 
+\stopsectionlevel
+
 \stoptext