X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FhsSyn%2FHsImpExp.lhs;h=9083d9e18c5d9e792570df1b057d41a17c76149b;hb=438596897ebbe25a07e1c82085cfbc5bdb00f09e;hp=0305911e60ed4fe048c09a6e596147a6c0bb7bd9;hpb=7a3bd641457666e10d0a47be9f22762e03defbf0;p=ghc-hetmet.git diff --git a/ghc/compiler/hsSyn/HsImpExp.lhs b/ghc/compiler/hsSyn/HsImpExp.lhs index 0305911..9083d9e 100644 --- a/ghc/compiler/hsSyn/HsImpExp.lhs +++ b/ghc/compiler/hsSyn/HsImpExp.lhs @@ -1,19 +1,16 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996 +% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % \section[HsImpExp]{Abstract syntax: imports, exports, interfaces} \begin{code} -#include "HsVersions.h" - module HsImpExp where -IMP_Ubiq() +#include "HsVersions.h" -import Name ( pprNonSym ) +import BasicTypes ( Module, IfaceFlavour(..) ) +import Name ( NamedThing ) import Outputable -import PprStyle ( PprStyle(..) ) -import Pretty import SrcLoc ( SrcLoc ) \end{code} @@ -28,6 +25,8 @@ One per \tr{import} declaration in a module. data ImportDecl name = ImportDecl Module -- module name Bool -- True => qualified + IfaceFlavour -- True => source imported module + -- (current interpretation: ignore ufolding info) (Maybe Module) -- as Module (Maybe (Bool, [IE name])) -- (True => hiding, names) SrcLoc @@ -35,21 +34,25 @@ data ImportDecl name \begin{code} instance (NamedThing name, Outputable name) => Outputable (ImportDecl name) where - ppr sty (ImportDecl mod qual as spec _) - = ppHang (ppCat [ppPStr SLIT("import"), pp_qual qual, ppPStr mod, pp_as as]) + ppr (ImportDecl mod qual as_source as spec _) + = hang (hsep [ptext SLIT("import"), pp_src as_source, + pp_qual qual, ptext mod, pp_as as]) 4 (pp_spec spec) where - pp_qual False = ppNil - pp_qual True = ppPStr SLIT("qualified") + pp_src HiFile = empty + pp_src HiBootFile = ptext SLIT("{-# SOURCE #-}") + + pp_qual False = empty + pp_qual True = ptext SLIT("qualified") - pp_as Nothing = ppNil - pp_as (Just a) = ppBeside (ppPStr SLIT("as ")) (ppPStr a) + pp_as Nothing = empty + pp_as (Just a) = ptext SLIT("as ") <+> ptext a - pp_spec Nothing = ppNil + pp_spec Nothing = empty pp_spec (Just (False, spec)) - = ppParens (interpp'SP sty spec) + = parens (interpp'SP spec) pp_spec (Just (True, spec)) - = ppBeside (ppPStr SLIT("hiding ")) (ppParens (interpp'SP sty spec)) + = ptext SLIT("hiding") <+> parens (interpp'SP spec) \end{code} %************************************************************************ @@ -77,14 +80,12 @@ ieName (IEThingAll n) = n \begin{code} instance (NamedThing name, Outputable name) => Outputable (IE name) where - ppr sty (IEVar var) = pprNonSym sty var - ppr sty (IEThingAbs thing) = ppr sty thing - ppr sty (IEThingAll thing) - = ppBesides [ppr sty thing, ppStr "(..)"] - ppr sty (IEThingWith thing withs) - = ppBeside (ppr sty thing) - (ppParens (ppInterleave ppComma (map (pprNonSym sty) withs))) - ppr sty (IEModuleContents mod) - = ppBeside (ppPStr SLIT("module ")) (ppPStr mod) + ppr (IEVar var) = ppr 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 (IEModuleContents mod) + = ptext SLIT("module") <+> ptext mod \end{code}