aboutsummaryrefslogtreecommitdiff
path: root/haddock-api/src/Haddock/Convert.hs
diff options
context:
space:
mode:
Diffstat (limited to 'haddock-api/src/Haddock/Convert.hs')
-rw-r--r--haddock-api/src/Haddock/Convert.hs16
1 files changed, 7 insertions, 9 deletions
diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs
index 87a273b2..01261477 100644
--- a/haddock-api/src/Haddock/Convert.hs
+++ b/haddock-api/src/Haddock/Convert.hs
@@ -1,3 +1,4 @@
+
{-# LANGUAGE CPP, PatternGuards #-}
-----------------------------------------------------------------------------
-- |
@@ -34,10 +35,10 @@ import TcType ( tcSplitSigmaTy )
import TyCon
import Type
import TyCoRep
-import TysPrim ( alphaTyVars, unliftedTypeKindTyConName )
+import TysPrim ( alphaTyVars )
import TysWiredIn ( listTyConName, starKindTyConName, unitTy )
import PrelNames ( hasKey, eqTyConKey, ipClassKey
- , tYPETyConKey, ptrRepLiftedDataConKey, ptrRepUnliftedDataConKey )
+ , tYPETyConKey, liftedRepDataConKey )
import Unique ( getUnique )
import Util ( filterByList, filterOut )
import Var
@@ -114,7 +115,8 @@ synifyAxBranch tc (CoAxBranch { cab_tvs = tkvs, cab_lhs = args, cab_rhs = rhs })
hs_rhs = synifyType WithinType rhs
in TyFamEqn { tfe_tycon = name
, tfe_pats = HsIB { hsib_body = typats
- , hsib_vars = map tyVarName tkvs }
+ , hsib_vars = map tyVarName tkvs
+ , hsib_closed = True }
, tfe_fixity = Prefix
, tfe_rhs = hs_rhs }
@@ -300,7 +302,7 @@ synifyDataCon use_gadt_syntax dc =
(False,True) -> case linear_tys of
[a,b] -> return $ InfixCon a b
_ -> Left "synifyDataCon: infix with non-2 args?"
- gadt_ty = HsIB [] (synifyType WithinType res_ty)
+ gadt_ty = HsIB [] (synifyType WithinType res_ty) False
-- finally we get synifyDataCon's result!
in hs_arg_tys >>=
\hat ->
@@ -378,12 +380,8 @@ synifyType _ (TyConApp tc tys)
-- Use */# instead of TYPE 'Lifted/TYPE 'Unlifted (#473)
| tc `hasKey` tYPETyConKey
, [TyConApp lev []] <- tys
- , lev `hasKey` ptrRepLiftedDataConKey
+ , lev `hasKey` liftedRepDataConKey
= noLoc (HsTyVar NotPromoted (noLoc starKindTyConName))
- | tc `hasKey` tYPETyConKey
- , [TyConApp lev []] <- tys
- , lev `hasKey` ptrRepUnliftedDataConKey
- = noLoc (HsTyVar NotPromoted (noLoc unliftedTypeKindTyConName))
-- Use non-prefix tuple syntax where possible, because it looks nicer.
| Just sort <- tyConTuple_maybe tc
, tyConArity tc == length tys