Skip to content
Snippets Groups Projects
Commit b8efaf4e authored by Niklas Haas's avatar Niklas Haas
Browse files

Filter family instances of hidden types

Currently, this check does not extend to hidden right hand sides,
although it probably should hide them in that case.
parent 72f655f5
No related branches found
No related tags found
5 merge requests!38Make --no-tmp-comp-dir the default,!37Adapt to latest xhtml version, various optimizations,!31Support HsToken in DataDecl and ClassDecl,!12Drop orphan instance when defined upstream.,!10Haddock interfaces produced from `.hi` files
...@@ -27,7 +27,7 @@ Changes in version 2.14.0 ...@@ -27,7 +27,7 @@ Changes in version 2.14.0
* Properly render License field (#271) * Properly render License field (#271)
* Print type/data family instances * Print type/data family instances (for exported types only)
* Fix display of poly-kinded type operators (#189) * Fix display of poly-kinded type operators (#189)
......
...@@ -3,6 +3,9 @@ ...@@ -3,6 +3,9 @@
-- in type instances. The expected behaviour is -- in type instances. The expected behaviour is
-- that we get the instance, Y is not linked and -- that we get the instance, Y is not linked and
-- Haddock shows a linking warning. -- Haddock shows a linking warning.
--
-- The other families and instances that are not exported should not
-- show up at all
module TypeFamilies2 (X, Foo, Bar) where module TypeFamilies2 (X, Foo, Bar) where
data X data X
...@@ -10,6 +13,11 @@ data Y ...@@ -10,6 +13,11 @@ data Y
type family Foo a type family Foo a
type instance Foo X = Y type instance Foo X = Y
type instance Foo Y = X -- Should be hidden
data family Bar a data family Bar a
data instance Bar X = BarX Y data instance Bar X = BarX Y
type family Invisible a
type instance Invisible X = Y
type instance Invisible Y = X
...@@ -73,6 +73,10 @@ attachToExportItem expInfo iface ifaceMap instIfaceMap export = ...@@ -73,6 +73,10 @@ attachToExportItem expInfo iface ifaceMap instIfaceMap export =
let fam_insts = [ (synifyFamInst i, n) let fam_insts = [ (synifyFamInst i, n)
| i <- sortBy (comparing instFam) fam_instances | i <- sortBy (comparing instFam) fam_instances
, let n = instLookup instDocMap (getName i) iface ifaceMap instIfaceMap , let n = instLookup instDocMap (getName i) iface ifaceMap instIfaceMap
, not $ isNameHidden expInfo (fi_fam i)
, not $ any (isTypeHidden expInfo) (fi_tys i)
-- Should we check for hidden RHS as well?
-- Ideally, in that case the RHS should simply not show up
] ]
cls_insts = [ (synifyInstHead i, instLookup instDocMap n iface ifaceMap instIfaceMap) cls_insts = [ (synifyInstHead i, instLookup instDocMap n iface ifaceMap instIfaceMap)
| let is = [ (instanceHead' i, getName i) | i <- cls_instances ] | let is = [ (instanceHead' i, getName i) | i <- cls_instances ]
...@@ -199,11 +203,11 @@ isInstanceHidden expInfo cls tys = ...@@ -199,11 +203,11 @@ isInstanceHidden expInfo cls tys =
instClassHidden = isNameHidden expInfo $ getName cls instClassHidden = isNameHidden expInfo $ getName cls
instTypeHidden :: Bool instTypeHidden :: Bool
instTypeHidden = any typeHidden tys instTypeHidden = any (isTypeHidden expInfo) tys
nameHidden :: Name -> Bool
nameHidden = isNameHidden expInfo
isTypeHidden :: ExportInfo -> Type -> Bool
isTypeHidden expInfo = typeHidden
where
typeHidden :: Type -> Bool typeHidden :: Type -> Bool
typeHidden t = typeHidden t =
case t of case t of
...@@ -213,3 +217,6 @@ isInstanceHidden expInfo cls tys = ...@@ -213,3 +217,6 @@ isInstanceHidden expInfo cls tys =
FunTy t1 t2 -> typeHidden t1 || typeHidden t2 FunTy t1 t2 -> typeHidden t1 || typeHidden t2
ForAllTy _ ty -> typeHidden ty ForAllTy _ ty -> typeHidden ty
LitTy _ -> False LitTy _ -> False
nameHidden :: Name -> Bool
nameHidden = isNameHidden expInfo
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