diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs
index 928bbed4729063fe09ad09ad07312e106b19e4fb..ce4ffda209bfa86ece5634af57a810e9d3632ad8 100644
--- a/haddock-api/src/Haddock/Convert.hs
+++ b/haddock-api/src/Haddock/Convert.hs
@@ -128,6 +128,7 @@ tyThingToLHsDecl prr t = case t of
 
        in withErrs (lefts atTyClDecls) . TyClD noExtField $ ClassDecl
          { tcdCtxt = Just $ synifyCtx (classSCTheta cl)
+         , tcdLayout = NoLayoutInfo
          , tcdLName = synifyNameN cl
          , tcdTyVars = synifyTyVars vs
          , tcdFixity = synifyFixity cl
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index 558e4d3cc70f07f91b14816cf0cc673bee3625fe..bb657018cb9c91e8e2a8470ecef47fbc43ad2e11 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -428,7 +428,8 @@ renameTyClD d = case d of
     return (DataDecl { tcdDExt = noExtField, tcdLName = lname', tcdTyVars = tyvars'
                      , tcdFixity = fixity, tcdDataDefn = defn' })
 
-  ClassDecl { tcdCtxt = lcontext, tcdLName = lname, tcdTyVars = ltyvars, tcdFixity = fixity
+  ClassDecl { tcdLayout = layout
+            , tcdCtxt = lcontext, tcdLName = lname, tcdTyVars = ltyvars, tcdFixity = fixity
             , tcdFDs = lfundeps, tcdSigs = lsigs, tcdATs = ats, tcdATDefs = at_defs } -> do
     lcontext' <- traverse renameLContext lcontext
     lname'    <- renameL lname
@@ -438,10 +439,12 @@ renameTyClD d = case d of
     ats'      <- mapM (renameLThing renameFamilyDecl) ats
     at_defs'  <- mapM (mapM renameTyFamDefltD) at_defs
     -- we don't need the default methods or the already collected doc entities
-    return (ClassDecl { tcdCtxt = lcontext', tcdLName = lname', tcdTyVars = ltyvars'
+    return (ClassDecl { tcdCExt = noExtField
+                      , tcdLayout = renameLayoutInfo layout
+                      , tcdCtxt = lcontext', tcdLName = lname', tcdTyVars = ltyvars'
                       , tcdFixity = fixity
                       , tcdFDs = lfundeps', tcdSigs = lsigs', tcdMeths= emptyBag
-                      , tcdATs = ats', tcdATDefs = at_defs', tcdDocs = [], tcdCExt = noExtField })
+                      , tcdATs = ats', tcdATDefs = at_defs', tcdDocs = [] })
 
   where
     renameLFunDep :: LHsFunDep GhcRn -> RnM (LHsFunDep DocNameI)
@@ -452,6 +455,11 @@ renameTyClD d = case d of
 
     renameLSig (L loc sig) = return . L (locA loc) =<< renameSig sig
 
+renameLayoutInfo :: LayoutInfo GhcRn -> LayoutInfo DocNameI
+renameLayoutInfo (ExplicitBraces ob cb) = ExplicitBraces ob cb
+renameLayoutInfo (VirtualBraces n) = VirtualBraces n
+renameLayoutInfo NoLayoutInfo = NoLayoutInfo
+
 renameFamilyDecl :: FamilyDecl GhcRn -> RnM (FamilyDecl DocNameI)
 renameFamilyDecl (FamilyDecl { fdInfo = info, fdLName = lname
                              , fdTyVars = ltyvars