diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 071a288e1..228b34d09 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -72,6 +72,7 @@ data WriterState =
               , stEmptyLine     :: Bool          -- true if no content on line
               , stHasCslRefs    :: Bool          -- has a Div with class refs
               , stCslHangingIndent :: Bool       -- use hanging indent for bib
+              , stIsFirstInDefinition :: Bool    -- first block in a defn list
               }
 
 startingState :: WriterOptions -> WriterState
@@ -102,7 +103,8 @@ startingState options = WriterState {
                 , stBeamer = False
                 , stEmptyLine = True
                 , stHasCslRefs = False
-                , stCslHangingIndent = False }
+                , stCslHangingIndent = False
+                , stIsFirstInDefinition = False }
 
 -- | Convert Pandoc to LaTeX.
 writeLaTeX :: PandocMonad m => WriterOptions -> Pandoc -> m Text
@@ -682,19 +684,25 @@ blockToLaTeX b@(RawBlock f x) = do
 blockToLaTeX (BulletList []) = return empty  -- otherwise latex error
 blockToLaTeX (BulletList lst) = do
   incremental <- gets stIncremental
+  isFirstInDefinition <- gets stIsFirstInDefinition
   beamer <- gets stBeamer
   let inc = if beamer && incremental then "[<+->]" else ""
   items <- mapM listItemToLaTeX lst
   let spacing = if isTightList lst
                    then text "\\tightlist"
                    else empty
-  return $ text ("\\begin{itemize}" <> inc) $$ spacing $$ vcat items $$
+  return $ text ("\\begin{itemize}" <> inc) $$
+             spacing $$
+             -- force list at beginning of definition to start on new line
+             (if isFirstInDefinition then "\\item[]" else mempty) $$
+             vcat items $$
              "\\end{itemize}"
 blockToLaTeX (OrderedList _ []) = return empty -- otherwise latex error
 blockToLaTeX (OrderedList (start, numstyle, numdelim) lst) = do
   st <- get
   let inc = if stBeamer st && stIncremental st then "[<+->]" else ""
   let oldlevel = stOLLevel st
+  isFirstInDefinition <- gets stIsFirstInDefinition
   put $ st {stOLLevel = oldlevel + 1}
   items <- mapM listItemToLaTeX lst
   modify (\s -> s {stOLLevel = oldlevel})
@@ -738,6 +746,8 @@ blockToLaTeX (OrderedList (start, numstyle, numdelim) lst) = do
          $$ stylecommand
          $$ resetcounter
          $$ spacing
+         -- force list at beginning of definition to start on new line
+         $$ (if isFirstInDefinition then "\\item[]" else mempty)
          $$ vcat items
          $$ "\\end{enumerate}"
 blockToLaTeX (DefinitionList []) = return empty
@@ -948,7 +958,14 @@ defListItemToLaTeX (term, defs) = do
     let term'' = if any isInternalLink term
                     then braces term'
                     else term'
-    def'  <- liftM vsep $ mapM blockListToLaTeX defs
+    def'  <- case concat defs of
+               [] -> return mempty
+               (x:xs) -> do
+                 modify $ \s -> s{stIsFirstInDefinition = True }
+                 firstitem <- blockToLaTeX x
+                 modify $ \s -> s{stIsFirstInDefinition = False }
+                 rest <- blockListToLaTeX xs
+                 return $ firstitem $+$ rest
     return $ case defs of
      ((Header{} : _) : _)    ->
        "\\item" <> brackets term'' <> " ~ " $$ def'
diff --git a/test/command/lists-inside-definition.md b/test/command/lists-inside-definition.md
new file mode 100644
index 000000000..f0cac0d69
--- /dev/null
+++ b/test/command/lists-inside-definition.md
@@ -0,0 +1,67 @@
+This inserts an empty `\item[]` when a list occurs at the
+beginning of a definition list definition; otherwise the list
+may start on the line with the label, which looks terrible.
+See https://tex.stackexchange.com/questions/192480/force-itemize-inside-description-onto-a-new-line
+
+```
+% pandoc -t latex
+Definition
+:   1. list
+    2. list
+^D
+\begin{description}
+\item[Definition]
+\begin{enumerate}
+\def\labelenumi{\arabic{enumi}.}
+\tightlist
+\item[]
+\item
+  list
+\item
+  list
+\end{enumerate}
+\end{description}
+```
+
+```
+% pandoc -t latex
+Definition
+:   Foo
+
+    1. list
+    2. list
+^D
+\begin{description}
+\item[Definition]
+Foo
+
+\begin{enumerate}
+\def\labelenumi{\arabic{enumi}.}
+\tightlist
+\item
+  list
+\item
+  list
+\end{enumerate}
+\end{description}
+```
+
+```
+% pandoc -t latex
+Definition
+:   - list
+    - list
+^D
+\begin{description}
+\item[Definition]
+\begin{itemize}
+\tightlist
+\item[]
+\item
+  list
+\item
+  list
+\end{itemize}
+\end{description}
+```
+