X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FhsSyn%2FHsImpExp.lhs;h=220afb7499c6b72bb6d6a8f4d7222e10de39f5e0;hb=e6218fe7eff4e34e1a3c823cd4b7aebe09d2d4fb;hp=b33fb2bcd730467c1a43a41b5ecbfcda13b17de3;hpb=b085ee40c7f265a5977ea6ec1c415e573be5ff8c;p=ghc-hetmet.git diff --git a/ghc/compiler/hsSyn/HsImpExp.lhs b/ghc/compiler/hsSyn/HsImpExp.lhs index b33fb2b..220afb7 100644 --- a/ghc/compiler/hsSyn/HsImpExp.lhs +++ b/ghc/compiler/hsSyn/HsImpExp.lhs @@ -8,11 +8,11 @@ module HsImpExp where #include "HsVersions.h" -import Name ( isLexSym ) -import Module ( ModuleName, WhereFrom ) +import Module ( Module ) import Outputable import FastString -import SrcLoc ( SrcLoc ) +import SrcLoc ( Located(..) ) +import Char ( isAlpha ) \end{code} %************************************************************************ @@ -23,19 +23,20 @@ import SrcLoc ( SrcLoc ) One per \tr{import} declaration in a module. \begin{code} +type LImportDecl name = Located (ImportDecl name) + data ImportDecl name - = ImportDecl ModuleName -- module name - WhereFrom + = ImportDecl (Located Module) -- module name + Bool -- True <=> {-# SOURCE #-} import Bool -- True => qualified - (Maybe ModuleName) -- as Module - (Maybe (Bool, [IE name])) -- (True => hiding, names) - SrcLoc + (Maybe Module) -- as Module + (Maybe (Bool, [LIE name])) -- (True => hiding, names) \end{code} \begin{code} instance (Outputable name) => Outputable (ImportDecl name) where - ppr (ImportDecl mod from qual as spec _) - = hang (hsep [ptext SLIT("import"), ppr from, + ppr (ImportDecl mod from qual as spec) + = hang (hsep [ptext SLIT("import"), ppr_imp from, pp_qual qual, ppr mod, pp_as as]) 4 (pp_spec spec) where @@ -45,13 +46,16 @@ instance (Outputable name) => Outputable (ImportDecl name) where pp_as Nothing = empty pp_as (Just a) = ptext SLIT("as ") <+> ppr a + ppr_imp True = ptext SLIT("{-# SOURCE #-}") + ppr_imp False = empty + pp_spec Nothing = empty pp_spec (Just (False, spec)) = parens (interpp'SP spec) pp_spec (Just (True, spec)) = ptext SLIT("hiding") <+> parens (interpp'SP spec) -ideclName (ImportDecl mod_nm _ _ _ _ _) = mod_nm +ideclName (ImportDecl mod_nm _ _ _ _) = mod_nm \end{code} %************************************************************************ @@ -61,12 +65,14 @@ ideclName (ImportDecl mod_nm _ _ _ _ _) = mod_nm %************************************************************************ \begin{code} +type LIE name = Located (IE name) + data IE name = IEVar name | IEThingAbs name -- Class/Type (can't tell) | IEThingAll name -- Class/Type plus all methods/constructors | IEThingWith name [name] -- Class/Type plus some methods/constructors - | IEModuleContents ModuleName -- (Export Only) + | IEModuleContents Module -- (Export Only) \end{code} \begin{code} @@ -86,23 +92,34 @@ ieNames (IEModuleContents _ ) = [] \begin{code} instance (Outputable name) => Outputable (IE name) where - ppr (IEVar var) = ppr_var var + ppr (IEVar var) = pprHsVar var ppr (IEThingAbs thing) = ppr thing ppr (IEThingAll thing) = hcat [ppr thing, text "(..)"] ppr (IEThingWith thing withs) - = ppr thing <> parens (fsep (punctuate comma (map ppr_var withs))) + = ppr thing <> parens (fsep (punctuate comma (map pprHsVar withs))) ppr (IEModuleContents mod) = ptext SLIT("module") <+> ppr mod - -ppr_var v | isOperator v = parens (ppr v) - | otherwise = ppr v \end{code} \begin{code} -isOperator :: Outputable a => a -> Bool -isOperator v = isLexSym (mkFastString (showSDocUnqual (ppr v))) - -- We use (showSDoc (ppr v)), rather than isSymOcc (getOccName v) simply so - -- that we don't need NamedThing in the context of all these functions. - -- Gruesome, but simple. +pprHsVar :: Outputable name => name -> SDoc +pprHsVar v | isOperator ppr_v = parens ppr_v + | otherwise = ppr_v + where + ppr_v = ppr v + +isOperator :: SDoc -> Bool +isOperator ppr_v + = case showSDocUnqual ppr_v of + ('(':s) -> False -- (), (,) etc + ('[':s) -> False -- [] + ('$':c:s) -> not (isAlpha c) -- Don't treat $d as an operator + (':':c:s) -> not (isAlpha c) -- Don't treat :T as an operator + ('_':s) -> False -- Not an operator + (c:s) -> not (isAlpha c) -- Starts with non-alpha + other -> False + -- We use (showSDoc (ppr v)), rather than isSymOcc (getOccName v) simply so + -- that we don't need NamedThing in the context of all these functions. + -- Gruesome, but simple. \end{code}