Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Shayne Fletcher
Glasgow Haskell Compiler
Commits
17b297d9
Commit
17b297d9
authored
Sep 01, 2007
by
Ian Lynagh
Browse files
Add {-# OPTIONS_GHC -w #-} and some blurb to all compiler modules
parent
e11fa7a5
Changes
298
Hide whitespace changes
Inline
Side-by-side
compiler/Makefile
View file @
17b297d9
...
...
@@ -218,6 +218,7 @@ boot :: $(CONFIG_HS)
$(CONFIG_HS)
:
$(FPTOOLS_TOP)/mk/config.mk
@
$(RM)
-f
$(CONFIG_HS)
@
echo
"Creating
$(CONFIG_HS)
... "
@
echo
"{-# OPTIONS_GHC -w #-}"
>>
$(CONFIG_HS)
@
echo
"module Config where"
>>
$(CONFIG_HS)
@
echo
"cProjectName =
\"
$(ProjectName)
\"
"
>>
$(CONFIG_HS)
@
echo
"cProjectVersion =
\"
$(ProjectVersion)
\"
"
>>
$(CONFIG_HS)
...
...
compiler/basicTypes/BasicTypes.lhs
View file @
17b297d9
...
...
@@ -14,6 +14,13 @@ types that
\end{itemize}
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module BasicTypes(
Version, bumpVersion, initialVersion,
...
...
compiler/basicTypes/DataCon.lhs
View file @
17b297d9
...
...
@@ -5,6 +5,13 @@
\section[DataCon]{@DataCon@: Data Constructors}
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module DataCon (
DataCon, DataConIds(..),
ConTag, fIRST_TAG,
...
...
compiler/basicTypes/Demand.lhs
View file @
17b297d9
...
...
@@ -5,6 +5,13 @@
\section[Demand]{@Demand@: the amount of demand on a value}
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
#ifndef OLD_STRICTNESS
module Demand () where
#else
...
...
compiler/basicTypes/Id.lhs
View file @
17b297d9
...
...
@@ -5,6 +5,13 @@
\section[Id]{@Ids@: Value and constructor identifiers}
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module Id (
Id, DictId,
...
...
compiler/basicTypes/IdInfo.lhs
View file @
17b297d9
...
...
@@ -8,6 +8,13 @@
Haskell. [WDP 94/11])
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module IdInfo (
GlobalIdDetails(..), notGlobalId, -- Not abstract
...
...
compiler/basicTypes/Literal.lhs
View file @
17b297d9
...
...
@@ -5,6 +5,13 @@
\section[Literal]{@Literal@: Machine literals (unboxed, of course)}
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module Literal
( Literal(..) -- Exported to ParseIface
, mkMachInt, mkMachWord
...
...
compiler/basicTypes/MkId.lhs
View file @
17b297d9
...
...
@@ -12,6 +12,13 @@ have a standard form, namely:
* primitive operations
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module MkId (
mkDictFunId, mkDefaultMethodId,
mkDictSelId,
...
...
compiler/basicTypes/Module.lhs
View file @
17b297d9
...
...
@@ -9,6 +9,13 @@ These are Uniquable, hence we can build FiniteMaps with Modules as
the keys.
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module Module
(
-- * The ModuleName type
...
...
compiler/basicTypes/Name.lhs
View file @
17b297d9
...
...
@@ -5,6 +5,13 @@
\section[Name]{@Name@: to transmit name info from renamer to typechecker}
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module Name (
-- Re-export the OccName stuff
module OccName,
...
...
compiler/basicTypes/NameEnv.lhs
View file @
17b297d9
...
...
@@ -5,6 +5,13 @@
\section[NameEnv]{@NameEnv@: name environments}
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module NameEnv (
NameEnv, mkNameEnv,
emptyNameEnv, unitNameEnv, nameEnvElts, nameEnvUniqueElts,
...
...
compiler/basicTypes/NameSet.lhs
View file @
17b297d9
...
...
@@ -4,6 +4,13 @@
%
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module NameSet (
-- Sets of Names
NameSet,
...
...
compiler/basicTypes/NewDemand.lhs
View file @
17b297d9
...
...
@@ -5,6 +5,13 @@
\section[Demand]{@Demand@: the amount of demand on a value}
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module NewDemand(
Demand(..),
topDmd, lazyDmd, seqDmd, evalDmd, errDmd, isStrictDmd,
...
...
compiler/basicTypes/OccName.lhs
View file @
17b297d9
...
...
@@ -4,6 +4,13 @@
%
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module OccName (
-- * The NameSpace type; abstact
NameSpace, tcName, clsName, tcClsName, dataName, varName,
...
...
compiler/basicTypes/RdrName.lhs
View file @
17b297d9
...
...
@@ -4,6 +4,13 @@
%
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module RdrName (
RdrName(..), -- Constructors exported only to BinIface
...
...
compiler/basicTypes/SrcLoc.lhs
View file @
17b297d9
...
...
@@ -3,6 +3,13 @@
%
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module SrcLoc (
SrcLoc, -- Abstract
...
...
compiler/basicTypes/UniqSupply.lhs
View file @
17b297d9
...
...
@@ -4,6 +4,13 @@
%
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module UniqSupply (
UniqSupply, -- Abstractly
...
...
compiler/basicTypes/Unique.lhs
View file @
17b297d9
...
...
@@ -16,6 +16,13 @@ Some of the other hair in this code is to be able to use a
Haskell).
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module Unique (
Unique, Uniquable(..), hasKey,
...
...
compiler/basicTypes/Var.lhs
View file @
17b297d9
...
...
@@ -5,6 +5,13 @@
\section{@Vars@: Variables}
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module Var (
Var,
varName, varUnique, varType,
...
...
compiler/basicTypes/VarEnv.lhs
View file @
17b297d9
...
...
@@ -4,6 +4,13 @@
%
\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details
module VarEnv (
VarEnv, IdEnv, TyVarEnv,
emptyVarEnv, unitVarEnv, mkVarEnv,
...
...
Prev
1
2
3
4
5
…
15
Next
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment