summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorIan Lynagh <igloo@earth.li>2012-01-25 16:30:36 +0000
committerIan Lynagh <igloo@earth.li>2012-01-26 19:54:12 +0000
commitd16f5c74627eec1e2f30153bb56e0e9fbdcf64b8 (patch)
treed2615c3f5161327af88f5cf683bf13fcd0efd427
parente3f689f745e36384c93ce7dff64d3a06360ace97 (diff)
downloadhaskell-d16f5c74627eec1e2f30153bb56e0e9fbdcf64b8.tar.gz
de-tabbed the hs-boot files
-rw-r--r--compiler/deSugar/DsExpr.lhs-boot15
-rw-r--r--compiler/deSugar/Match.lhs-boot51
-rw-r--r--compiler/hsSyn/HsExpr.lhs-boot19
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot11
-rw-r--r--compiler/rename/RnExpr.lhs-boot19
-rw-r--r--compiler/typecheck/TcExpr.lhs-boot25
-rw-r--r--compiler/typecheck/TcMatches.lhs-boot23
-rw-r--r--compiler/typecheck/TcSplice.lhs-boot27
-rw-r--r--compiler/typecheck/TcUnify.lhs-boot7
-rw-r--r--compiler/types/TyCon.lhs-boot15
10 files changed, 71 insertions, 141 deletions
diff --git a/compiler/deSugar/DsExpr.lhs-boot b/compiler/deSugar/DsExpr.lhs-boot
index 2a6d09b48e..03a47ed41b 100644
--- a/compiler/deSugar/DsExpr.lhs-boot
+++ b/compiler/deSugar/DsExpr.lhs-boot
@@ -1,16 +1,9 @@
\begin{code}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module DsExpr where
-import HsSyn ( HsExpr, LHsExpr, HsLocalBinds )
-import Var ( Id )
-import DsMonad ( DsM )
-import CoreSyn ( CoreExpr )
+import HsSyn ( HsExpr, LHsExpr, HsLocalBinds )
+import Var ( Id )
+import DsMonad ( DsM )
+import CoreSyn ( CoreExpr )
dsExpr :: HsExpr Id -> DsM CoreExpr
dsLExpr :: LHsExpr Id -> DsM CoreExpr
diff --git a/compiler/deSugar/Match.lhs-boot b/compiler/deSugar/Match.lhs-boot
index 31ee36b6e6..d10cda961e 100644
--- a/compiler/deSugar/Match.lhs-boot
+++ b/compiler/deSugar/Match.lhs-boot
@@ -1,42 +1,35 @@
\begin{code}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module Match where
-import Var ( Id )
-import TcType ( Type )
-import DsMonad ( DsM, EquationInfo, MatchResult )
-import CoreSyn ( CoreExpr )
-import HsSyn ( LPat, HsMatchContext, MatchGroup )
-import Name ( Name )
+import Var ( Id )
+import TcType ( Type )
+import DsMonad ( DsM, EquationInfo, MatchResult )
+import CoreSyn ( CoreExpr )
+import HsSyn ( LPat, HsMatchContext, MatchGroup )
+import Name ( Name )
-match :: [Id]
+match :: [Id]
-> Type
- -> [EquationInfo]
- -> DsM MatchResult
+ -> [EquationInfo]
+ -> DsM MatchResult
matchWrapper
- :: HsMatchContext Name
+ :: HsMatchContext Name
-> MatchGroup Id
- -> DsM ([Id], CoreExpr)
+ -> DsM ([Id], CoreExpr)
matchSimply
- :: CoreExpr
- -> HsMatchContext Name
- -> LPat Id
- -> CoreExpr
- -> CoreExpr
- -> DsM CoreExpr
+ :: CoreExpr
+ -> HsMatchContext Name
+ -> LPat Id
+ -> CoreExpr
+ -> CoreExpr
+ -> DsM CoreExpr
matchSinglePat
- :: CoreExpr
- -> HsMatchContext Name
- -> LPat Id
+ :: CoreExpr
+ -> HsMatchContext Name
+ -> LPat Id
-> Type
- -> MatchResult
- -> DsM MatchResult
+ -> MatchResult
+ -> DsM MatchResult
\end{code}
diff --git a/compiler/hsSyn/HsExpr.lhs-boot b/compiler/hsSyn/HsExpr.lhs-boot
index 6666243264..86032f5829 100644
--- a/compiler/hsSyn/HsExpr.lhs-boot
+++ b/compiler/hsSyn/HsExpr.lhs-boot
@@ -1,15 +1,8 @@
\begin{code}
{-# LANGUAGE KindSignatures #-}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module HsExpr where
-import SrcLoc ( Located )
+import SrcLoc ( Located )
import Outputable ( SDoc, OutputableBndr )
import {-# SOURCE #-} HsPat ( LPat )
@@ -34,17 +27,17 @@ type LHsExpr a = Located (HsExpr a)
type SyntaxExpr a = HsExpr a
pprLExpr :: (OutputableBndr i) =>
- LHsExpr i -> SDoc
+ LHsExpr i -> SDoc
pprExpr :: (OutputableBndr i) =>
- HsExpr i -> SDoc
+ HsExpr i -> SDoc
pprSplice :: (OutputableBndr i) =>
- HsSplice i -> SDoc
+ HsSplice i -> SDoc
pprPatBind :: (OutputableBndr b, OutputableBndr i) =>
- LPat b -> GRHSs i -> SDoc
+ LPat b -> GRHSs i -> SDoc
pprFunBind :: (OutputableBndr idL, OutputableBndr idR) =>
- idL -> Bool -> MatchGroup idR -> SDoc
+ idL -> Bool -> MatchGroup idR -> SDoc
\end{code}
diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot
index 0e639a3caf..7de92cb659 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot
+++ b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot
@@ -1,14 +1,7 @@
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module SPARC.CodeGen.Gen32 (
- getSomeReg,
- getRegister
+ getSomeReg,
+ getRegister
)
where
diff --git a/compiler/rename/RnExpr.lhs-boot b/compiler/rename/RnExpr.lhs-boot
index 5ca81d6db4..70d891dcbf 100644
--- a/compiler/rename/RnExpr.lhs-boot
+++ b/compiler/rename/RnExpr.lhs-boot
@@ -1,24 +1,17 @@
\begin{code}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module RnExpr where
import HsSyn
-import Name ( Name )
-import NameSet ( FreeVars )
-import RdrName ( RdrName )
+import Name ( Name )
+import NameSet ( FreeVars )
+import RdrName ( RdrName )
import TcRnTypes
rnLExpr :: LHsExpr RdrName
- -> RnM (LHsExpr Name, FreeVars)
+ -> RnM (LHsExpr Name, FreeVars)
rnStmts :: --forall thing.
- HsStmtContext Name -> [LStmt RdrName]
+ HsStmtContext Name -> [LStmt RdrName]
-> ([Name] -> RnM (thing, FreeVars))
- -> RnM (([LStmt Name], thing), FreeVars)
+ -> RnM (([LStmt Name], thing), FreeVars)
\end{code}
diff --git a/compiler/typecheck/TcExpr.lhs-boot b/compiler/typecheck/TcExpr.lhs-boot
index 7bd1e6c5c6..378a012f67 100644
--- a/compiler/typecheck/TcExpr.lhs-boot
+++ b/compiler/typecheck/TcExpr.lhs-boot
@@ -1,35 +1,28 @@
\begin{code}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module TcExpr where
-import HsSyn ( HsExpr, LHsExpr )
-import Name ( Name )
-import TcType ( TcType, TcRhoType, TcSigmaType )
+import HsSyn ( HsExpr, LHsExpr )
+import Name ( Name )
+import TcType ( TcType, TcRhoType, TcSigmaType )
import TcRnTypes( TcM, TcId, CtOrigin )
tcPolyExpr ::
- LHsExpr Name
+ LHsExpr Name
-> TcSigmaType
-> TcM (LHsExpr TcId)
tcMonoExpr, tcMonoExprNC ::
- LHsExpr Name
+ LHsExpr Name
-> TcRhoType
-> TcM (LHsExpr TcId)
tcInferRho, tcInferRhoNC ::
- LHsExpr Name
+ LHsExpr Name
-> TcM (LHsExpr TcId, TcRhoType)
tcSyntaxOp :: CtOrigin
- -> HsExpr Name
- -> TcType
- -> TcM (HsExpr TcId)
+ -> HsExpr Name
+ -> TcType
+ -> TcM (HsExpr TcId)
tcCheckId :: Name -> TcRhoType -> TcM (HsExpr TcId)
\end{code}
diff --git a/compiler/typecheck/TcMatches.lhs-boot b/compiler/typecheck/TcMatches.lhs-boot
index f898f3deb7..8c421da6da 100644
--- a/compiler/typecheck/TcMatches.lhs-boot
+++ b/compiler/typecheck/TcMatches.lhs-boot
@@ -1,24 +1,17 @@
\begin{code}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module TcMatches where
-import HsSyn ( GRHSs, MatchGroup )
+import HsSyn ( GRHSs, MatchGroup )
import TcEvidence( HsWrapper )
-import Name ( Name )
-import TcType ( TcRhoType )
+import Name ( Name )
+import TcType ( TcRhoType )
import TcRnTypes( TcM, TcId )
tcGRHSsPat :: GRHSs Name
- -> TcRhoType
- -> TcM (GRHSs TcId)
+ -> TcRhoType
+ -> TcM (GRHSs TcId)
tcMatchesFun :: Name -> Bool
- -> MatchGroup Name
- -> TcRhoType
- -> TcM (HsWrapper, MatchGroup TcId)
+ -> MatchGroup Name
+ -> TcRhoType
+ -> TcM (HsWrapper, MatchGroup TcId)
\end{code}
diff --git a/compiler/typecheck/TcSplice.lhs-boot b/compiler/typecheck/TcSplice.lhs-boot
index 5cb871a3a1..18a31b0b93 100644
--- a/compiler/typecheck/TcSplice.lhs-boot
+++ b/compiler/typecheck/TcSplice.lhs-boot
@@ -1,32 +1,25 @@
\begin{code}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module TcSplice where
-import HsSyn ( HsSplice, HsBracket, HsQuasiQuote,
+import HsSyn ( HsSplice, HsBracket, HsQuasiQuote,
HsExpr, HsType, LHsType, LHsExpr, LPat, LHsDecl )
-import Name ( Name )
-import NameSet ( FreeVars )
-import RdrName ( RdrName )
+import Name ( Name )
+import NameSet ( FreeVars )
+import RdrName ( RdrName )
import TcRnTypes( TcM, TcId )
-import TcType ( TcRhoType, TcKind )
+import TcType ( TcRhoType, TcKind )
import Annotations ( Annotation, CoreAnnTarget )
import qualified Language.Haskell.TH as TH
tcSpliceExpr :: HsSplice Name
- -> TcRhoType
- -> TcM (HsExpr TcId)
+ -> TcRhoType
+ -> TcM (HsExpr TcId)
kcSpliceType :: HsSplice Name -> FreeVars
- -> TcM (HsType Name, TcKind)
+ -> TcM (HsType Name, TcKind)
tcBracket :: HsBracket Name
- -> TcRhoType
- -> TcM (LHsExpr TcId)
+ -> TcRhoType
+ -> TcM (LHsExpr TcId)
tcSpliceDecls :: LHsExpr Name -> TcM [LHsDecl RdrName]
diff --git a/compiler/typecheck/TcUnify.lhs-boot b/compiler/typecheck/TcUnify.lhs-boot
index f53b658f40..4d07229963 100644
--- a/compiler/typecheck/TcUnify.lhs-boot
+++ b/compiler/typecheck/TcUnify.lhs-boot
@@ -1,11 +1,4 @@
\begin{code}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module TcUnify where
import TcType ( TcTauType, TcKind, Type, Kind )
import VarEnv ( TidyEnv )
diff --git a/compiler/types/TyCon.lhs-boot b/compiler/types/TyCon.lhs-boot
index dcf41dd545..d8ddff3f40 100644
--- a/compiler/types/TyCon.lhs-boot
+++ b/compiler/types/TyCon.lhs-boot
@@ -1,11 +1,4 @@
\begin{code}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module TyCon where
import Name (Name)
@@ -13,9 +6,9 @@ import Unique (Unique)
data TyCon
-tyConName :: TyCon -> Name
-tyConUnique :: TyCon -> Unique
-isTupleTyCon :: TyCon -> Bool
+tyConName :: TyCon -> Name
+tyConUnique :: TyCon -> Unique
+isTupleTyCon :: TyCon -> Bool
isUnboxedTupleTyCon :: TyCon -> Bool
-isFunTyCon :: TyCon -> Bool
+isFunTyCon :: TyCon -> Bool
\end{code}