X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FhsSyn%2FHsTypes.lhs;h=def44c5917e573bb87914e989186989eee1f1934;hp=2e2eaabccf92f0fda7ab63a5a82cc6213ebc4be1;hb=34c8d0312071f7d0f4d221a997d3408c653ef9e5;hpb=836b1e90821aacc9d1e09fe78085f911597274c8 diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index 2e2eaab..def44c5 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -6,6 +6,8 @@ HsTypes: Abstract syntax: user-defined types \begin{code} +{-# LANGUAGE DeriveDataTypeable #-} + module HsTypes ( HsType(..), LHsType, HsTyVarBndr(..), LHsTyVarBndr, @@ -42,6 +44,8 @@ import SrcLoc import StaticFlags import Outputable import FastString + +import Data.Data \end{code} @@ -76,6 +80,7 @@ data HsQuasiQuote id = HsQuasiQuote id -- The quasi-quoter SrcSpan -- The span of the enclosed string FastString -- The enclosed string + deriving (Data, Typeable) instance OutputableBndr id => Outputable (HsQuasiQuote id) where ppr = ppr_qq @@ -97,16 +102,6 @@ ppr_qq (HsQuasiQuote quoter _ quote) = type LBangType name = Located (BangType name) type BangType name = HsType name -- Bangs are in the HsType data type -data HsBang = HsNoBang -- Only used as a return value for getBangStrictness, - -- never appears on a HsBangTy - | HsStrict -- ! - | HsUnbox -- {-# UNPACK #-} ! (GHC extension, meaning "unbox") - -instance Outputable HsBang where - ppr (HsNoBang) = empty - ppr (HsStrict) = char '!' - ppr (HsUnbox) = ptext (sLit "!!") - getBangType :: LHsType a -> LHsType a getBangType (L _ (HsBangTy _ ty)) = ty getBangType ty = ty @@ -135,6 +130,7 @@ type LHsPred name = Located (HsPred name) data HsPred name = HsClassP name [LHsType name] -- class constraint | HsEqualP (LHsType name) (LHsType name)-- equality constraint | HsIParam (IPName name) (LHsType name) + deriving (Data, Typeable) type LHsType name = Located (HsType name) @@ -159,6 +155,8 @@ data HsType name | HsPArrTy (LHsType name) -- Elem. type of parallel array: [:t:] + | HsModalBoxType name (LHsType name) -- modal types; first argument is the environment classifier + | HsTupleTy Boxity [LHsType name] -- Element types (length gives arity) @@ -179,7 +177,7 @@ data HsType name -- ^^^^ -- HsPredTy -- Note no need for location info on the - -- enclosed HsPred; the one on the type will do + -- Enclosed HsPred; the one on the type will do | HsKindSig (LHsType name) -- (ty :: kind) Kind -- A type with a kind signature @@ -195,13 +193,18 @@ data HsType name | HsBangTy HsBang (LHsType name) -- Bang-style type annotations | HsRecTy [ConDeclField name] -- Only in data type declarations -data HsExplicitFlag = Explicit | Implicit + | HsCoreTy Type -- An escape hatch for tunnelling a *closed* + -- Core Type through HsSyn. + + deriving (Data, Typeable) + +data HsExplicitFlag = Explicit | Implicit deriving (Data, Typeable) data ConDeclField name -- Record fields have Haddoc docs on them = ConDeclField { cd_fld_name :: Located name, cd_fld_type :: LBangType name, cd_fld_doc :: Maybe LHsDocString } - + deriving (Data, Typeable) ----------------------- -- Combine adjacent for-alls. @@ -257,6 +260,7 @@ data HsTyVarBndr name -- *** NOTA BENE *** A "monotype" in a pragma can have -- for-alls in it, (mostly to do with dictionaries). These -- must be explicitly Kinded. + deriving (Data, Typeable) hsTyVarName :: HsTyVarBndr name -> name hsTyVarName (UserTyVar n _) = n @@ -355,8 +359,16 @@ pprHsForAll exp tvs cxt forall_part = ptext (sLit "forall") <+> interppSP tvs <> dot pprHsContext :: (OutputableBndr name) => HsContext name -> SDoc -pprHsContext [] = empty -pprHsContext cxt = ppr_hs_context cxt <+> ptext (sLit "=>") +pprHsContext [] = empty +pprHsContext [L _ pred] + | noParenHsPred pred = ppr pred <+> darrow +pprHsContext cxt = ppr_hs_context cxt <+> darrow + +noParenHsPred :: HsPred name -> Bool +-- c.f. TypeRep.noParenPred +noParenHsPred (HsClassP {}) = True +noParenHsPred (HsEqualP {}) = True +noParenHsPred (HsIParam {}) = False ppr_hs_context :: (OutputableBndr name) => HsContext name -> SDoc ppr_hs_context [] = empty @@ -429,9 +441,11 @@ ppr_mono_ty _ (HsTupleTy con tys) = tupleParens con (interpp'SP tys) ppr_mono_ty _ (HsKindSig ty kind) = parens (ppr_mono_lty pREC_TOP ty <+> dcolon <+> pprKind kind) ppr_mono_ty _ (HsListTy ty) = brackets (ppr_mono_lty pREC_TOP ty) ppr_mono_ty _ (HsPArrTy ty) = pabrackets (ppr_mono_lty pREC_TOP ty) +ppr_mono_ty _ (HsModalBoxType ecn ty) = ppr_modalBoxType (ppr ecn) (ppr_mono_lty pREC_TOP ty) ppr_mono_ty _ (HsPredTy pred) = ppr pred ppr_mono_ty _ (HsNumTy n) = integer n -- generics only ppr_mono_ty _ (HsSpliceTy s _ _) = pprSplice s +ppr_mono_ty _ (HsCoreTy ty) = ppr ty ppr_mono_ty ctxt_prec (HsAppTy fun_ty arg_ty) = maybeParen ctxt_prec pREC_CON $ @@ -465,6 +479,10 @@ ppr_fun_ty ctxt_prec ty1 ty2 -------------------------- pabrackets :: SDoc -> SDoc pabrackets p = ptext (sLit "[:") <> p <> ptext (sLit ":]") + +ppr_modalBoxType :: SDoc -> SDoc -> SDoc +ppr_modalBoxType ecn p = ptext (sLit "<[") <> p <> ptext (sLit "]>@") <> ecn + \end{code}