X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FhsSyn%2FHsImpExp.lhs;h=099537f9d0d7bbc6cff9580d245e7c0882809989;hb=f16dbbbe59cf3aa19c5fd384560a1b89076d7bc8;hp=ebd18eacf82351ed53807978304c965f325a90af;hpb=17b297d97d327620ed6bfab942f8992b2446f1bf;p=ghc-hetmet.git diff --git a/compiler/hsSyn/HsImpExp.lhs b/compiler/hsSyn/HsImpExp.lhs index ebd18ea..099537f 100644 --- a/compiler/hsSyn/HsImpExp.lhs +++ b/compiler/hsSyn/HsImpExp.lhs @@ -6,24 +6,21 @@ HsImpExp: Abstract syntax: imports, exports, interfaces \begin{code} -{-# OPTIONS_GHC -w #-} +{-# OPTIONS -fno-warn-incomplete-patterns #-} -- The above warning supression flag is a temporary kludge. -- While working on this module you are encouraged to remove it and fix -- any warnings in the module. See --- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings +-- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings -- for details module HsImpExp where -#include "HsVersions.h" - import Module ( ModuleName ) import HsDoc ( HsDoc ) import Outputable import FastString import SrcLoc ( Located(..) ) -import Char ( isAlpha ) \end{code} %************************************************************************ @@ -38,6 +35,7 @@ type LImportDecl name = Located (ImportDecl name) data ImportDecl name = ImportDecl (Located ModuleName) -- module name + (Maybe FastString) -- package qualifier Bool -- True <=> {-# SOURCE #-} import Bool -- True => qualified (Maybe ModuleName) -- as Module @@ -46,27 +44,31 @@ 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_imp from, - pp_qual qual, ppr mod, pp_as as]) + ppr (ImportDecl mod pkg from qual as spec) + = hang (hsep [ptext (sLit "import"), ppr_imp from, + pp_qual qual, pp_pkg pkg, ppr mod, pp_as as]) 4 (pp_spec spec) where + pp_pkg Nothing = empty + pp_pkg (Just p) = doubleQuotes (ftext p) + pp_qual False = empty - pp_qual True = ptext SLIT("qualified") + pp_qual True = ptext (sLit "qualified") pp_as Nothing = empty - pp_as (Just a) = ptext SLIT("as ") <+> ppr a + pp_as (Just a) = ptext (sLit "as ") <+> ppr a - ppr_imp True = ptext SLIT("{-# SOURCE #-}") + 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) + = ptext (sLit "hiding") <+> parens (interpp'SP spec) -ideclName (ImportDecl mod_nm _ _ _ _) = mod_nm +ideclName :: ImportDecl name -> Located ModuleName +ideclName (ImportDecl mod_nm _ _ _ _ _) = mod_nm \end{code} %************************************************************************ @@ -115,31 +117,10 @@ instance (Outputable name) => Outputable (IE name) where ppr (IEThingWith thing withs) = ppr thing <> parens (fsep (punctuate comma (map pprHsVar withs))) ppr (IEModuleContents mod) - = ptext SLIT("module") <+> ppr mod - ppr (IEGroup n doc) = text ("") + = ptext (sLit "module") <+> ppr mod + ppr (IEGroup n _) = text ("") ppr (IEDoc doc) = ppr doc ppr (IEDocNamed string) = text ("") \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}