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

Desugar a few more type constructors

parent eebb28ec
No related branches found
No related tags found
No related merge requests found
Pipeline #41461 passed with warnings
...@@ -314,9 +314,7 @@ type instance XParTy (GhcPass _) = EpAnn AnnParen ...@@ -314,9 +314,7 @@ type instance XParTy (GhcPass _) = EpAnn AnnParen
type instance XIParamTy GhcPs = EpAnn [AddEpAnn] type instance XIParamTy GhcPs = EpAnn [AddEpAnn]
type instance XIParamTy GhcRn = EpAnn [AddEpAnn] type instance XIParamTy GhcRn = EpAnn [AddEpAnn]
type instance XIParamTy GhcTc = Void type instance XIParamTy GhcTc = Void
type instance XStarTy GhcPs = NoExtField type instance XStarTy (GhcPass _) = NoExtField
type instance XStarTy GhcRn = NoExtField
type instance XStarTy GhcTc = Void
type instance XKindSig GhcPs = EpAnn [AddEpAnn] type instance XKindSig GhcPs = EpAnn [AddEpAnn]
type instance XKindSig GhcRn = EpAnn [AddEpAnn] type instance XKindSig GhcRn = EpAnn [AddEpAnn]
type instance XKindSig GhcTc = Void type instance XKindSig GhcTc = Void
...@@ -327,9 +325,8 @@ type instance XSpliceTy GhcPs = NoExtField ...@@ -327,9 +325,8 @@ type instance XSpliceTy GhcPs = NoExtField
type instance XSpliceTy GhcRn = NoExtField type instance XSpliceTy GhcRn = NoExtField
type instance XSpliceTy GhcTc = Void type instance XSpliceTy GhcTc = Void
type instance XDocTy GhcPs = EpAnn [AddEpAnn] type instance XDocTy (GhcPass _) = EpAnn [AddEpAnn]
type instance XDocTy GhcRn = EpAnn [AddEpAnn]
type instance XDocTy GhcTc = Void
type instance XBangTy GhcPs = EpAnn [AddEpAnn] type instance XBangTy GhcPs = EpAnn [AddEpAnn]
type instance XBangTy GhcRn = EpAnn [AddEpAnn] type instance XBangTy GhcRn = EpAnn [AddEpAnn]
type instance XBangTy GhcTc = Void type instance XBangTy GhcTc = Void
...@@ -346,9 +343,7 @@ type instance XExplicitTupleTy GhcPs = EpAnn [AddEpAnn] ...@@ -346,9 +343,7 @@ type instance XExplicitTupleTy GhcPs = EpAnn [AddEpAnn]
type instance XExplicitTupleTy GhcRn = NoExtField type instance XExplicitTupleTy GhcRn = NoExtField
type instance XExplicitTupleTy GhcTc = Void type instance XExplicitTupleTy GhcTc = Void
type instance XTyLit GhcPs = NoExtField type instance XTyLit (GhcPass _) = NoExtField
type instance XTyLit GhcRn = NoExtField
type instance XTyLit GhcTc = Void
type instance XWildCardTy GhcPs = NoExtField type instance XWildCardTy GhcPs = NoExtField
type instance XWildCardTy GhcRn = NoExtField type instance XWildCardTy GhcRn = NoExtField
...@@ -386,20 +381,25 @@ dsHsType t = case t of ...@@ -386,20 +381,25 @@ dsHsType t = case t of
HsTupleTy v _ _ -> dataConCantHappen v HsTupleTy v _ _ -> dataConCantHappen v
HsSumTy v _ -> dataConCantHappen v HsSumTy v _ -> dataConCantHappen v
HsOpTy _ t1 op t2 -> mkAppTys (mkTyVarTy (unLoc op)) [dsLHsType t1, dsLHsType t2] HsOpTy _ t1 op t2 -> mkAppTys (mkTyVarTy (unLoc op)) [dsLHsType t1, dsLHsType t2]
HsParTy _ t -> dsLHsType t HsParTy _ t1 -> dsLHsType t1
HsIParamTy v _ _ -> dataConCantHappen v HsIParamTy v _ _ -> dataConCantHappen v
HsKindSig v _ _ -> dataConCantHappen v HsKindSig v _ _ -> dataConCantHappen v
HsSpliceTy v _ -> dataConCantHappen v HsSpliceTy v _ -> dataConCantHappen v
HsDocTy v _ _ -> dataConCantHappen v HsDocTy _ t1 _ -> dsLHsType t1
HsBangTy v _ _ -> dataConCantHappen v HsBangTy v _ _ -> dataConCantHappen v
HsRecTy v _ -> dataConCantHappen v HsRecTy v _ -> dataConCantHappen v
HsExplicitListTy v _ _ -> dataConCantHappen v HsExplicitListTy v _ _ -> dataConCantHappen v
HsExplicitTupleTy v _ -> dataConCantHappen v HsExplicitTupleTy v _ -> dataConCantHappen v
HsTyLit v _ -> dataConCantHappen v HsTyLit _ lit -> dsHsTyLit lit
HsWildCardTy v -> dataConCantHappen v HsWildCardTy v -> dataConCantHappen v
HsStarTy v _ -> dataConCantHappen v HsStarTy _ _ -> liftedTypeKind
XHsType (HsTypeTc t' _) -> t' XHsType (HsTypeTc t' _) -> t'
dsHsTyLit :: HsTyLit -> Type
dsHsTyLit (HsNumTy _ n) = mkNumLitTy n
dsHsTyLit (HsStrTy _ str) = mkStrLitTy str
dsHsTyLit (HsCharTy _ c) = mkCharLitTy c
dsLHsType :: LHsType GhcTc -> Type dsLHsType :: LHsType GhcTc -> Type
dsLHsType = dsHsType . unLoc dsLHsType = dsHsType . unLoc
...@@ -438,14 +438,14 @@ unTcHsType t = case t of ...@@ -438,14 +438,14 @@ unTcHsType t = case t of
HsIParamTy v _ _ -> dataConCantHappen v HsIParamTy v _ _ -> dataConCantHappen v
HsKindSig v _ _ -> dataConCantHappen v HsKindSig v _ _ -> dataConCantHappen v
HsSpliceTy v _ -> dataConCantHappen v HsSpliceTy v _ -> dataConCantHappen v
HsDocTy v _ _ -> dataConCantHappen v HsDocTy x t1 doc -> HsDocTy x (unTcLHsType t1) doc
HsBangTy v _ _ -> dataConCantHappen v HsBangTy v _ _ -> dataConCantHappen v
HsRecTy v _ -> dataConCantHappen v HsRecTy v _ -> dataConCantHappen v
HsExplicitListTy v _ _ -> dataConCantHappen v HsExplicitListTy v _ _ -> dataConCantHappen v
HsExplicitTupleTy v _ -> dataConCantHappen v HsExplicitTupleTy v _ -> dataConCantHappen v
HsTyLit v _ -> dataConCantHappen v HsTyLit x lit -> HsTyLit x lit
HsWildCardTy v -> dataConCantHappen v HsWildCardTy v -> dataConCantHappen v
HsStarTy v _ -> dataConCantHappen v HsStarTy x isUni -> HsStarTy x isUni
XHsType (HsTypeTc _ t') -> t' XHsType (HsTypeTc _ t') -> t'
......
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