Skip to content
Snippets Groups Projects
Commit 9bede936 authored by Vladislav Zavialov's avatar Vladislav Zavialov
Browse files

Class layout info

parent 57b7493b
Branches wip/class-layout-info
No related tags found
4 merge requests!38Make --no-tmp-comp-dir the default,!37Adapt to latest xhtml version, various optimizations,!31Support HsToken in DataDecl and ClassDecl,!16Class layout info
......@@ -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
......
......@@ -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
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment