X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FhsSyn%2FHsImpExp.lhs;h=901396724bf12b7b455c56f8beb26623a4771aa5;hb=223d65c79ea253baa64c17a1735014c959a2ae32;hp=7800a025d55fff7cc23168140bf0d784b0adaada;hpb=69e14f75a4b031e489b7774914e5a176409cea78;p=ghc-hetmet.git diff --git a/ghc/compiler/hsSyn/HsImpExp.lhs b/ghc/compiler/hsSyn/HsImpExp.lhs index 7800a02..9013967 100644 --- a/ghc/compiler/hsSyn/HsImpExp.lhs +++ b/ghc/compiler/hsSyn/HsImpExp.lhs @@ -8,9 +8,11 @@ module HsImpExp where #include "HsVersions.h" -import Module ( ModuleName, WhereFrom, pprModuleName ) +import Module ( ModuleName ) import Outputable +import FastString import SrcLoc ( SrcLoc ) +import Char ( isAlpha ) \end{code} %************************************************************************ @@ -23,7 +25,7 @@ One per \tr{import} declaration in a module. \begin{code} data ImportDecl name = ImportDecl ModuleName -- module name - WhereFrom + Bool -- True <=> {-# SOURCE #-} import Bool -- True => qualified (Maybe ModuleName) -- as Module (Maybe (Bool, [IE name])) -- (True => hiding, names) @@ -33,21 +35,26 @@ data ImportDecl name \begin{code} instance (Outputable name) => Outputable (ImportDecl name) where ppr (ImportDecl mod from qual as spec _) - = hang (hsep [ptext SLIT("import"), ppr from, - pp_qual qual, pprModuleName mod, pp_as as]) + = hang (hsep [ptext SLIT("import"), ppr_imp from, + pp_qual qual, ppr mod, pp_as as]) 4 (pp_spec spec) where pp_qual False = empty pp_qual True = ptext SLIT("qualified") pp_as Nothing = empty - pp_as (Just a) = ptext SLIT("as ") <+> pprModuleName a + 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 \end{code} %************************************************************************ @@ -71,16 +78,45 @@ ieName (IEVar n) = n ieName (IEThingAbs n) = n ieName (IEThingWith n _) = n ieName (IEThingAll n) = n + +ieNames :: IE a -> [a] +ieNames (IEVar n ) = [n] +ieNames (IEThingAbs n ) = [n] +ieNames (IEThingAll n ) = [n] +ieNames (IEThingWith n ns) = n:ns +ieNames (IEModuleContents _ ) = [] \end{code} \begin{code} instance (Outputable name) => Outputable (IE name) where - ppr (IEVar var) = ppr 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 withs))) + = ppr thing <> parens (fsep (punctuate comma (map pprHsVar withs))) ppr (IEModuleContents mod) - = ptext SLIT("module") <+> pprModuleName mod + = ptext SLIT("module") <+> ppr mod +\end{code} + +\begin{code} +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}