diff --git a/compiler/basicTypes/Avail.hs b/compiler/basicTypes/Avail.hs index 8bf622e13d52f9a8b6eee357db54f8ed3dda5612..758a10412b9f6f8234c3cd9a58b6e94cd7ce04ee 100644 --- a/compiler/basicTypes/Avail.hs +++ b/compiler/basicTypes/Avail.hs @@ -2,6 +2,13 @@ -- (c) The University of Glasgow -- +{-# 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 Avail ( Avails, AvailInfo(..), diff --git a/compiler/basicTypes/BasicTypes.lhs b/compiler/basicTypes/BasicTypes.lhs index b2ffd70e352f73f1a45ca7b6f73ac483b364a90d..1f42d252ce54dc4d7ea1597a10e4851153f73642 100644 --- a/compiler/basicTypes/BasicTypes.lhs +++ b/compiler/basicTypes/BasicTypes.lhs @@ -16,6 +16,13 @@ types that \begin{code} {-# LANGUAGE DeriveDataTypeable #-} +{-# 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 BasicTypes( Version, bumpVersion, initialVersion, diff --git a/compiler/basicTypes/DataCon.lhs b/compiler/basicTypes/DataCon.lhs index 9bb41fcd60f6e5a403f9a9b304a3300374daf7c4..d1716755bfa0ceee3704a89306042cc1f2efd1d8 100644 --- a/compiler/basicTypes/DataCon.lhs +++ b/compiler/basicTypes/DataCon.lhs @@ -5,6 +5,13 @@ \section[DataCon]{@DataCon@: Data Constructors} \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 DataCon ( -- * Main data types DataCon, DataConIds(..), diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index b1e9ccb50eb6d9b46765bc0c560ceb1b3cc8dd3d..c4143edd4523ddc4fb64a718c422d97add967bc9 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -5,6 +5,13 @@ \section[Demand]{@Demand@: the amount of demand on a value} \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 Demand( Demand(..), topDmd, lazyDmd, seqDmd, evalDmd, errDmd, isStrictDmd, diff --git a/compiler/basicTypes/Id.lhs b/compiler/basicTypes/Id.lhs index e88bfa13302ac3b688c7ac74d9f870589ca87761..1a4f95c26a8bf31b904eaa22fd3c5d808ef15129 100644 --- a/compiler/basicTypes/Id.lhs +++ b/compiler/basicTypes/Id.lhs @@ -21,6 +21,14 @@ -- be global or local, see "Var#globalvslocal" -- -- * 'Var.Var': see "Var#name_types" + +{-# 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 Id ( -- * The main types Var, Id, isId, diff --git a/compiler/basicTypes/IdInfo.lhs b/compiler/basicTypes/IdInfo.lhs index 815cc7b6f428c8dfbed2f5362f61665bf3992c83..0d715ef02838f7bd2422b55ac0ba93642103e28c 100644 --- a/compiler/basicTypes/IdInfo.lhs +++ b/compiler/basicTypes/IdInfo.lhs @@ -8,6 +8,13 @@ Haskell. [WDP 94/11]) \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 IdInfo ( -- * The IdDetails type IdDetails(..), pprIdDetails, coVarDetails, diff --git a/compiler/basicTypes/Literal.lhs b/compiler/basicTypes/Literal.lhs index a3bd6fcbf0726298b9bf04bfb555b56c680347a6..7fef7c7f5ef173d08dca17a3a02b02193451084a 100644 --- a/compiler/basicTypes/Literal.lhs +++ b/compiler/basicTypes/Literal.lhs @@ -7,6 +7,13 @@ \begin{code} {-# LANGUAGE DeriveDataTypeable #-} +{-# 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 Literal ( -- * Main data type diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index e3a46899d75db6cba162f8a25bc19e1fec6c8855..a7184e01ed4dfc713da0dbfd617ae34589037e75 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -12,6 +12,13 @@ have a standard form, namely: - primitive operations \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 MkId ( mkDictFunId, mkDictFunTy, mkDictSelId, diff --git a/compiler/basicTypes/Module.lhs b/compiler/basicTypes/Module.lhs index e35c4d5a315953ddfe805632df64cd76f4f237a3..06fd6a5c734b776d8f1a8d1d4e6b16d3c88d5e6f 100644 --- a/compiler/basicTypes/Module.lhs +++ b/compiler/basicTypes/Module.lhs @@ -9,6 +9,13 @@ These are Uniquable, hence we can build Maps with Modules as the keys. \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 Module ( -- * The ModuleName type diff --git a/compiler/basicTypes/Name.lhs b/compiler/basicTypes/Name.lhs index 7a80ac1f16183524d3955bed1d591df6e7531da2..fde589044b090f2c47c539d5242d7004a41f2ede 100644 --- a/compiler/basicTypes/Name.lhs +++ b/compiler/basicTypes/Name.lhs @@ -31,6 +31,13 @@ -- * Internal, if they name things in the module being compiled. Some internal -- Names are system names, if they are names manufactured by the compiler +{-# 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 Name ( -- * The main types Name, -- Abstract diff --git a/compiler/basicTypes/NameEnv.lhs b/compiler/basicTypes/NameEnv.lhs index 0dc5c32c7ab38de66723ae971b0fd56e55d0a21f..8a59e7d2202ed0bd0f10a3390fe1cf4e950918fd 100644 --- a/compiler/basicTypes/NameEnv.lhs +++ b/compiler/basicTypes/NameEnv.lhs @@ -5,6 +5,13 @@ \section[NameEnv]{@NameEnv@: name environments} \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 NameEnv ( -- * Var, Id and TyVar environments (maps) NameEnv, diff --git a/compiler/basicTypes/NameSet.lhs b/compiler/basicTypes/NameSet.lhs index ebb5b9fd8697000c409c55b7e84715084c75c7b8..62fff75356975131d48207dfa5fe849ec2b9f496 100644 --- a/compiler/basicTypes/NameSet.lhs +++ b/compiler/basicTypes/NameSet.lhs @@ -4,6 +4,13 @@ % \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 NameSet ( -- * Names set type NameSet, diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 0df37e43008d2558bb7ba1ef2bcfb21ca6f43df5..a48a7d44bd9bcd3a3a3f1a160adfa7f1f47c717e 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -19,6 +19,14 @@ -- * 'Id.Id': see "Id#name_types" -- -- * 'Var.Var': see "Var#name_types" + +{-# 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 OccName ( -- * The 'NameSpace' type NameSpace, -- Abstract diff --git a/compiler/basicTypes/RdrName.lhs b/compiler/basicTypes/RdrName.lhs index b410d5914c4d885d4869b931bce3f38af1d7fb09..ba09d923b83d2e004b81cdf6cb5c0c802659c010 100644 --- a/compiler/basicTypes/RdrName.lhs +++ b/compiler/basicTypes/RdrName.lhs @@ -22,6 +22,14 @@ -- * 'Id.Id': see "Id#name_types" -- -- * 'Var.Var': see "Var#name_types" + +{-# 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 RdrName ( -- * The main type RdrName(..), -- Constructors exported only to BinIface diff --git a/compiler/basicTypes/SrcLoc.lhs b/compiler/basicTypes/SrcLoc.lhs index 7061793b82ae02b1ed18a7a1556658e5a41b7c0b..bb7c4c363ec9d99e2c9b126a0a04ab9d02b4ea81 100644 --- a/compiler/basicTypes/SrcLoc.lhs +++ b/compiler/basicTypes/SrcLoc.lhs @@ -8,6 +8,13 @@ -- When the earliest compiler we want to boostrap with is -- GHC 7.2, we can make RealSrcLoc properly abstract +{-# 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 + -- | This module contains types that relate to the positions of things -- in source files, and allow tagging of those things with locations diff --git a/compiler/basicTypes/Unique.lhs b/compiler/basicTypes/Unique.lhs index e7411e78835df14fd9942cb05c5804f71a5ddc44..6fba95c0b51eeead6c6cf321cc41476881ec2877 100644 --- a/compiler/basicTypes/Unique.lhs +++ b/compiler/basicTypes/Unique.lhs @@ -17,6 +17,14 @@ Haskell). \begin{code} {-# LANGUAGE BangPatterns #-} + +{-# 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 Unique ( -- * Main data types Unique, Uniquable(..), diff --git a/compiler/basicTypes/Var.lhs b/compiler/basicTypes/Var.lhs index ae8bada526f0f69c49fcadd5452b6d1af2a1eb61..a923f4d9dd70395d6138c3fa9c5b77a10a6a17c7 100644 --- a/compiler/basicTypes/Var.lhs +++ b/compiler/basicTypes/Var.lhs @@ -5,6 +5,13 @@ \section{@Vars@: Variables} \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 + -- | -- #name_types# -- GHC uses several kinds of name internally: diff --git a/compiler/basicTypes/VarEnv.lhs b/compiler/basicTypes/VarEnv.lhs index 905c0b5dfb10f4d2842e091def48113af807cb83..cdd79f5db278af8e4ea0640de5c7225ecbfa3e38 100644 --- a/compiler/basicTypes/VarEnv.lhs +++ b/compiler/basicTypes/VarEnv.lhs @@ -4,6 +4,13 @@ % \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 VarEnv ( -- * Var, Id and TyVar environments (maps) VarEnv, IdEnv, TyVarEnv, CoVarEnv, diff --git a/compiler/basicTypes/VarSet.lhs b/compiler/basicTypes/VarSet.lhs index c7464c34d79f516901718efac6f4d93ab776e7c7..5c71db99cc25edcbf13e2343ee30f115738571a8 100644 --- a/compiler/basicTypes/VarSet.lhs +++ b/compiler/basicTypes/VarSet.lhs @@ -4,6 +4,13 @@ % \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 VarSet ( -- * Var, Id and TyVar set types VarSet, IdSet, TyVarSet, CoVarSet, diff --git a/compiler/cmm/Bitmap.hs b/compiler/cmm/Bitmap.hs index acd398c8d5ffd0477bc9eedc9842d367b17b7784..1fbbf8fdf3fe52a1585399e083bfb8c4c9889b1a 100644 --- a/compiler/cmm/Bitmap.hs +++ b/compiler/cmm/Bitmap.hs @@ -6,6 +6,13 @@ -- places in generated code (stack frame liveness masks, function -- argument liveness masks, SRT bitmaps). +{-# 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 Bitmap ( Bitmap, mkBitmap, intsToBitmap, intsToReverseBitmap, diff --git a/compiler/cmm/Cmm.hs b/compiler/cmm/Cmm.hs index f18b417ad9b36397256a1b71756645590da1d4c0..93a1dc1e52df5a7d17d91f3456ff5d815b783e92 100644 --- a/compiler/cmm/Cmm.hs +++ b/compiler/cmm/Cmm.hs @@ -2,6 +2,13 @@ {-# LANGUAGE GADTs #-} {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} +{-# 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 + {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} #if __GLASGOW_HASKELL__ >= 703 -- GHC 7.0.1 improved incomplete pattern warnings with GADTs diff --git a/compiler/cmm/CmmBuildInfoTables.hs b/compiler/cmm/CmmBuildInfoTables.hs index 0301deb5931254e4997b7e79418507a36224133f..9873e82e077d7a8f948cc349697c1b78be3b1497 100644 --- a/compiler/cmm/CmmBuildInfoTables.hs +++ b/compiler/cmm/CmmBuildInfoTables.hs @@ -1,4 +1,11 @@ {-# OPTIONS_GHC -XGADTs -XNoMonoLocalBinds #-} +{-# 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 + -- Norman likes local bindings -- If this module lives on I'd like to get rid of this flag in due course diff --git a/compiler/cmm/CmmCallConv.hs b/compiler/cmm/CmmCallConv.hs index c81b868167f070b0de92b6613474ee1607236814..d3d9ba4b418b40a7c55f3862d293189eb25fd058 100644 --- a/compiler/cmm/CmmCallConv.hs +++ b/compiler/cmm/CmmCallConv.hs @@ -1,3 +1,10 @@ +{-# 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 CmmCallConv ( ParamLocation(..), assignArgumentsPos diff --git a/compiler/cmm/CmmExpr.hs b/compiler/cmm/CmmExpr.hs index b8cd3280e86ee27273966a9945fe0bd7fa4e89b5..ef97a82aa96edf88b0654883d053ab0d93010df8 100644 --- a/compiler/cmm/CmmExpr.hs +++ b/compiler/cmm/CmmExpr.hs @@ -1,4 +1,11 @@ +{-# 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 CmmExpr ( CmmExpr(..), cmmExprType, cmmExprWidth, maybeInvertCmmExpr , CmmReg(..), cmmRegType diff --git a/compiler/cmm/CmmInfo.hs b/compiler/cmm/CmmInfo.hs index 15f255472f0094e0de70fec1b8f42f34249abf82..a13ae12135d859139190e863d496f0195c5936c2 100644 --- a/compiler/cmm/CmmInfo.hs +++ b/compiler/cmm/CmmInfo.hs @@ -1,3 +1,10 @@ +{-# 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 CmmInfo ( mkEmptyContInfoTable, cmmToRawCmm, diff --git a/compiler/cmm/CmmLint.hs b/compiler/cmm/CmmLint.hs index ff41d58a326b15c070aa2be016f5fc4b7421711c..14fca533ae1395fb3590cef2cffa1a027fe3edc3 100644 --- a/compiler/cmm/CmmLint.hs +++ b/compiler/cmm/CmmLint.hs @@ -12,6 +12,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 CmmLint ( cmmLint, cmmLintTop ) where diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index e9b84b568ad3e28fdcf24d342f4d16fb1da3112d..4844af9d9ad9bc175f5a12d5b2df68a6efa8f0bf 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -1,6 +1,13 @@ -- CmmNode type for representation using Hoopl graphs. {-# LANGUAGE GADTs #-} +{-# 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 + {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} #if __GLASGOW_HASKELL__ >= 703 -- GHC 7.0.1 improved incomplete pattern warnings with GADTs diff --git a/compiler/cmm/CmmStackLayout.hs b/compiler/cmm/CmmStackLayout.hs index 85e4af03be0dd198debfa43dd3c79be81776d6fb..c659f41149d9e0fcbbf2e3726a152c406077d73f 100644 --- a/compiler/cmm/CmmStackLayout.hs +++ b/compiler/cmm/CmmStackLayout.hs @@ -2,6 +2,13 @@ -- Norman likes local bindings -- If this module lives on I'd like to get rid of this flag in due course +{-# 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 + -- Todo: remove {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs index 1a97c9702720fc5022fc9bba330885182e84a246..6d02e693fb33b966a81505d7aedbf8729faab866 100644 --- a/compiler/cmm/CmmUtils.hs +++ b/compiler/cmm/CmmUtils.hs @@ -1,4 +1,11 @@ {-# LANGUAGE GADTs #-} +{-# 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 + {-# OPTIONS_GHC -fno-warn-deprecations #-} -- Warnings from deprecated blockToNodeList {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} diff --git a/compiler/cmm/MkGraph.hs b/compiler/cmm/MkGraph.hs index bc2e4112d932f51f389608bcb7be8967c16229de..58bee2797d779ebf15a7164d3acf2df3d7a332ed 100644 --- a/compiler/cmm/MkGraph.hs +++ b/compiler/cmm/MkGraph.hs @@ -1,4 +1,11 @@ {-# LANGUAGE GADTs #-} +{-# 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 + {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} -- ToDo: remove {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} diff --git a/compiler/cmm/OldCmm.hs b/compiler/cmm/OldCmm.hs index 6b71fd66a86f46948f5cf9aa29f3fe158596f52f..3703de4e326853881473f912ea5f262ae4eb121d 100644 --- a/compiler/cmm/OldCmm.hs +++ b/compiler/cmm/OldCmm.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 OldCmm ( CmmGroup, GenCmmGroup, RawCmmGroup, CmmDecl, RawCmmDecl, ListGraph(..), diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index 08e28a91a687dc7dc419abaea8ceaa0ae4939031..bd861ff53d1abad17f661fbfc05d1c1477142a61 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -16,6 +16,13 @@ -- disappeared from the data type. -- +{-# 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 PprC ( writeCs, pprStringInCStyle diff --git a/compiler/cmm/PprCmmDecl.hs b/compiler/cmm/PprCmmDecl.hs index 370428d7505933904844ab3181794158c03d6fd1..1143d9beff59699c5ac2a45876f2434fe96d16c2 100644 --- a/compiler/cmm/PprCmmDecl.hs +++ b/compiler/cmm/PprCmmDecl.hs @@ -32,6 +32,13 @@ -- A useful example pass over Cmm is in nativeGen/MachCodeGen.hs -- +{-# 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 PprCmmDecl ( writeCmms, pprCmms, pprCmmGroup, pprSection, pprStatic ) diff --git a/compiler/cmm/PprCmmExpr.hs b/compiler/cmm/PprCmmExpr.hs index aa86ca04fc9f4df9c01ebe1d9d6be8296b9e7f41..76fbdcec8d6ae1580c42956aa683f9a5b853be2c 100644 --- a/compiler/cmm/PprCmmExpr.hs +++ b/compiler/cmm/PprCmmExpr.hs @@ -32,6 +32,13 @@ -- A useful example pass over Cmm is in nativeGen/MachCodeGen.hs -- +{-# 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 PprCmmExpr ( pprExpr, pprLit , pprExpr9 {-only to import in OldPprCmm. When it dies, remove the export -} diff --git a/compiler/cmm/SMRep.lhs b/compiler/cmm/SMRep.lhs index 44b40a3a8a06836184c70a817ab594739356c6cf..ce30799bf620ced56df7dd59c525835af0b8d8ed 100644 --- a/compiler/cmm/SMRep.lhs +++ b/compiler/cmm/SMRep.lhs @@ -9,6 +9,13 @@ This is here, rather than in ClosureInfo, just to keep nhc happy. Other modules should access this info through ClosureInfo. \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 SMRep ( -- * Words and bytes StgWord, StgHalfWord, diff --git a/compiler/codeGen/CgBindery.lhs b/compiler/codeGen/CgBindery.lhs index 3cccbef310a3e0fdccea3862fb557663065f202e..65f8a529812401fab09427076658ac0f16a3cfaa 100644 --- a/compiler/codeGen/CgBindery.lhs +++ b/compiler/codeGen/CgBindery.lhs @@ -5,6 +5,13 @@ \section[CgBindery]{Utility functions related to doing @CgBindings@} \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 CgBindery ( CgBindings, CgIdInfo, StableLoc, VolatileLoc, diff --git a/compiler/codeGen/CgCallConv.hs b/compiler/codeGen/CgCallConv.hs index 345b65cd3cb4b39a5a6a007bf550dd78c4273c43..0a3911ea82906f4dc71467330b870d04b1d94429 100644 --- a/compiler/codeGen/CgCallConv.hs +++ b/compiler/codeGen/CgCallConv.hs @@ -9,6 +9,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 CgCallConv ( -- Argument descriptors mkArgDescr, diff --git a/compiler/codeGen/CgCase.lhs b/compiler/codeGen/CgCase.lhs index 0eace0d57752defd825495dbf47910765b9796c8..c3141f4fd7e0cc95f6331cdc21d32d62c16332b2 100644 --- a/compiler/codeGen/CgCase.lhs +++ b/compiler/codeGen/CgCase.lhs @@ -4,6 +4,13 @@ % \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 CgCase ( cgCase, saveVolatileVarsAndRegs, restoreCurrentCostCentre ) where diff --git a/compiler/codeGen/CgClosure.lhs b/compiler/codeGen/CgClosure.lhs index 32190a3c9cbc80e8c2e5c16d227c38f7fc2ec33a..85d629dbaf1cadaf72248a557d2db8e96723731f 100644 --- a/compiler/codeGen/CgClosure.lhs +++ b/compiler/codeGen/CgClosure.lhs @@ -9,6 +9,13 @@ with {\em closures} on the RHSs of let(rec)s. See also @CgCon@, which deals with constructors. \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 CgClosure ( cgTopRhsClosure, cgStdRhsClosure, cgRhsClosure, diff --git a/compiler/codeGen/CgExpr.lhs b/compiler/codeGen/CgExpr.lhs index 5ffa4e550d4e6472491018b51748e6f84004a945..e69db9f61bb8e5ddf81a4b05d3a6bae63f27407c 100644 --- a/compiler/codeGen/CgExpr.lhs +++ b/compiler/codeGen/CgExpr.lhs @@ -4,6 +4,13 @@ % \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 CgExpr ( cgExpr ) where #include "HsVersions.h" diff --git a/compiler/codeGen/CgExtCode.hs b/compiler/codeGen/CgExtCode.hs index 5c56ee0bd5dcead06fb40884824129c51c4ee754..c94f23701b575878bb6a74613764a7baba8e3b4d 100644 --- a/compiler/codeGen/CgExtCode.hs +++ b/compiler/codeGen/CgExtCode.hs @@ -9,6 +9,13 @@ -- to collect declarations as we parse the proc, and feed the environment -- back in circularly (to avoid a two-pass algorithm). +{-# 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 CgExtCode ( ExtFCode(..), ExtCode, diff --git a/compiler/codeGen/CgForeignCall.hs b/compiler/codeGen/CgForeignCall.hs index 493b3a181b0de3c22215e4cc2f5106d69e622fb9..295d76344aac88c0ae513059c2e41a9a98f8b60b 100644 --- a/compiler/codeGen/CgForeignCall.hs +++ b/compiler/codeGen/CgForeignCall.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 CgForeignCall ( cgForeignCall, emitForeignCall, diff --git a/compiler/codeGen/CgHeapery.lhs b/compiler/codeGen/CgHeapery.lhs index 9e9cc8d1d81ed46ea0c0f76b7e3c42cd89313867..03b5deb058388dc72a353092664ce3ef8299492e 100644 --- a/compiler/codeGen/CgHeapery.lhs +++ b/compiler/codeGen/CgHeapery.lhs @@ -5,6 +5,13 @@ \section[CgHeapery]{Heap management functions} \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 CgHeapery ( initHeapUsage, getVirtHp, setVirtHp, setRealHp, getHpRelOffset, hpRel, diff --git a/compiler/codeGen/CgInfoTbls.hs b/compiler/codeGen/CgInfoTbls.hs index 305081d6800c51dd6d7e6e5c8ceaa1c2de2a017e..2ff422299b73a82a6b7854b46a7a168e7e4a3e60 100644 --- a/compiler/codeGen/CgInfoTbls.hs +++ b/compiler/codeGen/CgInfoTbls.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 CgInfoTbls ( emitClosureCodeAndInfoTable, emitInfoTableAndCode, diff --git a/compiler/codeGen/CgLetNoEscape.lhs b/compiler/codeGen/CgLetNoEscape.lhs index 9f878dcf6030c5bf03bc41bad98609a61c9d91f4..2fb603baed457d0e23279a68ee1573677837eb95 100644 --- a/compiler/codeGen/CgLetNoEscape.lhs +++ b/compiler/codeGen/CgLetNoEscape.lhs @@ -9,6 +9,13 @@ %******************************************************** \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 CgLetNoEscape ( cgLetNoEscapeClosure ) where #include "HsVersions.h" diff --git a/compiler/codeGen/CgMonad.lhs b/compiler/codeGen/CgMonad.lhs index f9ddeb959c4927f20db139025e3e6b2f2a7afb3e..1c9cfa7ec1ba613417916eb7b9117b4c8d292950 100644 --- a/compiler/codeGen/CgMonad.lhs +++ b/compiler/codeGen/CgMonad.lhs @@ -8,6 +8,13 @@ See the beginning of the top-level @CodeGen@ module, to see how this monadic stuff fits into the Big Picture. \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 + {-# LANGUAGE BangPatterns #-} module CgMonad ( Code, -- type diff --git a/compiler/codeGen/CgParallel.hs b/compiler/codeGen/CgParallel.hs index 682f28aad4ba6333524b8c275b1df9606ad1a6e8..2804104708b063781364aad5ddac723eded847cb 100644 --- a/compiler/codeGen/CgParallel.hs +++ b/compiler/codeGen/CgParallel.hs @@ -8,6 +8,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 CgParallel( staticGranHdr,staticParHdr, granFetchAndReschedule, granYield, diff --git a/compiler/codeGen/CgPrimOp.hs b/compiler/codeGen/CgPrimOp.hs index e8f75b5dfec3d663325d1599e5844ff96dda711e..23708fe56828665f204cee64ae0751064c1a8324 100644 --- a/compiler/codeGen/CgPrimOp.hs +++ b/compiler/codeGen/CgPrimOp.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 CgPrimOp ( cgPrimOp ) where diff --git a/compiler/codeGen/CgProf.hs b/compiler/codeGen/CgProf.hs index b43751361c1c7fb4ccba67635725fe52332b3bff..23a602c174b790ec9e379b9b3ced9f0ee38f8c36 100644 --- a/compiler/codeGen/CgProf.hs +++ b/compiler/codeGen/CgProf.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 CgProf ( mkCCostCentre, mkCCostCentreStack, diff --git a/compiler/codeGen/CgStackery.lhs b/compiler/codeGen/CgStackery.lhs index e6024e7410a80b46dee2b7fa1b15813a2cf39953..2628760183cd18b6043fbaf530ce98d4b7bbb7f9 100644 --- a/compiler/codeGen/CgStackery.lhs +++ b/compiler/codeGen/CgStackery.lhs @@ -8,6 +8,13 @@ Stack-twiddling operations, which are pretty low-down and grimy. (This is the module that knows all about stack layouts, etc.) \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 CgStackery ( spRel, getVirtSp, getRealSp, setRealSp, setRealAndVirtualSp, getSpRelOffset, diff --git a/compiler/codeGen/CgTailCall.lhs b/compiler/codeGen/CgTailCall.lhs index 994ad105ecde1d01faf055eedca92c86f79e0621..fb8f854c0ba7a153b5dbfbd0b6b01a21703e70d6 100644 --- a/compiler/codeGen/CgTailCall.lhs +++ b/compiler/codeGen/CgTailCall.lhs @@ -5,6 +5,13 @@ % Code generation for tail calls. \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 CgTailCall ( cgTailCall, performTailCall, performReturn, performPrimReturn, diff --git a/compiler/codeGen/CgTicky.hs b/compiler/codeGen/CgTicky.hs index 1e814fe15d314d8d1fbaa6dcf02310b58f837dc3..04f38ac8c402dbdad31234829bc16cb728bc423a 100644 --- a/compiler/codeGen/CgTicky.hs +++ b/compiler/codeGen/CgTicky.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 CgTicky ( emitTickyCounter, diff --git a/compiler/codeGen/ClosureInfo.lhs b/compiler/codeGen/ClosureInfo.lhs index 66eeb34c5f6d88b742180829d01539fd0e5dbf0f..ac047edb892e8b060d5d62a5d18cac92fd4a4b68 100644 --- a/compiler/codeGen/ClosureInfo.lhs +++ b/compiler/codeGen/ClosureInfo.lhs @@ -12,6 +12,13 @@ Much of the rationale for these things is in the ``details'' part of the STG paper. \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 ClosureInfo ( ClosureInfo(..), LambdaFormInfo(..), -- would be abstract but StandardFormInfo(..), -- mkCmmInfo looks inside diff --git a/compiler/codeGen/CodeGen.lhs b/compiler/codeGen/CodeGen.lhs index 806f654df03416b123b9aad9d4d905e619381ef1..08af9715dff194322f375d78f534cc27a86e97e7 100644 --- a/compiler/codeGen/CodeGen.lhs +++ b/compiler/codeGen/CodeGen.lhs @@ -11,6 +11,13 @@ This module says how things get going at the top level. functions drive the mangling of top-level bindings. \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 CodeGen ( codeGen ) where #include "HsVersions.h" diff --git a/compiler/codeGen/StgCmm.hs b/compiler/codeGen/StgCmm.hs index 0928645964df4177f5be580dea252337dae13439..7aa159844bf0b58b90255014b973152799bc08c3 100644 --- a/compiler/codeGen/StgCmm.hs +++ b/compiler/codeGen/StgCmm.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmm ( codeGen ) where #define FAST_STRING_NOT_NEEDED diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 4f60d0a6cfb16a529d5649802d97c7489ba83d52..9bf57b1cb497399d49abdb715f4e82a259850dbe 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmBind ( cgTopRhsClosure, cgBind, diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs index ede24a5c6f354df252f95834cf549d75cc71fea1..5c0741a65ee8006be88afd88cc315beabaa144e7 100644 --- a/compiler/codeGen/StgCmmClosure.hs +++ b/compiler/codeGen/StgCmmClosure.hs @@ -10,6 +10,13 @@ ----------------------------------------------------------------------------- {-# LANGUAGE RecordWildCards #-} +{-# 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 StgCmmClosure ( DynTag, tagForCon, isSmallFamily, ConTagZ, dataConTagZ, diff --git a/compiler/codeGen/StgCmmEnv.hs b/compiler/codeGen/StgCmmEnv.hs index 45429226759007b42606b71fa9b591125dca6cb3..d8a7061eec2fb228f1ab96357ac811279beaf821 100644 --- a/compiler/codeGen/StgCmmEnv.hs +++ b/compiler/codeGen/StgCmmEnv.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmEnv ( CgIdInfo, diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index bc4e9df44fad830967a54ef340c1373b1ca7d3e4..5ea935984d411349e39194e81d73b69b74622cb9 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmExpr ( cgExpr ) where #define FAST_STRING_NOT_NEEDED diff --git a/compiler/codeGen/StgCmmForeign.hs b/compiler/codeGen/StgCmmForeign.hs index 54a0214bcbc94298c258f682c128842833c8a302..f07fd6c6bcb8dafa30bc145e99b9399ef1713084 100644 --- a/compiler/codeGen/StgCmmForeign.hs +++ b/compiler/codeGen/StgCmmForeign.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmForeign ( cgForeignCall, loadThreadState, saveThreadState, emitPrimCall, emitCCall, diff --git a/compiler/codeGen/StgCmmGran.hs b/compiler/codeGen/StgCmmGran.hs index b6a1ae66bbbfd0f7d6c6d1afa7a1d5e3bc8cfcf2..232c7c6b583f37368d0717c7ac9b93ca53116d3e 100644 --- a/compiler/codeGen/StgCmmGran.hs +++ b/compiler/codeGen/StgCmmGran.hs @@ -8,6 +8,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmGran ( staticGranHdr,staticParHdr, granThunk, granYield, diff --git a/compiler/codeGen/StgCmmLayout.hs b/compiler/codeGen/StgCmmLayout.hs index f8137dc5648547b99daf092a7f0e03c7d4eb73f7..9afcd029a4f0e0a444a65bf4f884839481c0d9c6 100644 --- a/compiler/codeGen/StgCmmLayout.hs +++ b/compiler/codeGen/StgCmmLayout.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmLayout ( mkArgDescr, emitCall, emitReturn, diff --git a/compiler/codeGen/StgCmmMonad.hs b/compiler/codeGen/StgCmmMonad.hs index 7263f751c35ba42b47f2cbe6f9e041c8ceb81ade..cab0897fe8daffafc8575322313d5e6c0ceac5a5 100644 --- a/compiler/codeGen/StgCmmMonad.hs +++ b/compiler/codeGen/StgCmmMonad.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmMonad ( FCode, -- type diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index 4ce830a4eed1b7e06975d417cf57609a69edeee9..8935d565376315713cc5302c4241874a34971b5c 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmPrim ( cgOpApp ) where diff --git a/compiler/codeGen/StgCmmProf.hs b/compiler/codeGen/StgCmmProf.hs index 17b61c6a5974a2ca341f620c20316a3f452c2b58..338e10428b6e765704aa2648a9e27b89e18b86d1 100644 --- a/compiler/codeGen/StgCmmProf.hs +++ b/compiler/codeGen/StgCmmProf.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmProf ( initCostCentres, ccType, ccsType, mkCCostCentre, mkCCostCentreStack, diff --git a/compiler/codeGen/StgCmmTicky.hs b/compiler/codeGen/StgCmmTicky.hs index 88ff1389dd6915f4b7bb6632b568db1f0351d5ca..8b8ab34989df7afb014a2d1c3ee8f34253467a05 100644 --- a/compiler/codeGen/StgCmmTicky.hs +++ b/compiler/codeGen/StgCmmTicky.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmTicky ( emitTickyCounter, diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs index ddb87e4ffec84525d349a8ab386fa2ba7bfc538f..ca0d23a3ac9d68c2dc2908134edd28ce0ea8a2ce 100644 --- a/compiler/codeGen/StgCmmUtils.hs +++ b/compiler/codeGen/StgCmmUtils.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 StgCmmUtils ( cgLit, mkSimpleLit, emitDataLits, mkDataLits, diff --git a/compiler/coreSyn/CoreArity.lhs b/compiler/coreSyn/CoreArity.lhs index 0292cf967e41959a02106ed2bb9447bb77f306f6..63661ec08126eb5eca10a5107fc1cd6c881b3ac4 100644 --- a/compiler/coreSyn/CoreArity.lhs +++ b/compiler/coreSyn/CoreArity.lhs @@ -6,6 +6,13 @@ Arity and ete expansion \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 + -- | Arit and eta expansion module CoreArity ( manifestArity, exprArity, exprBotStrictness_maybe, diff --git a/compiler/coreSyn/CoreFVs.lhs b/compiler/coreSyn/CoreFVs.lhs index 4eaf965cc832d956cc0dcf59763f465b44358a47..0c30e1e9bcded2dfddee220e47c3b3be98498358 100644 --- a/compiler/coreSyn/CoreFVs.lhs +++ b/compiler/coreSyn/CoreFVs.lhs @@ -5,6 +5,13 @@ Taken quite directly from the Peyton Jones/Lester paper. \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 + {-# 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 diff --git a/compiler/coreSyn/CoreLint.lhs b/compiler/coreSyn/CoreLint.lhs index e5ed04bb690da80c17c5444aeafd52e5f6a326d7..9351da1716a27f6c8b2d72e621bad0f5a3f6ed47 100644 --- a/compiler/coreSyn/CoreLint.lhs +++ b/compiler/coreSyn/CoreLint.lhs @@ -7,6 +7,13 @@ A ``lint'' pass to check for Core correctness \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 CoreLint ( lintCoreBindings, lintUnfolding ) where #include "HsVersions.h" diff --git a/compiler/coreSyn/CorePrep.lhs b/compiler/coreSyn/CorePrep.lhs index 06d8d5bab46789a0c672f67b123dbcc5f0e80376..df568fce2385407b829853159c9f76f8a6d60f34 100644 --- a/compiler/coreSyn/CorePrep.lhs +++ b/compiler/coreSyn/CorePrep.lhs @@ -6,6 +6,13 @@ Core pass to saturate constructors and PrimOps \begin{code} {-# LANGUAGE BangPatterns #-} +{-# 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 CorePrep ( corePrepPgm, corePrepExpr ) where diff --git a/compiler/coreSyn/CoreSubst.lhs b/compiler/coreSyn/CoreSubst.lhs index c61e20e9356e25ed6913b9ba8b9fda0bdbd7eb71..728c4ec446d9b7f90e235c6bcc7205b8a633fd7c 100644 --- a/compiler/coreSyn/CoreSubst.lhs +++ b/compiler/coreSyn/CoreSubst.lhs @@ -6,6 +6,13 @@ Utility functions on @Core@ syntax \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 CoreSubst ( -- * Main data types Subst(..), -- Implementation exported for supercompiler's Renaming.hs only diff --git a/compiler/coreSyn/CoreSyn.lhs b/compiler/coreSyn/CoreSyn.lhs index e5c14b43565d0c77ea1accb81112b7fcc1da3e87..ea0ef2242f6eb71d0ece10a83b77d2951ca30958 100644 --- a/compiler/coreSyn/CoreSyn.lhs +++ b/compiler/coreSyn/CoreSyn.lhs @@ -6,6 +6,13 @@ \begin{code} {-# LANGUAGE DeriveDataTypeable, DeriveFunctor #-} +{-# 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 + -- | CoreSyn holds all the main data types for use by for the Glasgow Haskell Compiler midsection module CoreSyn ( -- * Main data types diff --git a/compiler/coreSyn/CoreTidy.lhs b/compiler/coreSyn/CoreTidy.lhs index 4004d3fa0e7947b8f8c1ce5a5c2514ba8c77fcd0..2045538ace6cbed4a2df12e6c61f2a9e8f1bde6c 100644 --- a/compiler/coreSyn/CoreTidy.lhs +++ b/compiler/coreSyn/CoreTidy.lhs @@ -7,6 +7,13 @@ This module contains "tidying" code for *nested* expressions, bindings, rules. The code for *top-level* bindings is in TidyPgm. \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 CoreTidy ( tidyExpr, tidyVarOcc, tidyRule, tidyRules, tidyUnfolding ) where diff --git a/compiler/coreSyn/CoreUnfold.lhs b/compiler/coreSyn/CoreUnfold.lhs index 5c9d1b2a4ccf695c69b3dcefefa89ed8c0905649..4f1dee3da32cd4c4bf4e3f9390f3864133b9ab28 100644 --- a/compiler/coreSyn/CoreUnfold.lhs +++ b/compiler/coreSyn/CoreUnfold.lhs @@ -15,6 +15,13 @@ literal''). In the corner of a @CoreUnfolding@ unfolding, you will find, unsurprisingly, a Core expression. \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 CoreUnfold ( Unfolding, UnfoldingGuidance, -- Abstract types diff --git a/compiler/coreSyn/ExternalCore.lhs b/compiler/coreSyn/ExternalCore.lhs index 51342beb7fb778e4244f1f7d052fe951fe7916dc..3d416f78a4e31f9ed7d8beb7abfec5e78d336868 100644 --- a/compiler/coreSyn/ExternalCore.lhs +++ b/compiler/coreSyn/ExternalCore.lhs @@ -2,6 +2,13 @@ % (c) The University of Glasgow 2001-2006 % \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 ExternalCore where data Module diff --git a/compiler/coreSyn/MkCore.lhs b/compiler/coreSyn/MkCore.lhs index 4375dd9b972e1feac736c5b881a39460bbadc996..d941b0a4b100dc3986a7b4d7126e23aa9156581e 100644 --- a/compiler/coreSyn/MkCore.lhs +++ b/compiler/coreSyn/MkCore.lhs @@ -1,4 +1,11 @@ \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 + -- | Handy functions for creating much Core syntax module MkCore ( -- * Constructing normal syntax diff --git a/compiler/coreSyn/MkExternalCore.lhs b/compiler/coreSyn/MkExternalCore.lhs index c185e49bfd176a7cecd285d0071f3bbd877ca6be..e38885ba546f61d689408e1aafbef139fa80b085 100644 --- a/compiler/coreSyn/MkExternalCore.lhs +++ b/compiler/coreSyn/MkExternalCore.lhs @@ -2,6 +2,13 @@ % (c) The University of Glasgow 2001-2006 % \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 MkExternalCore ( emitExternalCore ) where diff --git a/compiler/coreSyn/PprCore.lhs b/compiler/coreSyn/PprCore.lhs index 877814037de8d9368c2dba21130da9fd353ce291..2ba8a23120040a4da0292fc205cbf97d25df50b5 100644 --- a/compiler/coreSyn/PprCore.lhs +++ b/compiler/coreSyn/PprCore.lhs @@ -6,6 +6,13 @@ Printing of Core syntax \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 PprCore ( pprCoreExpr, pprParendExpr, pprCoreBinding, pprCoreBindings, pprCoreAlt, diff --git a/compiler/coreSyn/PprExternalCore.lhs b/compiler/coreSyn/PprExternalCore.lhs index d6b8b53dfd487933216a537d7c4090016fa0c00d..571b816e594b931bcdf31444ed162ebb5e5ae370 100644 --- a/compiler/coreSyn/PprExternalCore.lhs +++ b/compiler/coreSyn/PprExternalCore.lhs @@ -3,6 +3,13 @@ % \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 PprExternalCore () where import Encoding diff --git a/compiler/coreSyn/TrieMap.lhs b/compiler/coreSyn/TrieMap.lhs index 831baeade162b56f66e77566f5e20e60c1ab7cac..b7ee95c2af2a3c3a46a5113e9e865c3fcc67bc07 100644 --- a/compiler/coreSyn/TrieMap.lhs +++ b/compiler/coreSyn/TrieMap.lhs @@ -4,6 +4,13 @@ % \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 + {-# LANGUAGE TypeFamilies #-} module TrieMap( CoreMap, emptyCoreMap, extendCoreMap, lookupCoreMap, foldCoreMap, diff --git a/compiler/deSugar/Check.lhs b/compiler/deSugar/Check.lhs index 49d9f3de1c8b112d24ec80bce262a8bce1722eeb..01ceeb2295ae85f0c4e6f107b24cf84f30e53986 100644 --- a/compiler/deSugar/Check.lhs +++ b/compiler/deSugar/Check.lhs @@ -5,6 +5,13 @@ % Author: Juan J. Quintela \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 + {-# 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 diff --git a/compiler/deSugar/Coverage.lhs b/compiler/deSugar/Coverage.lhs index fc28b147fbdecd64693e88d4956edf1112487708..5e5534748d4f6fbaa2c32a27deb69a3e12b0f2d7 100644 --- a/compiler/deSugar/Coverage.lhs +++ b/compiler/deSugar/Coverage.lhs @@ -3,6 +3,13 @@ % (c) University of Glasgow, 2007 % \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 Coverage (addTicksToBinds, hpcInitCode) where import Type diff --git a/compiler/deSugar/Desugar.lhs b/compiler/deSugar/Desugar.lhs index b8f1af3a65a8c21d133d454ccb52dd12b851f908..b2ca5320ae8f275fb4535a245e43411c8fd2be1d 100644 --- a/compiler/deSugar/Desugar.lhs +++ b/compiler/deSugar/Desugar.lhs @@ -6,6 +6,13 @@ The Desugarer: turning HsSyn into Core. \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 Desugar ( deSugar, deSugarExpr ) where import DynFlags diff --git a/compiler/deSugar/DsArrows.lhs b/compiler/deSugar/DsArrows.lhs index b3fdc8f8b739b8f8bc534da646cf7fb96bacb7bf..d276baf86dfdaf2b743851b851678d5d51b1bd72 100644 --- a/compiler/deSugar/DsArrows.lhs +++ b/compiler/deSugar/DsArrows.lhs @@ -6,6 +6,13 @@ Desugaring arrow commands \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 DsArrows ( dsProcExpr ) where #include "HsVersions.h" diff --git a/compiler/deSugar/DsBinds.lhs b/compiler/deSugar/DsBinds.lhs index f207074cd893448ef9ab0d500658ef066909298c..f3be1964a87daca6b11c96d40d6347c5681d9daa 100644 --- a/compiler/deSugar/DsBinds.lhs +++ b/compiler/deSugar/DsBinds.lhs @@ -10,6 +10,13 @@ in that the @Rec@/@NonRec@/etc structure is thrown away (whereas at lower levels it is preserved with @let@/@letrec@s). \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 DsBinds ( dsTopLHsBinds, dsLHsBinds, decomposeRuleLhs, dsSpec, dsHsWrapper, dsTcEvBinds, dsEvBinds, ) where diff --git a/compiler/deSugar/DsCCall.lhs b/compiler/deSugar/DsCCall.lhs index f926f53a087dce4ca680415804d2cebc395d052a..79412b576c248ac33fff7b00383b86c2f63ffa5b 100644 --- a/compiler/deSugar/DsCCall.lhs +++ b/compiler/deSugar/DsCCall.lhs @@ -6,6 +6,13 @@ Desugaring foreign calls \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 DsCCall ( dsCCall , mkFCall diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index 3d79ce7150aea8ab10e054d3214e4a3333824ac8..74e5bf51f2afeea2be6ac5a5c103f26bc746c6a4 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -6,6 +6,13 @@ Desugaring exporessions. \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 + {-# 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 diff --git a/compiler/deSugar/DsExpr.lhs-boot b/compiler/deSugar/DsExpr.lhs-boot index c65e99d80db34a59fb45f139b7b309c2f2513391..2a6d09b48e03627c841fa8cdbc33393621277a5c 100644 --- a/compiler/deSugar/DsExpr.lhs-boot +++ b/compiler/deSugar/DsExpr.lhs-boot @@ -1,4 +1,11 @@ \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 ) diff --git a/compiler/deSugar/DsGRHSs.lhs b/compiler/deSugar/DsGRHSs.lhs index 9b80852a864dd07856689c3bac98e3a7151c61e2..8df556d7949112dedc1e516c72e7da057909e2d1 100644 --- a/compiler/deSugar/DsGRHSs.lhs +++ b/compiler/deSugar/DsGRHSs.lhs @@ -6,6 +6,13 @@ Matching guarded right-hand-sides (GRHSs) \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 + {-# 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 diff --git a/compiler/deSugar/DsListComp.lhs b/compiler/deSugar/DsListComp.lhs index aabd6b0d0d0776ed06632f65f321f55182f9e9b1..99dae749895658deea888a7938ff58c8cc6fad3e 100644 --- a/compiler/deSugar/DsListComp.lhs +++ b/compiler/deSugar/DsListComp.lhs @@ -6,6 +6,13 @@ Desugaring list comprehensions, monad comprehensions and array comprehensions \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 + {-# LANGUAGE NamedFieldPuns #-} {-# OPTIONS -fno-warn-incomplete-patterns #-} -- The above warning supression flag is a temporary kludge. diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index ff104c3f4f7a5b71466c53e7b94ef87d21e4d571..628f911308e2c063cf382dfd72f3fb774fa06aa8 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -13,6 +13,13 @@ -- a Royal Pain (triggers other recompilation). ----------------------------------------------------------------------------- +{-# 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 DsMeta( dsBracket, templateHaskellNames, qTyConName, nameTyConName, liftName, liftStringName, expQTyConName, patQTyConName, diff --git a/compiler/deSugar/DsUtils.lhs b/compiler/deSugar/DsUtils.lhs index 1bdeafb411d6040329faaef5325cf7968318e36b..dc3f99bbbcea728566724eafffabc035b5ead0fa 100644 --- a/compiler/deSugar/DsUtils.lhs +++ b/compiler/deSugar/DsUtils.lhs @@ -8,6 +8,13 @@ Utilities for desugaring This module exports some utility functions of no great interest. \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 + -- | Utility functions for constructing Core syntax, principally for desugaring module DsUtils ( EquationInfo(..), diff --git a/compiler/deSugar/Match.lhs b/compiler/deSugar/Match.lhs index 69f378eb1b5cb0df03c80172bfe5a6a3cffccee8..236a05bcb5f00a3dd77e89ffbc7644f565b5e5aa 100644 --- a/compiler/deSugar/Match.lhs +++ b/compiler/deSugar/Match.lhs @@ -6,6 +6,13 @@ The @match@ function \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 ( match, matchEquations, matchWrapper, matchSimply, matchSinglePat ) where #include "HsVersions.h" diff --git a/compiler/deSugar/Match.lhs-boot b/compiler/deSugar/Match.lhs-boot index 28f5136b1d88465a0971283d29b70ad28aeddc13..31ee36b6e6419249175f569e731be24a78c26018 100644 --- a/compiler/deSugar/Match.lhs-boot +++ b/compiler/deSugar/Match.lhs-boot @@ -1,4 +1,11 @@ \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 ) diff --git a/compiler/deSugar/MatchCon.lhs b/compiler/deSugar/MatchCon.lhs index 231ecd59025a72431f8a055e79a83b73e8777340..989008a5ca706c8514bfe12d9005c688b0598945 100644 --- a/compiler/deSugar/MatchCon.lhs +++ b/compiler/deSugar/MatchCon.lhs @@ -6,6 +6,13 @@ Pattern-matching constructors \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 MatchCon ( matchConFamily ) where #include "HsVersions.h" diff --git a/compiler/deSugar/MatchLit.lhs b/compiler/deSugar/MatchLit.lhs index 173bad999c68f18d3fcb6bb48d69b030a71deea4..84ec34247381dfd067f52137a32b20b645702822 100644 --- a/compiler/deSugar/MatchLit.lhs +++ b/compiler/deSugar/MatchLit.lhs @@ -6,6 +6,13 @@ Pattern-matching literal patterns \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 MatchLit ( dsLit, dsOverLit, hsLitKey, hsOverLitKey, tidyLitPat, tidyNPat, matchLiterals, matchNPlusKPats, matchNPats ) where diff --git a/compiler/ghci/ByteCodeGen.lhs b/compiler/ghci/ByteCodeGen.lhs index c7912b80f39efd445fc175a2d17f74aea07a6bc8..afc51163e3f56c631b93eee4175e9c02e755e318 100644 --- a/compiler/ghci/ByteCodeGen.lhs +++ b/compiler/ghci/ByteCodeGen.lhs @@ -5,6 +5,13 @@ ByteCodeGen: Generate bytecode from Core \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 ByteCodeGen ( UnlinkedBCO, byteCodeGen, coreExprToBCOs ) where #include "HsVersions.h" diff --git a/compiler/ghci/ByteCodeInstr.lhs b/compiler/ghci/ByteCodeInstr.lhs index 84a9af2b6fd4ebbc20faf577ee77254fecb9e883..ada0be6f0f733a4eb0edd3dc21f3de102843d7f7 100644 --- a/compiler/ghci/ByteCodeInstr.lhs +++ b/compiler/ghci/ByteCodeInstr.lhs @@ -4,6 +4,13 @@ ByteCodeInstrs: Bytecode instruction definitions \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 + {-# OPTIONS_GHC -funbox-strict-fields #-} module ByteCodeInstr ( diff --git a/compiler/ghci/ByteCodeItbls.lhs b/compiler/ghci/ByteCodeItbls.lhs index 78b06e77a872b0fa2958154cc7338e3a084528f9..3c1cbb5d02e6e2389b0ed0e79e116d0628524c5a 100644 --- a/compiler/ghci/ByteCodeItbls.lhs +++ b/compiler/ghci/ByteCodeItbls.lhs @@ -4,6 +4,13 @@ ByteCodeItbls: Generate infotables for interpreter-made bytecodes \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 + {-# OPTIONS -optc-DNON_POSIX_SOURCE #-} {-# OPTIONS -w #-} diff --git a/compiler/ghci/LibFFI.hsc b/compiler/ghci/LibFFI.hsc index 86714effa42f3b4bfc4331719ce2b33190404407..d54307973ef73a3ac29ae92db3d77dae468294ea 100644 --- a/compiler/ghci/LibFFI.hsc +++ b/compiler/ghci/LibFFI.hsc @@ -8,6 +8,13 @@ #include +{-# 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#TabsvsSp +-- for details + module LibFFI ( ForeignCallToken, prepForeignCall diff --git a/compiler/ghci/Linker.lhs b/compiler/ghci/Linker.lhs index e0a11ddcd3efc47a9e1af6a88422ba4243fed747..3e9ab435797c4bbab059b74d0e72140220809708 100644 --- a/compiler/ghci/Linker.lhs +++ b/compiler/ghci/Linker.lhs @@ -8,6 +8,13 @@ -- calling the object-code linker and the byte-code linker where -- necessary. +{-# 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 + {-# OPTIONS -fno-cse #-} -- -fno-cse is needed for GLOBAL_VAR's to behave properly diff --git a/compiler/ghci/ObjLink.lhs b/compiler/ghci/ObjLink.lhs index f45914560624c300142f0413ff5ac374181298e6..ea644b9d90edbc66fb69d3fb83cf1b56ffef1688 100644 --- a/compiler/ghci/ObjLink.lhs +++ b/compiler/ghci/ObjLink.lhs @@ -9,6 +9,13 @@ Primarily, this module consists of an interface to the C-land dynamic linker. \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 ObjLink ( initObjLinker, -- :: IO () loadDLL, -- :: String -> IO (Maybe String) diff --git a/compiler/ghci/RtClosureInspect.hs b/compiler/ghci/RtClosureInspect.hs index 340899fa8a01bbc55f435cefe91bfd73fce15731..84d0acf3169c1d1c867613ea7969e771c26eae95 100644 --- a/compiler/ghci/RtClosureInspect.hs +++ b/compiler/ghci/RtClosureInspect.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 RtClosureInspect( cvObtainTerm, -- :: HscEnv -> Int -> Bool -> Maybe Type -> HValue -> IO Term cvReconstructType, diff --git a/compiler/hsSyn/Convert.lhs b/compiler/hsSyn/Convert.lhs index f9c275e4f321e3247f247b5cad6caf5c1f903d96..fc33dc125f8967bdf2a2ad37cd1876c4f6ec2e82 100644 --- a/compiler/hsSyn/Convert.lhs +++ b/compiler/hsSyn/Convert.lhs @@ -6,6 +6,13 @@ This module converts Template Haskell syntax into HsSyn \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 Convert( convertToHsExpr, convertToPat, convertToHsDecls, convertToHsType, thRdrNameGuesses ) where diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 56d0040788c772f57895124c2344242f11ae142e..9cdc47d3a4188502d18fc461b8dcc4f6c3857466 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -7,6 +7,13 @@ Datatype for: @BindGroup@, @Bind@, @Sig@, @Bind@. \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 + {-# LANGUAGE DeriveDataTypeable #-} module HsBinds where diff --git a/compiler/hsSyn/HsExpr.lhs b/compiler/hsSyn/HsExpr.lhs index 31d65b47db2181cd4b9d08bc89435f61035b83c0..869532e858a3ee25e1575996af1f5c292c175bf4 100644 --- a/compiler/hsSyn/HsExpr.lhs +++ b/compiler/hsSyn/HsExpr.lhs @@ -3,6 +3,13 @@ % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % \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 + {-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables #-} -- | Abstract Haskell syntax for expressions. diff --git a/compiler/hsSyn/HsExpr.lhs-boot b/compiler/hsSyn/HsExpr.lhs-boot index ccae21055aaab284bedd38c3884057fb22098a4b..4dff75c802345acd97e160e267bbef6e1c00bd75 100644 --- a/compiler/hsSyn/HsExpr.lhs-boot +++ b/compiler/hsSyn/HsExpr.lhs-boot @@ -1,4 +1,11 @@ \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 HsExpr where import SrcLoc ( Located ) diff --git a/compiler/hsSyn/HsLit.lhs b/compiler/hsSyn/HsLit.lhs index 2b556ea7aa2b35b80d8451d9371762c0f35c1c19..b8e4b11e6b6f0ed99add70203fd562568afbd9c6 100644 --- a/compiler/hsSyn/HsLit.lhs +++ b/compiler/hsSyn/HsLit.lhs @@ -5,6 +5,13 @@ \section[HsLit]{Abstract syntax: source-language literals} \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 + {-# LANGUAGE DeriveDataTypeable #-} module HsLit where diff --git a/compiler/hsSyn/HsPat.lhs b/compiler/hsSyn/HsPat.lhs index 5c404a6ae883f329f4b275ae7b6cf72b14ffaf35..201515ec9fdea311be26a6271800bedf877e2a38 100644 --- a/compiler/hsSyn/HsPat.lhs +++ b/compiler/hsSyn/HsPat.lhs @@ -5,6 +5,13 @@ \section[PatSyntax]{Abstract Haskell syntax---patterns} \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 + {-# 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 diff --git a/compiler/hsSyn/HsSyn.lhs b/compiler/hsSyn/HsSyn.lhs index ce748ebfab65cc788d317c240e6f87b9f336433e..a8ae81e93564bb8bc8de8d8a22bef446a872bf8d 100644 --- a/compiler/hsSyn/HsSyn.lhs +++ b/compiler/hsSyn/HsSyn.lhs @@ -9,6 +9,13 @@ which is declared in the various \tr{Hs*} modules. This module, therefore, is almost nothing but re-exporting. \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 + {-# LANGUAGE DeriveDataTypeable #-} module HsSyn ( diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index 89a002b63c2d6ad4b0c1be5096b7b3f6e4e7f615..9e20dbdd4db2b54bfdf56f5905e50831e45b1385 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -6,6 +6,13 @@ HsTypes: Abstract syntax: user-defined types \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 + {-# LANGUAGE DeriveDataTypeable #-} module HsTypes ( diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index 3b520c0c9e55b972cb34b6c76791ea24f52e176c..207c2bc18915b7c4cad94701c919360cd1b59d14 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -14,6 +14,13 @@ which deal with the intantiated versions are located elsewhere: Id typecheck/TcHsSyn \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 HsUtils( -- Terms mkHsPar, mkHsApp, mkHsConApp, mkSimpleHsAlt, diff --git a/compiler/iface/BinIface.hs b/compiler/iface/BinIface.hs index d7d6311a7e654ab943dac85ca300a1db2a56fe61..166fabe1d97b092db6d7a3070242a6386988b16a 100644 --- a/compiler/iface/BinIface.hs +++ b/compiler/iface/BinIface.hs @@ -1,3 +1,10 @@ +{-# 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 + {-# OPTIONS_GHC -O #-} -- We always optimise this, otherwise performance of a non-optimised -- compiler is severely affected diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 70106529894c04325e3e8aca0510a2575b8e01b0..348da8c6c48aebac3c6970cdce6734e56d190e48 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -4,6 +4,13 @@ % \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 BuildTyCl ( buildSynTyCon, buildAlgTyCon, diff --git a/compiler/iface/IfaceEnv.lhs b/compiler/iface/IfaceEnv.lhs index 0cecf39d1f81e03efd1afab6fc2bfcd6f80763e3..4c66a983141ffeb1ade319ffdff4a7832eecccfd 100644 --- a/compiler/iface/IfaceEnv.lhs +++ b/compiler/iface/IfaceEnv.lhs @@ -1,6 +1,13 @@ (c) The University of Glasgow 2002-2006 \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 IfaceEnv ( newGlobalBinder, newImplicitBinder, lookupIfaceTop, diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 57b179946ecf108caf97e422f21266aca01a223d..deeac37c65ddc52cf5558456cb5344b17d81d9cd 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -4,6 +4,13 @@ % \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 IfaceSyn ( module IfaceType, diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs index f2bf13d42a437828a317eea233730c89bec6c91c..471acd0639175b61033c5e1e3b4da3212f625098 100644 --- a/compiler/iface/IfaceType.lhs +++ b/compiler/iface/IfaceType.lhs @@ -6,6 +6,13 @@ This module defines interface types and binders \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 IfaceType ( IfExtName, IfLclName, IfIPName, diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs index 4fea1166b0fab1b4a126486694342291955db412..6dbcc8c68b55e21f9ab53633937a2d3427f9659b 100644 --- a/compiler/iface/MkIface.lhs +++ b/compiler/iface/MkIface.lhs @@ -4,6 +4,13 @@ % \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 MkIface ( mkUsedNames, mkDependencies, diff --git a/compiler/main/Annotations.lhs b/compiler/main/Annotations.lhs index f031f14dc9af595cca2ce3df8c1cae0381b042f8..ec61a1f4a6ce2048d9ed87a0a976f574d71cdc16 100644 --- a/compiler/main/Annotations.lhs +++ b/compiler/main/Annotations.lhs @@ -4,6 +4,13 @@ % \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 Annotations ( -- * Main Annotation data types Annotation(..), diff --git a/compiler/main/CodeOutput.lhs b/compiler/main/CodeOutput.lhs index 4941d5eea1f98b5cb3f7c445f8eebc44dc80edc5..c97be6e13efd56a9c186cd4d1e0c8958b2c99ad7 100644 --- a/compiler/main/CodeOutput.lhs +++ b/compiler/main/CodeOutput.lhs @@ -4,6 +4,13 @@ \section{Code output phase} \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 CodeOutput( codeOutput, outputForeignStubs ) where #include "HsVersions.h" diff --git a/compiler/main/Constants.lhs b/compiler/main/Constants.lhs index 236f1f8653c23593d6890761471d66b58e0f306d..2e276f64c67a5113cae63be8eb7793110b34ae7c 100644 --- a/compiler/main/Constants.lhs +++ b/compiler/main/Constants.lhs @@ -4,6 +4,13 @@ \section[Constants]{Info about this compilation} \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 Constants (module Constants) where #include "ghc_boot_platform.h" diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs index 1835430f1330cfd1cd95506df4def1ff395f4753..2a0785d4993fe94956271c7257082c260a4782b2 100644 --- a/compiler/main/DriverPhases.hs +++ b/compiler/main/DriverPhases.hs @@ -7,6 +7,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 DriverPhases ( HscSource(..), isHsBoot, hscSourceString, Phase(..), diff --git a/compiler/main/ErrUtils.lhs b/compiler/main/ErrUtils.lhs index f47b8be935bc2bc87dbffe340a5e2a5ab8497c30..614d25aed183841c0583ffe79473581a2d3f0397 100644 --- a/compiler/main/ErrUtils.lhs +++ b/compiler/main/ErrUtils.lhs @@ -4,6 +4,13 @@ \section[ErrsUtils]{Utilities for error reporting} \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 ErrUtils ( Message, mkLocMessage, printError, pprMessageBag, Severity(..), diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 5e1eaac96fc0b68124a54f76ddb806ea3bba050a..039e8f15ba01e8b634d4d418157efafa2de66e37 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -6,6 +6,13 @@ -- -- ----------------------------------------------------------------------------- +{-# 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 GHC ( -- * Initialisation defaultErrorHandler, diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index d27e5246a9ba7abe1d27bc83cba8b14fca0aba0a..abbaa1fb75db6e02ba3bdce164be9f18731d134f 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -9,6 +9,13 @@ -- -- ----------------------------------------------------------------------------- +{-# 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 GhcMake( depanal, load, LoadHowMuch(..), diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs index a3f7e79dde2e18927aecae6aa50ca76117fc5950..2b6a14bb27eab4771cac3fc75a95268feb3db7e9 100644 --- a/compiler/main/HeaderInfo.hs +++ b/compiler/main/HeaderInfo.hs @@ -8,6 +8,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 HeaderInfo ( getImports , mkPrelImports -- used by the renamer too , getOptionsFromFile, getOptions diff --git a/compiler/main/HscStats.lhs b/compiler/main/HscStats.lhs index 34310e038c6aade8bcb2bdb0f739cb84dda6d786..f89903f75c7782b54191b0a80ecd6c113c1655b1 100644 --- a/compiler/main/HscStats.lhs +++ b/compiler/main/HscStats.lhs @@ -4,6 +4,13 @@ \section[GHC_Stats]{Statistics for per-module compilations} \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 HscStats ( ppSourceStats ) where #include "HsVersions.h" diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs index 0fd710a7eb36e9386bdf96339b3a2c68c25cbbee..b4cf6b8197fa5b7e436aac8d511582373a65298d 100644 --- a/compiler/main/InteractiveEval.hs +++ b/compiler/main/InteractiveEval.hs @@ -6,6 +6,13 @@ -- -- ----------------------------------------------------------------------------- +{-# 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 InteractiveEval ( #ifdef GHCI RunResult(..), Status(..), Resume(..), History(..), diff --git a/compiler/main/PackageConfig.hs b/compiler/main/PackageConfig.hs index 50c1e7105aeea53f25f0044271e49a375fc13b57..913e58c6fbc7f6d0c2c418a591dea7b2de7c46b8 100644 --- a/compiler/main/PackageConfig.hs +++ b/compiler/main/PackageConfig.hs @@ -3,6 +3,14 @@ -- -- | Package configuration information: essentially the interface to Cabal, with some utilities + +{-# 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 PackageConfig ( -- $package_naming diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 1efb5b690309960843e1a29893cb4240fcef8334..9c291e817b1ed7e241f5bfeef09adf568b80a088 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -2,6 +2,13 @@ % (c) The University of Glasgow, 2006 % \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 + -- | Package manipulation module Packages ( module PackageConfig, diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 635bdce389eff1d3c56c7697dc589266f23a4ae7..1ee18f84e36551b07e547dfa42ac745e6b9caefd 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 PprTyThing ( PrintExplicitForalls, pprTyThing, diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs index 37b500896b86ec3bc4d5ce5fcdec1238ea8d87b1..dd00d3d6b3c404b2f6efe7a951741f0599c3b24d 100644 --- a/compiler/main/StaticFlags.hs +++ b/compiler/main/StaticFlags.hs @@ -1,3 +1,10 @@ +{-# 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 + {-# OPTIONS -fno-cse #-} -- -fno-cse is needed for GLOBAL_VAR's to behave properly diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index 85e8802f953c09088dcebfe37e95c1af363f0369..b2a6b5bb6750e45467bde7712ddc2d1f9eddb6a0 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -4,6 +4,13 @@ \section{Tidying up Core} \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 TidyPgm ( mkBootModDetailsTc, tidyProgram, globaliseAndTidyId ) where diff --git a/compiler/nativeGen/AsmCodeGen.lhs b/compiler/nativeGen/AsmCodeGen.lhs index b5144d69725912f1d978fdb433d9689189884f88..d77f5dfca34f9bacc51393c997e6b7f95023a150 100644 --- a/compiler/nativeGen/AsmCodeGen.lhs +++ b/compiler/nativeGen/AsmCodeGen.lhs @@ -7,6 +7,13 @@ -- ----------------------------------------------------------------------------- \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 AsmCodeGen ( nativeCodeGen ) where #include "HsVersions.h" diff --git a/compiler/nativeGen/NCGMonad.hs b/compiler/nativeGen/NCGMonad.hs index 57d2adf9b86677d880fe4ae17a87bd685f13a942..71250a245228606345095a06f01d2bd6eb2de422 100644 --- a/compiler/nativeGen/NCGMonad.hs +++ b/compiler/nativeGen/NCGMonad.hs @@ -6,6 +6,13 @@ -- -- ----------------------------------------------------------------------------- +{-# 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 NCGMonad ( NatM_State(..), mkNatM_State, diff --git a/compiler/nativeGen/PIC.hs b/compiler/nativeGen/PIC.hs index a8f65ba480b1e1768a529ec0ed04a74744002da5..aca320eec594ba6beb62b3d41c11351aadb86c33 100644 --- a/compiler/nativeGen/PIC.hs +++ b/compiler/nativeGen/PIC.hs @@ -38,6 +38,13 @@ and ppc-linux). -} +{-# 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 PIC ( cmmMakeDynamicReference, ReferenceKind(..), diff --git a/compiler/nativeGen/PPC/Cond.hs b/compiler/nativeGen/PPC/Cond.hs index 7345ee5f1d020dfc9126ea5c2b5dcc11eda37e2f..ec5ef621c8345b703ef3a8330c127ce8099cdd10 100644 --- a/compiler/nativeGen/PPC/Cond.hs +++ b/compiler/nativeGen/PPC/Cond.hs @@ -1,4 +1,11 @@ +{-# 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 PPC.Cond ( Cond(..), condNegate, diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs index ffe54080335a3a0ef02f9334f25b5327bd8f33bf..d6f4bafd0dd1eafc16a2fa327cfe825cb3ce86aa 100644 --- a/compiler/nativeGen/PPC/Instr.hs +++ b/compiler/nativeGen/PPC/Instr.hs @@ -9,6 +9,13 @@ #include "HsVersions.h" #include "nativeGen/NCG.h" +{-# 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 PPC.Instr ( archWordSize, RI(..), diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs index a2797a403a354634630555528ba07544fd708e38..26f06c373b2c5ed685541080b9a620c654322114 100644 --- a/compiler/nativeGen/PPC/Ppr.hs +++ b/compiler/nativeGen/PPC/Ppr.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 PPC.Ppr ( pprNatCmmDecl, pprBasicBlock, diff --git a/compiler/nativeGen/PPC/RegInfo.hs b/compiler/nativeGen/PPC/RegInfo.hs index 2a30087ab71def7ba6a2dd168c39b6de4e2ec001..019cf82f6a214bf5765e2f06fe805359b7d05f51 100644 --- a/compiler/nativeGen/PPC/RegInfo.hs +++ b/compiler/nativeGen/PPC/RegInfo.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 PPC.RegInfo ( JumpDest( DestBlockId ), getJumpDestBlockId, canShortcut, diff --git a/compiler/nativeGen/PPC/Regs.hs b/compiler/nativeGen/PPC/Regs.hs index 7a2a84b68c9020d4eed2b24f39ae886b438c7399..2f1bae39c1423fbfd513d24997bd13a5f6f9054b 100644 --- a/compiler/nativeGen/PPC/Regs.hs +++ b/compiler/nativeGen/PPC/Regs.hs @@ -4,6 +4,13 @@ -- -- ----------------------------------------------------------------------------- +{-# 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 PPC.Regs ( -- squeeze functions virtualRegSqueeze, diff --git a/compiler/nativeGen/PprBase.hs b/compiler/nativeGen/PprBase.hs index 5a50a79cae1f91d7bb50a69b18898ddf9fba86ee..b05d6be8a18455a467b974d40340f88c800ff6d4 100644 --- a/compiler/nativeGen/PprBase.hs +++ b/compiler/nativeGen/PprBase.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 PprBase ( asmSDoc, pprCLabel_asm, diff --git a/compiler/nativeGen/Reg.hs b/compiler/nativeGen/Reg.hs index 50d179c00252fc5bd17eefd2572558ceb05360c0..25d50f18f81202335028745da6da35468ebcbd25 100644 --- a/compiler/nativeGen/Reg.hs +++ b/compiler/nativeGen/Reg.hs @@ -4,6 +4,14 @@ -- by NCGMonad and the register allocators, which are shared -- by all architectures. -- + +{-# 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 Reg ( RegNo, Reg(..), diff --git a/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs b/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs index 6172cde5debf1adc09ac18451f8d3a975d074d1f..83ad5feb75e80b64bc40ae9477fc128cdf58e009 100644 --- a/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs +++ b/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Utils for calculating general worst, bound, squeese and free, functions. -- -- as per: "A Generalized Algorithm for Graph-Coloring Register Allocation" diff --git a/compiler/nativeGen/RegAlloc/Graph/ArchX86.hs b/compiler/nativeGen/RegAlloc/Graph/ArchX86.hs index e12d62deebf3199875b897489a9700cb578cf4c4..c9ee33463493d74911006bc10cb7e5ca57c944dd 100644 --- a/compiler/nativeGen/RegAlloc/Graph/ArchX86.hs +++ b/compiler/nativeGen/RegAlloc/Graph/ArchX86.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | A description of the register set of the X86. -- This isn't used directly in GHC proper. -- diff --git a/compiler/nativeGen/RegAlloc/Graph/Coalesce.hs b/compiler/nativeGen/RegAlloc/Graph/Coalesce.hs index 41901bb9dafc66ea4043eeeee9aeab995532bbf6..0680beac00679a4944ee7ef3ca193560dd96cec2 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Coalesce.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Coalesce.hs @@ -1,6 +1,13 @@ -- | Register coalescing. -- +{-# 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 RegAlloc.Graph.Coalesce ( regCoalesce, slurpJoinMovs diff --git a/compiler/nativeGen/RegAlloc/Graph/Main.hs b/compiler/nativeGen/RegAlloc/Graph/Main.hs index efc04930cdc30e6fa417550c7c0a07d249ee3797..5b6b3b28a3afb38bc1be8401773f8bd96dd5a07c 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Main.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Main.hs @@ -4,6 +4,13 @@ -- TODO: The colors in graphviz graphs for x86_64 and ppc could be nicer. -- +{-# 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 RegAlloc.Graph.Main ( regAlloc ) diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs b/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs index 94c274dfaf33055027477984a6b20ff9a2ebd4ec..ec583782558cdb2d6bd36f95fc102d08e9208aa1 100644 --- a/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs +++ b/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs @@ -23,6 +23,13 @@ -- This also works if the reloads in B1\/B2 were spills instead, because -- spilling %r1 to a slot makes that slot have the same value as %r1. -- +{-# 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 RegAlloc.Graph.SpillClean ( cleanSpills ) diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs index e11532e15f2e46e17475db0b1641684ddd7c64f3..222e222c75d5adb127ddbfe7fd646c1cbe6b5fcd 100644 --- a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs +++ b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs @@ -1,4 +1,11 @@ +{-# 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 RegAlloc.Graph.SpillCost ( SpillCostRecord, plusSpillCostRecord, diff --git a/compiler/nativeGen/RegAlloc/Graph/Stats.hs b/compiler/nativeGen/RegAlloc/Graph/Stats.hs index 626262c658ff490b313877aaed80ba8f59f1d04a..69be2f0ed6701a10f4347312fc3f0b82307cb1e8 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Stats.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Stats.hs @@ -1,6 +1,13 @@ {-# OPTIONS -fno-warn-missing-signatures #-} -- | Carries interesting info for debugging / profiling of the -- graph coloring register allocator. +{-# 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 RegAlloc.Graph.Stats ( RegAllocStats (..), diff --git a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs index 6d17a4f077d5907e30f3fc03676f1397bf63d269..1b0893e45d3435f965348587ce4658cdb78f88a7 100644 --- a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs +++ b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs @@ -1,4 +1,11 @@ +{-# 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 RegAlloc.Linear.FreeRegs ( FR(..), maxSpillSlots diff --git a/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs b/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs index ba07e618716c0931ce8dc0b0586391ac425ad1dd..3bf49a31f2fee1d5ecc289d18d906fea4b5f174c 100644 --- a/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs +++ b/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Handles joining of a jump instruction to its targets. -- The first time we encounter a jump to a particular basic block, we diff --git a/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs index 3db5555bffa049e9868a56f3778099adad77b70f..10726cd4b4069d03bb0896213159d052d6a40802 100644 --- a/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs +++ b/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Free regs map for PowerPC module RegAlloc.Linear.PPC.FreeRegs where diff --git a/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs index f48a893c09db9c0f07e9a404a17b60ae8f232eea..d3bc88c09fa301637989ee49e23448c0d809dd12 100644 --- a/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs +++ b/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Free regs map for SPARC module RegAlloc.Linear.SPARC.FreeRegs where diff --git a/compiler/nativeGen/RegAlloc/Linear/StackMap.hs b/compiler/nativeGen/RegAlloc/Linear/StackMap.hs index 1dd410aa46a86e63c7bd4ce2ae012d47e1228b18..ea05cf0d0f43a85dbecf5f48e9104c32b38796ff 100644 --- a/compiler/nativeGen/RegAlloc/Linear/StackMap.hs +++ b/compiler/nativeGen/RegAlloc/Linear/StackMap.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | The assignment of virtual registers to stack slots -- We have lots of stack slots. Memory-to-memory moves are a pain on most diff --git a/compiler/nativeGen/RegAlloc/Linear/State.hs b/compiler/nativeGen/RegAlloc/Linear/State.hs index 9999a1e2e439e2a359cb653359b5488cbf91e663..3de277b2744944d3546ed91c0ee51070c7ce50bd 100644 --- a/compiler/nativeGen/RegAlloc/Linear/State.hs +++ b/compiler/nativeGen/RegAlloc/Linear/State.hs @@ -3,6 +3,13 @@ -- Here we keep all the state that the register allocator keeps track -- of as it walks the instructions in a basic block. +{-# 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 RegAlloc.Linear.State ( RA_State(..), RegM, diff --git a/compiler/nativeGen/RegAlloc/Linear/Stats.hs b/compiler/nativeGen/RegAlloc/Linear/Stats.hs index 21664b12bad26d16d107f51c166b445c02c109bf..bfd196ac05e4192d89528ec4167bee7703d16f6f 100644 --- a/compiler/nativeGen/RegAlloc/Linear/Stats.hs +++ b/compiler/nativeGen/RegAlloc/Linear/Stats.hs @@ -1,3 +1,10 @@ +{-# 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 RegAlloc.Linear.Stats ( binSpillReasons, countRegRegMovesNat, diff --git a/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs index 27810ff8c609f3049f7ce3ef0a3e0a5fdc13dfaa..7e7d99b008b714cd739c18f727ab63870bf2dfde 100644 --- a/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs +++ b/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Free regs map for i386 and x86_64 module RegAlloc.Linear.X86.FreeRegs where diff --git a/compiler/nativeGen/RegClass.hs b/compiler/nativeGen/RegClass.hs index 2a4ac333e9d18335774bc13e27b9def8f7effba3..3bc2f75e5310f4ec60d9752b95def55bfdb3d604 100644 --- a/compiler/nativeGen/RegClass.hs +++ b/compiler/nativeGen/RegClass.hs @@ -1,3 +1,10 @@ +{-# 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 + -- | An architecture independent description of a register's class. module RegClass diff --git a/compiler/nativeGen/SPARC/AddrMode.hs b/compiler/nativeGen/SPARC/AddrMode.hs index 58487941e30107d0a1653a46d8c48d4d66c17fb4..f00458af81a6b8f0af5510f94844b9b228fbff11 100644 --- a/compiler/nativeGen/SPARC/AddrMode.hs +++ b/compiler/nativeGen/SPARC/AddrMode.hs @@ -1,4 +1,11 @@ +{-# 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.AddrMode ( AddrMode(..), addrOffset diff --git a/compiler/nativeGen/SPARC/Base.hs b/compiler/nativeGen/SPARC/Base.hs index a77bc2dd0b25a309315028334bb0c1f94efef4bc..de11b9f77ccdfa1da45db8ebc701947e0d76bd57 100644 --- a/compiler/nativeGen/SPARC/Base.hs +++ b/compiler/nativeGen/SPARC/Base.hs @@ -5,6 +5,13 @@ -- In the interests of cross-compilation, we want to free ourselves -- from the autoconf generated modules like main/Constants -- +{-# 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.Base ( wordLength, wordLengthInBits, diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index acdf41c2bd474cc8045ddf45182fe144b982367a..91a850d5fc03791c8d2bb87e230934a25ee837fe 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 ( cmmTopCodeGen, generateJumpTableForInstr, diff --git a/compiler/nativeGen/SPARC/CodeGen/Amode.hs b/compiler/nativeGen/SPARC/CodeGen/Amode.hs index 8f1fad8dd3229eb60ca0b8d01d3efb0fc3a0db21..92e70eb4dcdcaec9cb7031010074fad7176166fd 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Amode.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Amode.hs @@ -1,4 +1,11 @@ +{-# 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.Amode ( getAmode ) diff --git a/compiler/nativeGen/SPARC/CodeGen/Base.hs b/compiler/nativeGen/SPARC/CodeGen/Base.hs index 57fb7c9e90e7b4ce7b8c16710f740675a8873f49..8990072c3f6da7443d758f40d9a69c61370ced4d 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Base.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Base.hs @@ -1,4 +1,11 @@ +{-# 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.Base ( InstrBlock, CondCode(..), diff --git a/compiler/nativeGen/SPARC/CodeGen/CCall.hs b/compiler/nativeGen/SPARC/CodeGen/CCall.hs index 99ef441eabb8eeeff0642862beee7fd772347907..5b2666764267eb92e15887f60a9afb2e73c3e745 100644 --- a/compiler/nativeGen/SPARC/CodeGen/CCall.hs +++ b/compiler/nativeGen/SPARC/CodeGen/CCall.hs @@ -1,4 +1,11 @@ -- | Generating C calls +{-# 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.CCall ( genCCall ) diff --git a/compiler/nativeGen/SPARC/CodeGen/CondCode.hs b/compiler/nativeGen/SPARC/CodeGen/CondCode.hs index 25422659a66e24bf4670ee89e078dc080572e347..215a565ba6a894082b3b516713c4618edf72d267 100644 --- a/compiler/nativeGen/SPARC/CodeGen/CondCode.hs +++ b/compiler/nativeGen/SPARC/CodeGen/CondCode.hs @@ -1,4 +1,11 @@ +{-# 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.CondCode ( getCondCode, condIntCode, diff --git a/compiler/nativeGen/SPARC/CodeGen/Expand.hs b/compiler/nativeGen/SPARC/CodeGen/Expand.hs index f65cbaa01a78b5806f355f98b6c3a810d9fff6de..c468fcc25548dfcc822e84b0fbf60833450b530f 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Expand.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Expand.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Expand out synthetic instructions into single machine instrs. module SPARC.CodeGen.Expand ( expandTop diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs index ddeed0508b87596cfd6c13cd6fe19171dccef4ee..454e786f1a00f0f83d0730550d0d7c90ee2e15ee 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Evaluation of 32 bit values. module SPARC.CodeGen.Gen32 ( getSomeReg, diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot index 4816a1d9a7e39b618dfb50123cea4a7c64a9485d..0e639a3cafe1585a765d65b9cfdb6d053a40dc11 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot +++ b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot @@ -1,4 +1,11 @@ +{-# 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 diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen64.hs b/compiler/nativeGen/SPARC/CodeGen/Gen64.hs index 92302e94afef53aa4e88a9dba1e1a333ebc69a4a..5bcab2cb10f2d5e62a64fdb980a41fe9682f166c 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Gen64.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Gen64.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Evaluation of 64 bit values on 32 bit platforms. module SPARC.CodeGen.Gen64 ( assignMem_I64Code, diff --git a/compiler/nativeGen/SPARC/CodeGen/Sanity.hs b/compiler/nativeGen/SPARC/CodeGen/Sanity.hs index a3053cbae8d954bc20e6c6d972bfca40e5fdcec0..78dbb1b493df70b19c3adcabce599f2f27919a5b 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Sanity.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Sanity.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | One ounce of sanity checking is worth 10000000000000000 ounces -- of staring blindly at assembly code trying to find the problem.. -- diff --git a/compiler/nativeGen/SPARC/Cond.hs b/compiler/nativeGen/SPARC/Cond.hs index d0f12efcf5943a862342562536c75c909e45a069..404f1e5acf57466bff7221bb4b124f267882ce26 100644 --- a/compiler/nativeGen/SPARC/Cond.hs +++ b/compiler/nativeGen/SPARC/Cond.hs @@ -1,4 +1,11 @@ +{-# 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.Cond ( Cond(..), condUnsigned, diff --git a/compiler/nativeGen/SPARC/Imm.hs b/compiler/nativeGen/SPARC/Imm.hs index bcb35b2ab5e53ed88264ad8f6648d30e0b078806..74dc8e0041a30cbfcbb4e1764041642744121206 100644 --- a/compiler/nativeGen/SPARC/Imm.hs +++ b/compiler/nativeGen/SPARC/Imm.hs @@ -1,4 +1,11 @@ +{-# 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.Imm ( -- immediate values Imm(..), diff --git a/compiler/nativeGen/SPARC/Instr.hs b/compiler/nativeGen/SPARC/Instr.hs index 61090e05c84e6cfe95ab739ac4f3b91091db0dcd..742a4e7d33f237f90478d28db91e1a62ef8c609b 100644 --- a/compiler/nativeGen/SPARC/Instr.hs +++ b/compiler/nativeGen/SPARC/Instr.hs @@ -9,6 +9,13 @@ #include "HsVersions.h" #include "nativeGen/NCG.h" +{-# 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.Instr ( RI(..), riZero, diff --git a/compiler/nativeGen/SPARC/Ppr.hs b/compiler/nativeGen/SPARC/Ppr.hs index 9d0ed2a9164040350b08fe699615b04a6b877132..5c811c5e3a774c6a8b33d11e0e8fd6a30b177c9a 100644 --- a/compiler/nativeGen/SPARC/Ppr.hs +++ b/compiler/nativeGen/SPARC/Ppr.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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.Ppr ( pprNatCmmDecl, pprBasicBlock, diff --git a/compiler/nativeGen/SPARC/RegPlate.hs b/compiler/nativeGen/SPARC/RegPlate.hs index a0d0e4c88d23b04f137dbc847db8f37fe9f96974..7a7d447757a3cf7f70bf9612d075270e28edaddb 100644 --- a/compiler/nativeGen/SPARC/RegPlate.hs +++ b/compiler/nativeGen/SPARC/RegPlate.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Nasty #ifdefery that generates the definitions for -- freeReg and globalRegMaybe from the information in includes/MachRegs.h. -- diff --git a/compiler/nativeGen/SPARC/Regs.hs b/compiler/nativeGen/SPARC/Regs.hs index 1fea9d61790e2cb3058bd9290e210149eff4e144..ff899c24b15980eb80b1173e227427f5459da5ff 100644 --- a/compiler/nativeGen/SPARC/Regs.hs +++ b/compiler/nativeGen/SPARC/Regs.hs @@ -4,6 +4,13 @@ -- -- ----------------------------------------------------------------------------- +{-# 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.Regs ( -- registers showReg, diff --git a/compiler/nativeGen/SPARC/ShortcutJump.hs b/compiler/nativeGen/SPARC/ShortcutJump.hs index 10e2e9fbaaa9c52f5c72619b6d02ba039032a00c..5d63fd73a14b799a8b1d19fddcb0cbe25ed7d3e7 100644 --- a/compiler/nativeGen/SPARC/ShortcutJump.hs +++ b/compiler/nativeGen/SPARC/ShortcutJump.hs @@ -1,4 +1,11 @@ +{-# 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.ShortcutJump ( JumpDest(..), getJumpDestBlockId, canShortcut, diff --git a/compiler/nativeGen/SPARC/Stack.hs b/compiler/nativeGen/SPARC/Stack.hs index 0c19181f194ba9b2813b4e40eacbb04f67e2aa70..7f756938891d144139e2dab347d58d1d3b44a149 100644 --- a/compiler/nativeGen/SPARC/Stack.hs +++ b/compiler/nativeGen/SPARC/Stack.hs @@ -1,4 +1,11 @@ +{-# 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.Stack ( spRel, fpRel, diff --git a/compiler/nativeGen/Size.hs b/compiler/nativeGen/Size.hs index 5d939d7d98a7f8e71c200549c8cdc7f2a8d89b61..99e5de679b1141d7b07441fe56853d23666c7a6e 100644 --- a/compiler/nativeGen/Size.hs +++ b/compiler/nativeGen/Size.hs @@ -1,3 +1,10 @@ +{-# 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 + -- | Sizes on this architecture -- A Size is a combination of width and class -- diff --git a/compiler/nativeGen/TargetReg.hs b/compiler/nativeGen/TargetReg.hs index a9d20212f0a091a83d1431d01f218beb30685fd5..c8f8ea6bf1181b76aede7bb99d85cfa437c0a651 100644 --- a/compiler/nativeGen/TargetReg.hs +++ b/compiler/nativeGen/TargetReg.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Hard wired things related to registers. -- This is module is preventing the native code generator being able to -- emit code for non-host architectures. diff --git a/compiler/nativeGen/X86/Cond.hs b/compiler/nativeGen/X86/Cond.hs index 4907059ae786ad98d101e4168d7148c4cf0d017c..ce97095222728ff9af2eda9e6bdfff0c612960b6 100644 --- a/compiler/nativeGen/X86/Cond.hs +++ b/compiler/nativeGen/X86/Cond.hs @@ -1,4 +1,11 @@ +{-# 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 X86.Cond ( Cond(..), condUnsigned, diff --git a/compiler/nativeGen/X86/RegInfo.hs b/compiler/nativeGen/X86/RegInfo.hs index 7f094f80e46dbf9ea104c9196874d58f2b373c60..3b4e63a9d818a50a9311579c63883fa132d07162 100644 --- a/compiler/nativeGen/X86/RegInfo.hs +++ b/compiler/nativeGen/X86/RegInfo.hs @@ -1,4 +1,11 @@ +{-# 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 X86.RegInfo ( mkVirtualReg, regDotColor diff --git a/compiler/parser/Ctype.lhs b/compiler/parser/Ctype.lhs index 2b76465080c6c73b8c0152835d0d6b735c17c827..5b8c9b9af15bfdf304f430d605e226f46b735453 100644 --- a/compiler/parser/Ctype.lhs +++ b/compiler/parser/Ctype.lhs @@ -1,6 +1,13 @@ Character classification \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 Ctype ( is_ident -- Char# -> Bool , is_symbol -- Char# -> Bool diff --git a/compiler/parser/LexCore.hs b/compiler/parser/LexCore.hs index 68b341916395ff7e2f657545baecab0d2c5424ea..b3d8d63fbd4beb370a4e713f8681199a6e8beefa 100644 --- a/compiler/parser/LexCore.hs +++ b/compiler/parser/LexCore.hs @@ -1,4 +1,11 @@ +{-# 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 LexCore where import ParserCoreUtils diff --git a/compiler/prelude/PrelInfo.lhs b/compiler/prelude/PrelInfo.lhs index 98531e28afad6060e7c678ecd9cde08c257f7e30..bb3e54ada26a15999a3e33e1dfaecc080d240763 100644 --- a/compiler/prelude/PrelInfo.lhs +++ b/compiler/prelude/PrelInfo.lhs @@ -4,6 +4,13 @@ \section[PrelInfo]{The @PrelInfo@ interface to the compiler's prelude knowledge} \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 PrelInfo ( wiredInIds, ghcPrimIds, primOpRules, builtinRules, diff --git a/compiler/prelude/TysPrim.lhs b/compiler/prelude/TysPrim.lhs index 81094acaa10a0b10c679410f09ff6aa414fb19b0..0c2de06924e80cc20ef135f215766a86a0b3c882 100644 --- a/compiler/prelude/TysPrim.lhs +++ b/compiler/prelude/TysPrim.lhs @@ -6,6 +6,13 @@ \section[TysPrim]{Wired-in knowledge about primitive types} \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 + -- | This module defines TyCons that can't be expressed in Haskell. -- They are all, therefore, wired-in TyCons. C.f module TysWiredIn module TysPrim( diff --git a/compiler/prelude/TysWiredIn.lhs b/compiler/prelude/TysWiredIn.lhs index a2daf1535cc3b1ccd8da04eedba1a2648d966c7f..54acefc087d1c1bb320e4ff4b57f9ae27889df28 100644 --- a/compiler/prelude/TysWiredIn.lhs +++ b/compiler/prelude/TysWiredIn.lhs @@ -4,6 +4,13 @@ \section[TysWiredIn]{Wired-in knowledge about {\em non-primitive} types} \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 + -- | This module is about types that can be defined in Haskell, but which -- must be wired into the compiler nonetheless. C.f module TysPrim module TysWiredIn ( diff --git a/compiler/profiling/CostCentre.lhs b/compiler/profiling/CostCentre.lhs index 8c2d938b8e4db2cf418bee0eb5528c4ff482048b..9545b2eb893c1e152330725b8db9befc8efc0663 100644 --- a/compiler/profiling/CostCentre.lhs +++ b/compiler/profiling/CostCentre.lhs @@ -1,4 +1,11 @@ \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 + {-# LANGUAGE BangPatterns, DeriveDataTypeable #-} module CostCentre ( diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index 72d58eab20385b2b13afb2b15362d455223222f5..faecd40b537eadcdc2046bb5fefd966acdc9b565 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -9,6 +9,13 @@ type-synonym declarations; those cannot be done at this stage because they may be affected by renaming (which isn't fully worked out yet). \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 RnBinds ( -- Renaming top-level bindings rnTopBindsLHS, rnTopBindsRHS, rnValBindsRHS, diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs index 261d65ac78055835d71f94899093619039fb5ead..c6ab6bb592e1ade439dcb181284169abb10882f6 100644 --- a/compiler/rename/RnEnv.lhs +++ b/compiler/rename/RnEnv.lhs @@ -4,6 +4,13 @@ \section[RnEnv]{Environment manipulation for the renamer monad} \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 RnEnv ( newTopSrcBinder, lookupLocatedTopBndrRn, lookupTopBndrRn, diff --git a/compiler/rename/RnExpr.lhs b/compiler/rename/RnExpr.lhs index d6bc2b1c5554ce1211fc32b71accdbaef9b60184..f57998ef4407eb4e4b2eb533bfebfbc7658eef50 100644 --- a/compiler/rename/RnExpr.lhs +++ b/compiler/rename/RnExpr.lhs @@ -10,6 +10,13 @@ general, all of these functions return a renamed thing, and a set of free variables. \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 ( rnLExpr, rnExpr, rnStmts ) where diff --git a/compiler/rename/RnExpr.lhs-boot b/compiler/rename/RnExpr.lhs-boot index 8870017a3a9b5c5f7413f5c59c522547320d2530..2d59537b95ebca0890ad39f254efc4f1efaab038 100644 --- a/compiler/rename/RnExpr.lhs-boot +++ b/compiler/rename/RnExpr.lhs-boot @@ -1,4 +1,11 @@ \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 ) diff --git a/compiler/rename/RnHsSyn.lhs b/compiler/rename/RnHsSyn.lhs index 79aaf6aa7a6fe125fb1737daa3f3aaa4e1b5ab15..7b0591dd19b5c68a119672ec695b8ef99fe424ed 100644 --- a/compiler/rename/RnHsSyn.lhs +++ b/compiler/rename/RnHsSyn.lhs @@ -4,6 +4,13 @@ \section[RnHsSyn]{Specialisations of the @HsSyn@ syntax for the renamer} \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 RnHsSyn( -- Names charTyCon_name, listTyCon_name, parrTyCon_name, tupleTyCon_name, diff --git a/compiler/rename/RnNames.lhs b/compiler/rename/RnNames.lhs index eeaae149a348ae87b880a77e1f70b238dedde6a4..02ed64f5cbd0d1233b1c24efc7dd5b2ba6d62f47 100644 --- a/compiler/rename/RnNames.lhs +++ b/compiler/rename/RnNames.lhs @@ -4,6 +4,13 @@ \section[RnNames]{Extracting imported and top-level names in scope} \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 RnNames ( rnImports, getLocalNonValBinders, rnExports, extendGlobalRdrEnvRn, diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index b24815a79a5b914120fc122be0da1e8efdcd8341..5c28f73a56f2123a024215888666f469117b552d 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -10,6 +10,13 @@ general, all of these functions return a renamed thing, and a set of free variables. \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 + {-# LANGUAGE ScopedTypeVariables #-} module RnPat (-- main entry points rnPat, rnPats, rnBindPat, diff --git a/compiler/rename/RnSource.lhs b/compiler/rename/RnSource.lhs index 1c7f79e3e31ef85539922dd45ec2e321b6ab0e3d..8b34fb4e5b6702ab776b03d0545e8b8616f2c8e8 100644 --- a/compiler/rename/RnSource.lhs +++ b/compiler/rename/RnSource.lhs @@ -4,6 +4,13 @@ \section[RnSource]{Main pass of renamer} \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 RnSource ( rnSrcDecls, addTcgDUs, rnTyClDecls, findSplice ) where diff --git a/compiler/rename/RnTypes.lhs b/compiler/rename/RnTypes.lhs index 647beda9fcc4680ba2923e61f110ad4c717d2445..3607170e7009d258c4c5be06f16354d31d02bb95 100644 --- a/compiler/rename/RnTypes.lhs +++ b/compiler/rename/RnTypes.lhs @@ -4,6 +4,13 @@ \section[RnSource]{Main pass of renamer} \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 RnTypes ( -- Type related stuff rnHsType, rnLHsType, rnLHsTypes, rnContext, diff --git a/compiler/simplCore/CSE.lhs b/compiler/simplCore/CSE.lhs index 4dc8f875e8bdf84e79c39d04a1e4236280deeff3..4a92f818d41b363074fb750bd54d5aa06b61a2ab 100644 --- a/compiler/simplCore/CSE.lhs +++ b/compiler/simplCore/CSE.lhs @@ -4,6 +4,13 @@ \section{Common subexpression} \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 CSE ( cseProgram ) where diff --git a/compiler/simplCore/CoreMonad.lhs b/compiler/simplCore/CoreMonad.lhs index 6ad402c789012edc11e7a97fb5b25b0ef0ee893f..950c6a9a75fa3d50be082d9da501aa8433209e2d 100644 --- a/compiler/simplCore/CoreMonad.lhs +++ b/compiler/simplCore/CoreMonad.lhs @@ -4,6 +4,13 @@ \section[CoreMonad]{The core pipeline monad} \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 + {-# LANGUAGE UndecidableInstances #-} module CoreMonad ( diff --git a/compiler/simplCore/FloatIn.lhs b/compiler/simplCore/FloatIn.lhs index ea915ed68aa21e5ab9da88cbed27052d6838c4c7..6745fda8cb30b9b48084e5d9cc0ac988f7544edc 100644 --- a/compiler/simplCore/FloatIn.lhs +++ b/compiler/simplCore/FloatIn.lhs @@ -12,6 +12,13 @@ case, so that we don't allocate things, save them on the stack, and then discover that they aren't needed in the chosen branch. \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 FloatIn ( floatInwards ) where #include "HsVersions.h" diff --git a/compiler/simplCore/FloatOut.lhs b/compiler/simplCore/FloatOut.lhs index 3a51c4f6591a4a340147d5fd5b6f8497e96dfd2c..1b2555d01854cf4f7de33b81b5cb64b3376b31af 100644 --- a/compiler/simplCore/FloatOut.lhs +++ b/compiler/simplCore/FloatOut.lhs @@ -6,6 +6,13 @@ ``Long-distance'' floating of bindings towards the top level. \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 FloatOut ( floatOutwards ) where import CoreSyn diff --git a/compiler/simplCore/LiberateCase.lhs b/compiler/simplCore/LiberateCase.lhs index 5388b4210c186be538014efc4f39b92776fcd55b..35bfb5fcc12920f38a7150290d75b73ae8b5873f 100644 --- a/compiler/simplCore/LiberateCase.lhs +++ b/compiler/simplCore/LiberateCase.lhs @@ -4,6 +4,13 @@ \section[LiberateCase]{Unroll recursion to allow evals to be lifted from a loop} \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 LiberateCase ( liberateCase ) where #include "HsVersions.h" diff --git a/compiler/simplCore/OccurAnal.lhs b/compiler/simplCore/OccurAnal.lhs index df6c76be3360e4aa1a09046b24493f6e5f8c4e3c..65a6927be703a9fdac53873876f49d6f0cc58e64 100644 --- a/compiler/simplCore/OccurAnal.lhs +++ b/compiler/simplCore/OccurAnal.lhs @@ -12,6 +12,13 @@ The occurrence analyser re-typechecks a core expression, returning a new core expression with (hopefully) improved usage information. \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 + {-# LANGUAGE BangPatterns #-} module OccurAnal ( occurAnalysePgm, occurAnalyseExpr diff --git a/compiler/simplCore/SAT.lhs b/compiler/simplCore/SAT.lhs index b11411ce1b67141fdf97bfec00f0ae9af27bcfce..a17e40d59c0777e3dd23572d875e87cef30cc684 100644 --- a/compiler/simplCore/SAT.lhs +++ b/compiler/simplCore/SAT.lhs @@ -49,6 +49,13 @@ essential to make this work well! \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 SAT ( doStaticArgs ) where diff --git a/compiler/simplCore/SetLevels.lhs b/compiler/simplCore/SetLevels.lhs index 76a44f41280fe6c7f4a0fb868bd6b905a0bb5614..9af757c1afc85fa08de29698e76c27d275feb289 100644 --- a/compiler/simplCore/SetLevels.lhs +++ b/compiler/simplCore/SetLevels.lhs @@ -42,6 +42,13 @@ the scrutinee of the case, and we can inline it. \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 SetLevels ( setLevels, diff --git a/compiler/simplCore/SimplCore.lhs b/compiler/simplCore/SimplCore.lhs index 9c0cc822ccadd738caf24fe83579234b368146fc..12d180642e3fe948d0b399c213bbbceacd042b6c 100644 --- a/compiler/simplCore/SimplCore.lhs +++ b/compiler/simplCore/SimplCore.lhs @@ -4,6 +4,13 @@ \section[SimplCore]{Driver for simplifying @Core@ programs} \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 SimplCore ( core2core, simplifyExpr ) where #include "HsVersions.h" diff --git a/compiler/simplCore/SimplEnv.lhs b/compiler/simplCore/SimplEnv.lhs index 298cc6359777c64a5f8b4dade920305d35c0331f..022b3540610d108f0c4dd9f25eae4a6c11c2900d 100644 --- a/compiler/simplCore/SimplEnv.lhs +++ b/compiler/simplCore/SimplEnv.lhs @@ -4,6 +4,13 @@ o% (c) The AQUA Project, Glasgow University, 1993-1998 \section[SimplMonad]{The simplifier Monad} \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 SimplEnv ( InId, InBind, InExpr, InAlt, InArg, InType, InBndr, InVar, OutId, OutTyVar, OutBind, OutExpr, OutAlt, OutArg, OutType, OutBndr, OutVar, diff --git a/compiler/simplCore/SimplMonad.lhs b/compiler/simplCore/SimplMonad.lhs index a664377e015857662d4d2bb01017c49965bab7ba..647da72d167573982c64ad583925193e434655ce 100644 --- a/compiler/simplCore/SimplMonad.lhs +++ b/compiler/simplCore/SimplMonad.lhs @@ -4,6 +4,13 @@ \section[SimplMonad]{The simplifier Monad} \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 SimplMonad ( -- The monad SimplM, diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index 553e64ec65c07d1962a9e7ee68e910a46d942d3a..7c887cb2e3f93d2d4fec92f293716ca85c00dabc 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -4,6 +4,13 @@ \section[SimplUtils]{The simplifier utilities} \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 SimplUtils ( -- Rebuilding mkLam, mkCase, prepareAlts, tryEtaExpand, diff --git a/compiler/simplCore/Simplify.lhs b/compiler/simplCore/Simplify.lhs index 853815c2ce223da2879f1027f41ee4ba1424d57a..f72be2cbb4716fb13cdcc1e4c214d59437d49a59 100644 --- a/compiler/simplCore/Simplify.lhs +++ b/compiler/simplCore/Simplify.lhs @@ -4,6 +4,13 @@ \section[Simplify]{The main module of the simplifier} \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 Simplify ( simplTopBinds, simplExpr ) where #include "HsVersions.h" diff --git a/compiler/simplStg/SRT.lhs b/compiler/simplStg/SRT.lhs index c9eabfd1a188bff5937b01bdf4694b74c5ba5b7f..b6947dca4c3fd008c63b418f24ebc30fccb17b1e 100644 --- a/compiler/simplStg/SRT.lhs +++ b/compiler/simplStg/SRT.lhs @@ -7,6 +7,13 @@ each let-binding. At the same time, we figure out which top-level bindings have no CAF references, and record the fact in their IdInfo. \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 + {-# 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 diff --git a/compiler/simplStg/SimplStg.lhs b/compiler/simplStg/SimplStg.lhs index c1faf8047b86fed9e39020fd175a27c7204663c2..8ade2d5f100f8f9181f64d3ce9cc4862b281db83 100644 --- a/compiler/simplStg/SimplStg.lhs +++ b/compiler/simplStg/SimplStg.lhs @@ -4,6 +4,13 @@ \section[SimplStg]{Driver for simplifying @STG@ programs} \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 SimplStg ( stg2stg ) where #include "HsVersions.h" diff --git a/compiler/simplStg/StgStats.lhs b/compiler/simplStg/StgStats.lhs index aca29740ac1c4b06afd5001b9cc7f0673711d64d..d389431f18e339a84592a66bf3e01a42997c6170 100644 --- a/compiler/simplStg/StgStats.lhs +++ b/compiler/simplStg/StgStats.lhs @@ -21,6 +21,13 @@ The program gather statistics about \end{enumerate} \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 + {-# 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 diff --git a/compiler/specialise/Rules.lhs b/compiler/specialise/Rules.lhs index ef29eb58eb4621a4a2e0fe9d93bb843427de9f56..8e55be48fd8ea4e55f95ab181481ae19b44e4c14 100644 --- a/compiler/specialise/Rules.lhs +++ b/compiler/specialise/Rules.lhs @@ -4,6 +4,13 @@ \section[CoreRules]{Transformation rules} \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 + -- | Functions for collecting together and applying rewrite rules to a module. -- The 'CoreRule' datatype itself is declared elsewhere. module Rules ( diff --git a/compiler/specialise/SpecConstr.lhs b/compiler/specialise/SpecConstr.lhs index 0959425e8fd0f689dc9d3acce6e70c0a79f982cc..2ddc42479e6055f14cdf113d432bac139badf101 100644 --- a/compiler/specialise/SpecConstr.lhs +++ b/compiler/specialise/SpecConstr.lhs @@ -9,6 +9,13 @@ ToDo [Nov 2010] \section[SpecConstr]{Specialise over constructors} \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 + -- 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 diff --git a/compiler/specialise/Specialise.lhs b/compiler/specialise/Specialise.lhs index 24f9d080db9a95642ac862f54f5a997302d320ad..77ab8db886138e7a8f3187cbee25d85f6777b7ae 100644 --- a/compiler/specialise/Specialise.lhs +++ b/compiler/specialise/Specialise.lhs @@ -4,6 +4,13 @@ \section[Specialise]{Stamping out overloading, and (optionally) polymorphism} \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 Specialise ( specProgram ) where #include "HsVersions.h" diff --git a/compiler/stgSyn/CoreToStg.lhs b/compiler/stgSyn/CoreToStg.lhs index 3194974c8f3980c8ba66b01d037a6a1be53ad9ac..98e5303b02562213be340b14c9ae877c3d220644 100644 --- a/compiler/stgSyn/CoreToStg.lhs +++ b/compiler/stgSyn/CoreToStg.lhs @@ -7,6 +7,13 @@ And, as we have the info in hand, we may convert some lets to let-no-escapes. \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 CoreToStg ( coreToStg, coreExprToStg ) where #include "HsVersions.h" diff --git a/compiler/stgSyn/StgLint.lhs b/compiler/stgSyn/StgLint.lhs index 98b2de14449fc8694b3d12e3c6622978802eb71a..d54294f4f395f2bb0647607fbb5b168ac282abfb 100644 --- a/compiler/stgSyn/StgLint.lhs +++ b/compiler/stgSyn/StgLint.lhs @@ -4,6 +4,13 @@ \section[StgLint]{A ``lint'' pass to check for Stg correctness} \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 StgLint ( lintStgBindings ) where import StgSyn diff --git a/compiler/stgSyn/StgSyn.lhs b/compiler/stgSyn/StgSyn.lhs index c6a6762a15bf5da16019c0352ef1aa7479063e0a..e2fb0c85408aa09ec379c1988bca4ad29151c95c 100644 --- a/compiler/stgSyn/StgSyn.lhs +++ b/compiler/stgSyn/StgSyn.lhs @@ -9,6 +9,13 @@ form of @CoreSyntax@, the style being one that happens to be ideally suited to spineless tagless code generation. \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 StgSyn ( GenStgArg(..), GenStgLiveVars, diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index f52ab78180c7d602e49ce04e907a4d80e9aa8f1a..614798873eba8fd5930679c93ef2cc53ed0304fd 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -7,6 +7,13 @@ ----------------- \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 DmdAnal ( dmdAnalPgm, dmdAnalTopRhs, both {- needed by WwLib -} ) where diff --git a/compiler/stranal/WorkWrap.lhs b/compiler/stranal/WorkWrap.lhs index c947388d183d389b17368a4675c7d702f93a0d6f..230c42808c5be933ed37916bb1bdec6e6085030b 100644 --- a/compiler/stranal/WorkWrap.lhs +++ b/compiler/stranal/WorkWrap.lhs @@ -4,6 +4,13 @@ \section[WorkWrap]{Worker/wrapper-generating back-end of strictness analyser} \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 WorkWrap ( wwTopBinds, mkWrapper ) where import CoreSyn diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index b18ded311804edf6c38426c96cd1ac6156cd6c5f..4b18b8ba7dcb089467ab153295b422f532234c1f 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -4,6 +4,13 @@ \section[WwLib]{A library for the ``worker\/wrapper'' back-end to the strictness analyser} \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 WwLib ( mkWwBodies, mkWWstr, mkWorkerArgs ) where #include "HsVersions.h" diff --git a/compiler/typecheck/FamInst.lhs b/compiler/typecheck/FamInst.lhs index 39f5cdad376f79f5b21d10e0887e3fc7810f475b..97ba4e8ab7a6315877b5d6c16aac6fd1bbc6165d 100644 --- a/compiler/typecheck/FamInst.lhs +++ b/compiler/typecheck/FamInst.lhs @@ -1,6 +1,13 @@ The @FamInst@ type: family instance heads \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 FamInst ( checkFamInstConsistency, tcExtendLocalFamInstEnv, tcLookupFamInst, tcLookupDataFamInst, diff --git a/compiler/typecheck/Inst.lhs b/compiler/typecheck/Inst.lhs index 64acaf367a69e895e5a63d8b915ef52e92e36643..5a597501671723b79e6977c274fd828239703936 100644 --- a/compiler/typecheck/Inst.lhs +++ b/compiler/typecheck/Inst.lhs @@ -6,6 +6,13 @@ The @Inst@ type: dictionaries or method instances \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 Inst ( deeplySkolemise, deeplyInstantiate, instCall, instStupidTheta, diff --git a/compiler/typecheck/TcArrows.lhs b/compiler/typecheck/TcArrows.lhs index 0dfe8b0f1e221abce46c74b61318c1211d0c536e..62690a50bd6a1cd81b19af603ca2043dc5474cb2 100644 --- a/compiler/typecheck/TcArrows.lhs +++ b/compiler/typecheck/TcArrows.lhs @@ -5,6 +5,13 @@ Typecheck arrow notation \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 TcArrows ( tcProc ) where import {-# SOURCE #-} TcExpr( tcMonoExpr, tcInferRho, tcSyntaxOp, tcCheckId ) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 0bf1169c54c0d729caa39f36d3075a0bafb84683..83497a8f4ca1012825ea588f4e22cdf3bbf264a6 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -1,4 +1,11 @@ \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 TcCanonical( mkCanonical, mkCanonicals, mkCanonicalFEV, mkCanonicalFEVs, canWanteds, canGivens, canOccursCheck, canEqToWorkList, diff --git a/compiler/typecheck/TcClassDcl.lhs b/compiler/typecheck/TcClassDcl.lhs index 83e91222073bc1eb762307aaa0963f9d7111b219..ab938d368ad0b88a1a6074b124d101c355e5af12 100644 --- a/compiler/typecheck/TcClassDcl.lhs +++ b/compiler/typecheck/TcClassDcl.lhs @@ -6,6 +6,13 @@ Typechecking class declarations \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 TcClassDcl ( tcClassSigs, tcClassDecl2, findMethodBind, instantiateMethod, tcInstanceMethodBody, mkGenericDefMethBind, diff --git a/compiler/typecheck/TcDefaults.lhs b/compiler/typecheck/TcDefaults.lhs index 50b5767cef93614c00d88330f39d0e26931392bb..61193f7f9be279d5f3aef8834fe99d676c0b535e 100644 --- a/compiler/typecheck/TcDefaults.lhs +++ b/compiler/typecheck/TcDefaults.lhs @@ -5,6 +5,13 @@ \section[TcDefaults]{Typechecking \tr{default} declarations} \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 TcDefaults ( tcDefaults ) where import HsSyn diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 2c714efd52ee038ad143c7d2c0f68543323c7b17..a5c55263a3300d01ef2cbe6b25579a5dcb486ef6 100755 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -6,6 +6,13 @@ Handles @deriving@ clauses on @data@ declarations. \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 TcDeriv ( tcDeriving ) where #include "HsVersions.h" diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 0892783d7e64a05192aa8fde1a4b792f12d251c8..b8acec65ba8074c81406c2de1da6702748ae175f 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -1,4 +1,11 @@ \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 TcErrors( reportUnsolved, warnDefaulting, diff --git a/compiler/typecheck/TcExpr.lhs b/compiler/typecheck/TcExpr.lhs index 31023c389d1f32fdd08a8fdb77150b8dce751901..34e429f1189dc6a85d3fd2be5f11719b434756a9 100644 --- a/compiler/typecheck/TcExpr.lhs +++ b/compiler/typecheck/TcExpr.lhs @@ -5,6 +5,13 @@ \section[TcExpr]{Typecheck an expression} \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 + -- 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 diff --git a/compiler/typecheck/TcExpr.lhs-boot b/compiler/typecheck/TcExpr.lhs-boot index 5a4f005fbedbe494c75e0cbed07ed0e131361b87..7bd1e6c5c688f61e42c8c3b7bc7c118996987d06 100644 --- a/compiler/typecheck/TcExpr.lhs-boot +++ b/compiler/typecheck/TcExpr.lhs-boot @@ -1,4 +1,11 @@ \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 ) diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index cf9c46a747b6f07f75472247ccef8e54e6bb2cf3..202dace414d7487c6f01067220a182c7a708b0b3 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -11,6 +11,13 @@ This module is nominally ``subordinate'' to @TcDeriv@, which is the This is where we do all the grimy bindings' generation. \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 TcGenDeriv ( BagDerivStuff, DerivStuff(..), diff --git a/compiler/typecheck/TcGenGenerics.lhs b/compiler/typecheck/TcGenGenerics.lhs index 543204759c5a6fa798916c0cb7bf69f5e7eca9dc..d034a39b953343fc13ee0fd39f5ea1f4c8145e6f 100644 --- a/compiler/typecheck/TcGenGenerics.lhs +++ b/compiler/typecheck/TcGenGenerics.lhs @@ -6,6 +6,13 @@ The deriving code for the Generic class (equivalent to the code in TcGenDeriv, for other classes) \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 TcGenGenerics (canDoGenerics, gen_Generic_binds) where diff --git a/compiler/typecheck/TcHsSyn.lhs b/compiler/typecheck/TcHsSyn.lhs index f805720ab52725afa40c9c4c57fab2f9a931ef24..e50d41bd13106de35fa456f74b562faa1982746c 100644 --- a/compiler/typecheck/TcHsSyn.lhs +++ b/compiler/typecheck/TcHsSyn.lhs @@ -9,6 +9,13 @@ This module is an extension of @HsSyn@ syntax, for use in the type checker. \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 TcHsSyn ( mkHsConApp, mkHsDictLet, mkHsApp, hsLitType, hsLPatType, hsPatType, diff --git a/compiler/typecheck/TcHsType.lhs b/compiler/typecheck/TcHsType.lhs index fd249dadd09de8645c1c93fe91f5253ff9d863d2..b0ef207799ec229a56ee7a7aa9970b6b4596228b 100644 --- a/compiler/typecheck/TcHsType.lhs +++ b/compiler/typecheck/TcHsType.lhs @@ -5,6 +5,13 @@ \section[TcMonoType]{Typechecking user-specified @MonoTypes@} \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 TcHsType ( tcHsSigType, tcHsSigTypeNC, tcHsDeriv, tcHsVectInst, tcHsInstHead, tcHsQuantifiedType, diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs index bddeb2d9bdb342d98f53ca36953f63dd1746d112..01bffce61d4c66be3b0c30e57a531421c5d2e6bf 100644 --- a/compiler/typecheck/TcInstDcls.lhs +++ b/compiler/typecheck/TcInstDcls.lhs @@ -6,6 +6,13 @@ TcInstDecls: Typechecking instance declarations \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 TcInstDcls ( tcInstDecls1, tcInstDecls2 ) where #include "HsVersions.h" diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 7c1bbdd2ff24f5ab53023347c016ed39c717aeda..5315c20dd1829a3913725a565cbb339b871a7b5b 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1,4 +1,11 @@ \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 TcInteract ( solveInteract, solveInteractGiven, solveInteractWanted, AtomicInert, tyVarsOfInert, diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs index 51cf343505b9a842c319c22e38f7cbfccb8997e8..032516bd41b2691c915124164abb012485db090d 100644 --- a/compiler/typecheck/TcMType.lhs +++ b/compiler/typecheck/TcMType.lhs @@ -9,6 +9,13 @@ This module contains monadic operations over types that contain mutable type variables \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 TcMType ( TcTyVar, TcKind, TcType, TcTauType, TcThetaType, TcTyVarSet, diff --git a/compiler/typecheck/TcMatches.lhs b/compiler/typecheck/TcMatches.lhs index bcbdb5dab4de8c3ffc3a74336b223420cf86bc58..cb16fb3cebf8a9d94886d0347e70ab3c2759b2fc 100644 --- a/compiler/typecheck/TcMatches.lhs +++ b/compiler/typecheck/TcMatches.lhs @@ -6,6 +6,13 @@ TcMatches: Typecheck some @Matches@ \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 ( tcMatchesFun, tcGRHSsPat, tcMatchesCase, tcMatchLambda, TcMatchCtxt(..), TcStmtChecker, tcStmts, tcStmtsAndThen, tcDoStmts, tcBody, diff --git a/compiler/typecheck/TcMatches.lhs-boot b/compiler/typecheck/TcMatches.lhs-boot index 8d0fba26997ea515f2f219c526119a83361551d0..fccde2b5487936409c50bbde5d2623ff5c8f3b32 100644 --- a/compiler/typecheck/TcMatches.lhs-boot +++ b/compiler/typecheck/TcMatches.lhs-boot @@ -1,4 +1,11 @@ \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, HsWrapper ) import Name ( Name ) diff --git a/compiler/typecheck/TcPat.lhs b/compiler/typecheck/TcPat.lhs index 6be0a2897841f5cdd83a334f3d8c07209e8b574a..e99d2656fcac7f3c2381bd6d8de4eec3690a962f 100644 --- a/compiler/typecheck/TcPat.lhs +++ b/compiler/typecheck/TcPat.lhs @@ -6,6 +6,13 @@ TcPat: Typechecking patterns \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 TcPat ( tcLetPat, TcSigFun, TcSigInfo(..), TcPragFun , LetBndrSpec(..), addInlinePrags, warnPrags , tcPat, tcPats, newNoSigLetBndr, newSigLetBndr diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs index 412784e91d1d75a96e8c5ffd78cf7e0bdba69afa..4095e41e9af850c30dcc0429e5564f8b3cded755 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -5,6 +5,13 @@ \section[TcMovectle]{Typechecking a whole module} \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 TcRnDriver ( #ifdef GHCI tcRnStmt, tcRnExpr, tcRnType, diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 536391085ec3e4a0180e025efef856ae4f8137b2..6f873be62408be530583420c00d949e905f7ea16 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -16,6 +16,13 @@ For state that is global and should be returned at the end (e.g not part of the stack mechanism), you should use an TcRef (= IORef) to store them. \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 TcRnTypes( TcRnIf, TcRn, TcM, RnM, IfM, IfL, IfG, -- The monad is opaque outside this module TcRef, diff --git a/compiler/typecheck/TcRules.lhs b/compiler/typecheck/TcRules.lhs index 8676555a03e791009004f89b1f19adbe457f7004..9aae216ab5e8d180729d641f897bb372f5b56472 100644 --- a/compiler/typecheck/TcRules.lhs +++ b/compiler/typecheck/TcRules.lhs @@ -6,6 +6,13 @@ TcRules: Typechecking transformation rules \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 TcRules ( tcRules ) where import HsSyn diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 4d5039b3399bbec3b049a9784151b43f094ff2b0..e7d2e496044186daada2a37be0100b37065a652b 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -1,4 +1,11 @@ \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 + -- Type definitions for the constraint solver module TcSMonad ( diff --git a/compiler/typecheck/TcSimplify.lhs b/compiler/typecheck/TcSimplify.lhs index 064545dc687c83bc7956bd66a69ebcd8b0c779ea..dc8c5f95f9d27f4b8a243c194427a2d31807d7ff 100644 --- a/compiler/typecheck/TcSimplify.lhs +++ b/compiler/typecheck/TcSimplify.lhs @@ -1,4 +1,11 @@ \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 TcSimplify( simplifyInfer, simplifyAmbiguityCheck, simplifyDefault, simplifyDeriv, diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index e924303169cc46ccc4598af0f0dd9593de5f95c1..8931378f236d0aa582e5fdf429e0dd39b293b348 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -7,6 +7,13 @@ TcSplice: Template Haskell splices \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 + {-# OPTIONS -fno-warn-unused-imports -fno-warn-unused-binds #-} -- The above warning supression flag is a temporary kludge. -- While working on this module you are encouraged to remove it and fix diff --git a/compiler/typecheck/TcSplice.lhs-boot b/compiler/typecheck/TcSplice.lhs-boot index a75ab3507ba33d07db3113ca6907335199459dee..5cb871a3a1ba94d417d39b279dc836ebe22b5c87 100644 --- a/compiler/typecheck/TcSplice.lhs-boot +++ b/compiler/typecheck/TcSplice.lhs-boot @@ -1,4 +1,11 @@ \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, HsExpr, HsType, LHsType, LHsExpr, LPat, LHsDecl ) diff --git a/compiler/typecheck/TcTyClsDecls.lhs b/compiler/typecheck/TcTyClsDecls.lhs index 7d71b66306b49fe4dd3bcda1c3ee170ae2def20f..7a56db4020c8f920f6d84c70022ba46bf96e9abb 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -6,6 +6,13 @@ TcTyClsDecls: Typecheck type and class declarations \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 TcTyClsDecls ( tcTyAndClassDecls, mkRecSelBinds, diff --git a/compiler/typecheck/TcTyDecls.lhs b/compiler/typecheck/TcTyDecls.lhs index a3dd2b86b3b2c501cfb0c62dc7079d7d319e4b80..f5d880d8fa6b1e59702ab69646e663dcc20a6659 100644 --- a/compiler/typecheck/TcTyDecls.lhs +++ b/compiler/typecheck/TcTyDecls.lhs @@ -9,6 +9,13 @@ This stuff is only used for source-code decls; it's recorded in interface files for imported data types. \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 TcTyDecls( calcRecFlags, calcSynCycles, calcClassCycles diff --git a/compiler/typecheck/TcType.lhs b/compiler/typecheck/TcType.lhs index dea3adc63a281d4debb57e182442e37bdccc4e84..52ee7a2b622c33d5b44d42ca3ba148f77f9dc66b 100644 --- a/compiler/typecheck/TcType.lhs +++ b/compiler/typecheck/TcType.lhs @@ -15,6 +15,13 @@ The "tc" prefix is for "TypeChecker", because the type checker is the principal client. \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 TcType ( -------------------------------- -- Types diff --git a/compiler/typecheck/TcUnify.lhs b/compiler/typecheck/TcUnify.lhs index b48e78b4e3a02b57791ff881fdfa8ce3d10dc7be..b73f70447deab9257dff55ca6507144aee449268 100644 --- a/compiler/typecheck/TcUnify.lhs +++ b/compiler/typecheck/TcUnify.lhs @@ -6,6 +6,13 @@ Type subsumption and unification \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 ( -- Full-blown subsumption tcWrapResult, tcSubType, tcGen, diff --git a/compiler/typecheck/TcUnify.lhs-boot b/compiler/typecheck/TcUnify.lhs-boot index 631b6fecc62ca761a33a1f35960caedf57cf89b2..431bfaabdc6446930891faa40101036834def8d2 100644 --- a/compiler/typecheck/TcUnify.lhs-boot +++ b/compiler/typecheck/TcUnify.lhs-boot @@ -1,4 +1,11 @@ \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 ) import TcRnTypes( TcM ) diff --git a/compiler/types/Class.lhs b/compiler/types/Class.lhs index a96cb2f20e6b4547ab75028b0c20a45a1ab07bb1..18782374996df86b6756b6040205c0469e81c971 100644 --- a/compiler/types/Class.lhs +++ b/compiler/types/Class.lhs @@ -6,6 +6,13 @@ The @Class@ datatype \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 Class ( Class, ClassOpItem, DefMeth (..), diff --git a/compiler/types/Coercion.lhs b/compiler/types/Coercion.lhs index ea2edc3077ba05697b217dc64cb531e6fd31cd39..f21f0cae959b2c46a882135ecc60eda971e55ead 100644 --- a/compiler/types/Coercion.lhs +++ b/compiler/types/Coercion.lhs @@ -3,6 +3,13 @@ % \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 for (a) type kinds and (b) type coercions, -- as used in System FC. See 'CoreSyn.Expr' for -- more on System FC and how coercions fit into it. diff --git a/compiler/types/FamInstEnv.lhs b/compiler/types/FamInstEnv.lhs index 07a15dd644d99c52163bb0b45fcaa104f90dc368..6e9abe0d3e9e5a6a4ce2024d9a02ba40d3703db1 100644 --- a/compiler/types/FamInstEnv.lhs +++ b/compiler/types/FamInstEnv.lhs @@ -5,6 +5,13 @@ FamInstEnv: Type checked family instance declarations \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 FamInstEnv ( FamInst(..), famInstTyCon, famInstTyVars, pprFamInst, pprFamInstHdr, pprFamInsts, diff --git a/compiler/types/FunDeps.lhs b/compiler/types/FunDeps.lhs index 792ca5f82a4f0c9f4b365c64a20eea18129c82f1..03b4b0a55e0992f64c2bd37020c6d87986c8a0dc 100644 --- a/compiler/types/FunDeps.lhs +++ b/compiler/types/FunDeps.lhs @@ -8,6 +8,13 @@ FunDeps - functional dependencies It's better to read it as: "if we know these, then we're going to know these" \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 FunDeps ( FDEq (..), Equation(..), pprEquation, diff --git a/compiler/types/Kind.lhs b/compiler/types/Kind.lhs index 2bdabc639a0399cb2759d96fb0f162868eb7b036..e5ef583c99829343d1de31fe8f7807f4f8c6cbcf 100644 --- a/compiler/types/Kind.lhs +++ b/compiler/types/Kind.lhs @@ -3,6 +3,13 @@ % \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 Kind ( -- * Main data type Kind, typeKind, diff --git a/compiler/types/OptCoercion.lhs b/compiler/types/OptCoercion.lhs index c5b3e2955a125cf9716b72b8b3cc1fa9f5325345..4880e68a3af4c2051c82f68f5020668205c64bf3 100644 --- a/compiler/types/OptCoercion.lhs +++ b/compiler/types/OptCoercion.lhs @@ -3,6 +3,13 @@ % \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 OptCoercion ( optCoercion ) where #include "HsVersions.h" diff --git a/compiler/types/TyCon.lhs b/compiler/types/TyCon.lhs index 45a11bc89d5a4d536819a6bc80890d91a3031ad0..6db746bc769338126b2ed1bbf503605d8b632f49 100644 --- a/compiler/types/TyCon.lhs +++ b/compiler/types/TyCon.lhs @@ -6,6 +6,13 @@ The @TyCon@ datatype \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( -- * Main TyCon data types TyCon, FieldLabel, diff --git a/compiler/types/TyCon.lhs-boot b/compiler/types/TyCon.lhs-boot index 51ea99b17c940f1ec7cd171a2ed629967b835169..dcf41dd54543b295a35c02b7ea6a2f1138ec631a 100644 --- a/compiler/types/TyCon.lhs-boot +++ b/compiler/types/TyCon.lhs-boot @@ -1,4 +1,11 @@ \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) diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs index 0811ba5845e0903f05619dcef1f9a6ab840891be..c662d19031cb1f0760512934db3ebde21951bb64 100644 --- a/compiler/types/Type.lhs +++ b/compiler/types/Type.lhs @@ -6,6 +6,13 @@ Type - public interface \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 + -- 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 diff --git a/compiler/types/TypeRep.lhs b/compiler/types/TypeRep.lhs index 2908047ad39b868851b958893d329f732b200c12..df3c9cab77067485cec5f0c70c064c802e256ab5 100644 --- a/compiler/types/TypeRep.lhs +++ b/compiler/types/TypeRep.lhs @@ -5,6 +5,13 @@ \section[TypeRep]{Type - friends' interface} \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 + -- We expose the relevant stuff from this module via the Type module {-# OPTIONS_HADDOCK hide #-} {-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable #-} diff --git a/compiler/types/Unify.lhs b/compiler/types/Unify.lhs index 06bae088c0312d483e9f58a1bcdf33fde1eb9a60..575bcfbeead2db8c61309bea41806d6675a7d889 100644 --- a/compiler/types/Unify.lhs +++ b/compiler/types/Unify.lhs @@ -3,6 +3,13 @@ % \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 Unify ( -- Matching of types: -- the "tc" prefix indicates that matching always diff --git a/compiler/utils/BufWrite.hs b/compiler/utils/BufWrite.hs index 306413573f322f0c9bbcf80a71d0d0b03bf4ebe9..ba26be374e03f807b07a75f40a4f90c957bb09c7 100644 --- a/compiler/utils/BufWrite.hs +++ b/compiler/utils/BufWrite.hs @@ -10,6 +10,13 @@ -- ----------------------------------------------------------------------------- +{-# 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 BufWrite ( BufHandle(..), newBufHandle, diff --git a/compiler/utils/Digraph.lhs b/compiler/utils/Digraph.lhs index aa0f654e0c776f52b06b19fd4f0e2ae4959c7ce8..1bb460674cd2adfcda353b84be18bb826f5781c7 100644 --- a/compiler/utils/Digraph.lhs +++ b/compiler/utils/Digraph.lhs @@ -3,6 +3,13 @@ % \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 + {-# LANGUAGE ScopedTypeVariables #-} module Digraph( Graph, graphFromVerticesAndAdjacency, graphFromEdgedVertices, diff --git a/compiler/utils/FastMutInt.lhs b/compiler/utils/FastMutInt.lhs index 26183071f15c2622b5d5cd8ad7eafd5612822535..d29bb9136c3f1b476fe345a800f479856aaa909b 100644 --- a/compiler/utils/FastMutInt.lhs +++ b/compiler/utils/FastMutInt.lhs @@ -1,4 +1,11 @@ \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 + {-# LANGUAGE BangPatterns #-} {-# OPTIONS -cpp #-} {-# OPTIONS_GHC -O #-} diff --git a/compiler/utils/GraphBase.hs b/compiler/utils/GraphBase.hs index 249626eb279c0a48767abfef54f7c835689754aa..c070df47620f1b359b82efc14eb47a183dc53158 100644 --- a/compiler/utils/GraphBase.hs +++ b/compiler/utils/GraphBase.hs @@ -1,6 +1,13 @@ -- | Types for the general graph colorer. +{-# 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 GraphBase ( Triv, Graph (..), diff --git a/compiler/utils/GraphColor.hs b/compiler/utils/GraphColor.hs index 8dc41216e7996e194fc45ad4df7d2d3ce3f0ef28..b9ed3e2643a40a9faa9e267537749e7515ca5396 100644 --- a/compiler/utils/GraphColor.hs +++ b/compiler/utils/GraphColor.hs @@ -1,5 +1,12 @@ {-# OPTIONS -fno-warn-missing-signatures #-} +{-# 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 + -- | Graph Coloring. -- This is a generic graph coloring library, abstracted over the type of -- the node keys, nodes and colors. diff --git a/compiler/utils/GraphOps.hs b/compiler/utils/GraphOps.hs index 1fa4199aa22c9b2ac99ca9cda8c1b68adb2761f5..69d4943fb0897f1e906a924b31cee8a604de889a 100644 --- a/compiler/utils/GraphOps.hs +++ b/compiler/utils/GraphOps.hs @@ -1,4 +1,11 @@ {-# OPTIONS -fno-warn-missing-signatures #-} +{-# 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 + -- | Basic operations on graphs. -- diff --git a/compiler/utils/GraphPpr.hs b/compiler/utils/GraphPpr.hs index 8149b2aa86363e86ebef4a011ceb1085df9d17a1..5ea5fdfb75c20c0aeeb8f5bf6ab56fcd5f284225 100644 --- a/compiler/utils/GraphPpr.hs +++ b/compiler/utils/GraphPpr.hs @@ -1,6 +1,13 @@ -- | Pretty printing of graphs. +{-# 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 GraphPpr ( dumpGraph, dotGraph diff --git a/compiler/utils/ListSetOps.lhs b/compiler/utils/ListSetOps.lhs index 334fb5968934bad133322b34cb9ef62e01f90197..2c6c6b0b6ccfe793c2c533e1629285c966824756 100644 --- a/compiler/utils/ListSetOps.lhs +++ b/compiler/utils/ListSetOps.lhs @@ -5,6 +5,13 @@ \section[ListSetOps]{Set-like operations on lists} \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 ListSetOps ( unionLists, minusList, insertList, diff --git a/compiler/utils/Maybes.lhs b/compiler/utils/Maybes.lhs index 39e6185a19eedbc355a31573e951e5ac0f05994b..5d8fcfa6cc8a2c1ac4cf0cf2e7d66617de9ba7f3 100644 --- a/compiler/utils/Maybes.lhs +++ b/compiler/utils/Maybes.lhs @@ -4,6 +4,13 @@ % \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 Maybes ( module Data.Maybe, diff --git a/compiler/utils/MonadUtils.hs b/compiler/utils/MonadUtils.hs index 75a88dfcbd77ed837279c60aac10d550d7207dba..3108a03d6486331edc19bb930aa955a8ec83c743 100644 --- a/compiler/utils/MonadUtils.hs +++ b/compiler/utils/MonadUtils.hs @@ -2,6 +2,13 @@ -- | Utilities related to Monad and Applicative classes -- Mostly for backwards compatability. +{-# 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 MonadUtils ( Applicative(..) , (<$>) diff --git a/compiler/utils/OrdList.lhs b/compiler/utils/OrdList.lhs index 74c9ed8d0b1e2191b160a9d6601009b07cbe1ca7..a56cdf3f58e1efc4c08a072a53bbd3b6aadc9ee6 100644 --- a/compiler/utils/OrdList.lhs +++ b/compiler/utils/OrdList.lhs @@ -9,6 +9,13 @@ Provide trees (of instructions), so that lists of instructions can be appended in linear time. \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 OrdList ( OrdList, nilOL, isNilOL, unitOL, appOL, consOL, snocOL, concatOL, diff --git a/compiler/utils/Outputable.lhs b/compiler/utils/Outputable.lhs index bb4685d02c0ccc11ce8dfa92fcee4d84f7863ba4..d69e8ada63d08430611b0d97ddbc527b93880b6f 100644 --- a/compiler/utils/Outputable.lhs +++ b/compiler/utils/Outputable.lhs @@ -4,6 +4,13 @@ % \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 + -- | This module defines classes and functions for pretty-printing. It also -- exports a number of helpful debugging and other utilities such as 'trace' and 'panic'. -- diff --git a/compiler/utils/Panic.lhs b/compiler/utils/Panic.lhs index 1fd815604c204ecac2708b44cf684a8be247cd94..4cf2695b761414b12af4cbbe025d09141a53855b 100644 --- a/compiler/utils/Panic.lhs +++ b/compiler/utils/Panic.lhs @@ -8,6 +8,13 @@ It's hard to put these functions anywhere else without causing some unnecessary loops in the module dependency graph. \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 Panic ( GhcException(..), showGhcException, throwGhcException, handleGhcException, ghcError, progName, diff --git a/compiler/utils/UniqFM.lhs b/compiler/utils/UniqFM.lhs index 0cd9235cadc0bf17772d2c062d2b68851d23fc22..c3d204215e720d6be2f749247bc81598c62887ca 100644 --- a/compiler/utils/UniqFM.lhs +++ b/compiler/utils/UniqFM.lhs @@ -20,6 +20,13 @@ and ``addToUFM\_C'' and ``Data.IntMap.insertWith'' differ in the order of arguments of combining function. \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 + {-# OPTIONS -Wall #-} module UniqFM ( -- * Unique-keyed mappings diff --git a/compiler/utils/UniqSet.lhs b/compiler/utils/UniqSet.lhs index 443d28b3e45eb6a83fea35f354db83152aae03c5..f8e7d9039f739e759dce949828a6bd5ff4547e14 100644 --- a/compiler/utils/UniqSet.lhs +++ b/compiler/utils/UniqSet.lhs @@ -9,6 +9,13 @@ Based on @UniqFMs@ (as you would expect). Basically, the things need to be in class @Uniquable@. \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 UniqSet ( -- * Unique set type UniqSet, -- type synonym for UniqFM a diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs index dccb52dbb7a6b54a6b671c60ffc91bc3e39e8ba1..5fa4691113dfd106da897557017c1fd30443a42c 100644 --- a/compiler/utils/Util.lhs +++ b/compiler/utils/Util.lhs @@ -4,6 +4,13 @@ % \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 + -- | Highly random utility functions module Util ( -- * Flags dependent on the compiler build diff --git a/compiler/vectorise/Vectorise/Monad/Local.hs b/compiler/vectorise/Vectorise/Monad/Local.hs index ce9b494c5a060487d1478831bc4143d07cd4d23e..4ead2f436e61ac5601c897b15a22d36eebed3158 100644 --- a/compiler/vectorise/Vectorise/Monad/Local.hs +++ b/compiler/vectorise/Vectorise/Monad/Local.hs @@ -1,4 +1,11 @@ +{-# 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 Vectorise.Monad.Local ( readLEnv, setLEnv, diff --git a/compiler/vectorise/Vectorise/Type/PRepr.hs b/compiler/vectorise/Vectorise/Type/PRepr.hs index db26366d4c55a0823ad7ca84a56cfe3b69c4c08f..18191ca732d451dfa1bfb61f525abf50b1bfdf01 100644 --- a/compiler/vectorise/Vectorise/Type/PRepr.hs +++ b/compiler/vectorise/Vectorise/Type/PRepr.hs @@ -1,4 +1,11 @@ +{-# 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 Vectorise.Type.PRepr ( buildPReprTyCon , buildPAScAndMethods diff --git a/compiler/vectorise/Vectorise/Type/TyConDecl.hs b/compiler/vectorise/Vectorise/Type/TyConDecl.hs index 600afd2c249d26f5fc6c309316e284d729aaef10..38af2dc84671212f9efd838378ba810ec57b39c6 100644 --- a/compiler/vectorise/Vectorise/Type/TyConDecl.hs +++ b/compiler/vectorise/Vectorise/Type/TyConDecl.hs @@ -1,3 +1,10 @@ +{-# 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 Vectorise.Type.TyConDecl ( vectTyConDecls ) where diff --git a/compiler/vectorise/Vectorise/Utils/Hoisting.hs b/compiler/vectorise/Vectorise/Utils/Hoisting.hs index d0785e51488d92c793a0961a432785d9d0fa3557..3625508515d42e753bad7a6689b3e78b48a6cef1 100644 --- a/compiler/vectorise/Vectorise/Utils/Hoisting.hs +++ b/compiler/vectorise/Vectorise/Utils/Hoisting.hs @@ -1,4 +1,11 @@ +{-# 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 Vectorise.Utils.Hoisting ( Inline(..), addInlineArity, diff --git a/compiler/vectorise/Vectorise/Utils/Poly.hs b/compiler/vectorise/Vectorise/Utils/Poly.hs index a27afeaf992c0b00aadf015f67ac8af04b575c59..5f554d731f2a14845c7372d7adf69c8401bc45ac 100644 --- a/compiler/vectorise/Vectorise/Utils/Poly.hs +++ b/compiler/vectorise/Vectorise/Utils/Poly.hs @@ -1,4 +1,11 @@ +{-# 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 Vectorise.Utils.Poly ( polyAbstract, polyApply, diff --git a/compiler/vectorise/Vectorise/Var.hs b/compiler/vectorise/Vectorise/Var.hs index 9c81d301183d0a7f26f235af21dd7396219eb4cf..ea549f3a2ed1fedf28722ef112515def24be3a98 100644 --- a/compiler/vectorise/Vectorise/Var.hs +++ b/compiler/vectorise/Vectorise/Var.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Vectorise variables and literals. module Vectorise.Var ( vectBndr, diff --git a/compiler/vectorise/Vectorise/Vect.hs b/compiler/vectorise/Vectorise/Vect.hs index 156d540bc6eb231a09d82eeac261e03e085f8546..a093cfc40478ba71757a12a958eaefc63380f868 100644 --- a/compiler/vectorise/Vectorise/Vect.hs +++ b/compiler/vectorise/Vectorise/Vect.hs @@ -1,4 +1,11 @@ +{-# 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 + -- | Simple vectorised constructors and projections. module Vectorise.Vect ( Vect, VVar, VExpr, VBind, diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index 66b3c05b44af6297a59f47e2580e041250e9e816..55d8946c4f3cdb04d1aead37e5936ecb59a7d463 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -1,6 +1,13 @@ {-# OPTIONS_GHC -fno-cse -fno-warn-orphans #-} -- -fno-cse is needed for GLOBAL_VAR's to behave properly +{-# 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#TabsvsSp +-- for details + ----------------------------------------------------------------------------- -- -- Monadery code used in InteractiveUI diff --git a/ghc/GhciTags.hs b/ghc/GhciTags.hs index df826e1926011731a54c9559b3e33544a4ae8a71..a3ad646309d1164fbd0f5b94265779eabbd72800 100644 --- a/ghc/GhciTags.hs +++ b/ghc/GhciTags.hs @@ -6,6 +6,13 @@ -- ----------------------------------------------------------------------------- +{-# 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#TabsvsSp +-- for details + {-# OPTIONS_GHC -fno-warn-name-shadowing #-} module GhciTags ( createCTagsWithLineNumbersCmd, diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 5b1c6817a35de1cc483fb786a6288d2b45a2babb..0525f4098cd8171b9b6951572ac596af8934458d 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -1,6 +1,13 @@ {-# OPTIONS -fno-cse #-} -- -fno-cse is needed for GLOBAL_VAR's to behave properly +{-# 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#TabsvsSp +-- for details + {-# OPTIONS_GHC -fno-warn-name-shadowing #-} ----------------------------------------------------------------------------- -- diff --git a/ghc/Main.hs b/ghc/Main.hs index d44ecc58af1344df09d3eec020725d79a7449bbb..4829a4f5a8dc3bafe43cff860f1f548321c950a5 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -1,5 +1,12 @@ {-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-} +{-# 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#TabsvsSp +-- for details + ----------------------------------------------------------------------------- -- -- GHC Driver program diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index f0d8de1a2a580f3df9e57ba30870f9395eced8c4..6afac177a6049e71165aa0be3a248550f6175228 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -19,9 +19,9 @@ SRC_HC_OPTS += -Wall $(WERROR) -H64m -O0 # Safe by default #SRC_HC_OPTS += -Dsh_SAFE_DEFAULT -GhcStage1HcOpts += -O +GhcStage1HcOpts += -O -fwarn-tabs -GhcStage2HcOpts += -O +GhcStage2HcOpts += -O -fwarn-tabs # Using -O (rather than -O0) here bringes my validate down from 22mins to 16 mins. # Compiling stage2 takes longer, but we gain a faster haddock, faster # running of the tests, and faster building of the utils to be installed diff --git a/utils/genprimopcode/Main.hs b/utils/genprimopcode/Main.hs index df6c46b2b74740d7042635b4f1489018d2d4f13e..da15c2532c7d1b7f4aa770c03433f31d4c86e163 100644 --- a/utils/genprimopcode/Main.hs +++ b/utils/genprimopcode/Main.hs @@ -1,4 +1,11 @@ {-# OPTIONS -cpp #-} +{-# 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 + ------------------------------------------------------------------ -- A primop-table mangling program -- ------------------------------------------------------------------ diff --git a/utils/genprimopcode/Syntax.hs b/utils/genprimopcode/Syntax.hs index 5fe4e0b23e42f2c94425f697deb9350f83bdd17c..b20712b62de8e10efbd855128c259d1792692d7c 100644 --- a/utils/genprimopcode/Syntax.hs +++ b/utils/genprimopcode/Syntax.hs @@ -1,4 +1,11 @@ +{-# 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 Syntax where import Data.List