summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/hsSyn/HsImpExp.lhs66
1 files changed, 33 insertions, 33 deletions
diff --git a/compiler/hsSyn/HsImpExp.lhs b/compiler/hsSyn/HsImpExp.lhs
index 24ba87d301..266b6fdbeb 100644
--- a/compiler/hsSyn/HsImpExp.lhs
+++ b/compiler/hsSyn/HsImpExp.lhs
@@ -10,8 +10,8 @@ HsImpExp: Abstract syntax: imports, exports, interfaces
module HsImpExp where
-import Module ( ModuleName )
-import HsDoc ( HsDocString )
+import Module ( ModuleName )
+import HsDoc ( HsDocString )
import Outputable
import FastString
@@ -21,9 +21,9 @@ import Data.Data
\end{code}
%************************************************************************
-%* *
+%* *
\subsection{Import and export declaration lists}
-%* *
+%* *
%************************************************************************
One per \tr{import} declaration in a module.
@@ -38,7 +38,7 @@ data ImportDecl name
ideclSource :: Bool, -- ^ True <=> {-# SOURCE #-} import
ideclSafe :: Bool, -- ^ True => safe import
ideclQualified :: Bool, -- ^ True => qualified
- ideclImplicit :: Bool, -- ^ True => implicit import (of Prelude)
+ ideclImplicit :: Bool, -- ^ True => implicit import (of Prelude)
ideclAs :: Maybe ModuleName, -- ^ as Module
ideclHiding :: Maybe (Bool, [LIE name]) -- ^ (True => hiding, names)
} deriving (Data, Typeable)
@@ -64,7 +64,7 @@ instance (Outputable name) => Outputable (ImportDecl name) where
, ideclAs = as, ideclHiding = spec })
= hang (hsep [ptext (sLit "import"), ppr_imp from, pp_implicit implicit, pp_safe safe,
pp_qual qual, pp_pkg pkg, ppr mod', pp_as as])
- 4 (pp_spec spec)
+ 4 (pp_spec spec)
where
pp_implicit False = empty
pp_implicit True = ptext (sLit ("(implicit)"))
@@ -72,30 +72,30 @@ instance (Outputable name) => Outputable (ImportDecl name) where
pp_pkg Nothing = empty
pp_pkg (Just p) = doubleQuotes (ftext p)
- pp_qual False = empty
- pp_qual True = ptext (sLit "qualified")
+ pp_qual False = empty
+ pp_qual True = ptext (sLit "qualified")
- pp_safe False = empty
- pp_safe True = ptext (sLit "safe")
+ pp_safe False = empty
+ pp_safe True = ptext (sLit "safe")
- pp_as Nothing = empty
- pp_as (Just a) = ptext (sLit "as") <+> ppr a
+ pp_as Nothing = empty
+ pp_as (Just a) = ptext (sLit "as") <+> ppr a
- ppr_imp True = ptext (sLit "{-# SOURCE #-}")
- ppr_imp False = empty
+ ppr_imp True = ptext (sLit "{-# SOURCE #-}")
+ ppr_imp False = empty
- pp_spec Nothing = empty
- pp_spec (Just (False, ies)) = ppr_ies ies
- pp_spec (Just (True, ies)) = ptext (sLit "hiding") <+> ppr_ies ies
+ pp_spec Nothing = empty
+ pp_spec (Just (False, ies)) = ppr_ies ies
+ pp_spec (Just (True, ies)) = ptext (sLit "hiding") <+> ppr_ies ies
- ppr_ies [] = ptext (sLit "()")
- ppr_ies ies = char '(' <+> interpp'SP ies <+> char ')'
+ ppr_ies [] = ptext (sLit "()")
+ ppr_ies ies = char '(' <+> interpp'SP ies <+> char ')'
\end{code}
%************************************************************************
-%* *
+%* *
\subsection{Imported and exported entities}
-%* *
+%* *
%************************************************************************
\begin{code}
@@ -104,10 +104,10 @@ type LIE name = Located (IE name)
-- | Imported or exported entity.
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)
+ | 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)
| IEGroup Int HsDocString -- ^ Doc section heading
| IEDoc HsDocString -- ^ Some documentation
| IEDocNamed String -- ^ Reference to named doc
@@ -116,7 +116,7 @@ data IE name
\begin{code}
ieName :: IE name -> name
-ieName (IEVar n) = n
+ieName (IEVar n) = n
ieName (IEThingAbs n) = n
ieName (IEThingWith n _) = n
ieName (IEThingAll n) = n
@@ -126,22 +126,22 @@ ieNames :: IE a -> [a]
ieNames (IEVar n ) = [n]
ieNames (IEThingAbs n ) = [n]
ieNames (IEThingAll n ) = [n]
-ieNames (IEThingWith n ns) = n:ns
+ieNames (IEThingWith n ns) = n : ns
ieNames (IEModuleContents _ ) = []
ieNames (IEGroup _ _ ) = []
ieNames (IEDoc _ ) = []
-ieNames (IEDocNamed _ ) = []
+ieNames (IEDocNamed _ ) = []
\end{code}
\begin{code}
instance (Outputable name) => Outputable (IE name) where
- ppr (IEVar var) = pprHsVar var
- ppr (IEThingAbs thing) = ppr thing
- ppr (IEThingAll thing) = hcat [ppr thing, text "(..)"]
+ 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 pprHsVar withs)))
+ = ppr thing <> parens (fsep (punctuate comma (map pprHsVar withs)))
ppr (IEModuleContents mod')
- = ptext (sLit "module") <+> ppr mod'
+ = ptext (sLit "module") <+> ppr mod'
ppr (IEGroup n _) = text ("<IEGroup: " ++ (show n) ++ ">")
ppr (IEDoc doc) = ppr doc
ppr (IEDocNamed string) = text ("<IEDocNamed: " ++ string ++ ">")